| Copyright | (C) 2023 Alexey Tochin | 
|---|---|
| License | BSD3 (see the file LICENSE) | 
| Maintainer | Alexey Tochin <Alexey.Tochin@gmail.com> | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
| Extensions | 
 | 
Debug.SimpleExpr.Expr
Description
Simple expressions base types and manipulations.
Synopsis
- number :: Integer -> SimpleExpr
- variable :: String -> SimpleExpr
- unaryFunc :: String -> SimpleExpr -> SimpleExpr
- binaryFunc :: String -> SimpleExpr -> SimpleExpr -> SimpleExpr
- simplify :: SimpleExpr -> SimpleExpr
- simplifyStep :: (SimpleExpr -> SimpleExpr) -> SimpleExpr -> SimpleExpr
- data SimpleExprF a- = NumberF Integer
- | VariableF String
- | BinaryFuncF String a a
- | SymbolicFuncF String [a]
 
- type SimpleExpr = Fix SimpleExprF
- type Expr = ListOf SimpleExpr
- class ListOf inner outer
- content :: ListOf inner outer => outer -> [inner]
- dependencies :: SimpleExpr -> [SimpleExpr]
- showWithBrackets :: SimpleExpr -> String
Expression manipulation
number :: Integer -> SimpleExpr Source #
Initializes a single integer number expression.
Examples of usage
>>>a = number 42>>>a42>>>:t aa :: SimpleExpr
variable :: String -> SimpleExpr Source #
Initializes a single symbolic variable expression.
Examples of usage
>>>x = variable "x">>>xx>>>:t xx :: SimpleExpr
unaryFunc :: String -> SimpleExpr -> SimpleExpr Source #
Inituialize unarry function
Examples of usage
>>>x = variable "x">>>f = unaryFunc "f">>>f xf(x)>>>:t xx :: SimpleExpr>>>:t ff :: SimpleExpr -> SimpleExpr
binaryFunc :: String -> SimpleExpr -> SimpleExpr -> SimpleExpr Source #
Inituialize unarry function
Examples of usage
>>>x = variable "x">>>y = variable "y">>>(-*-) = binaryFunc "-*-">>>x -*- yx-*-y>>>:t xx :: SimpleExpr>>>:t (-*-)(-*-) :: SimpleExpr -> SimpleExpr -> SimpleExpr>>>:t x-*-yx-*-y :: SimpleExpr
simplify :: SimpleExpr -> SimpleExpr Source #
Simplify expression using some primitive rules like '0 * x -> 0' specified in simplifyStep implementation.
Examples of usage
>>>import Prelude (($))>>>import Debug.SimpleExpr (variable, simplify)>>>import NumHask ((+), (-), (*))
>>>x = variable "x">>>simplify $ (x + 0) * 1 - x * (3 - 2)0
simplifyStep :: (SimpleExpr -> SimpleExpr) -> SimpleExpr -> SimpleExpr Source #
Minimalistic simplification step.
Examples of usage
>>>import Prelude (($), id)>>>import NumHask ((+), (*), (**))
>>>simplifyStep id (0 + (0 + (0 + 10)))0+(0+10)
>>>simplifyStep id (1 * (0 + (10 ** 1)))0+(10^1)
Base types
data SimpleExprF a Source #
Expression F-algebra functional.
Constructors
| NumberF Integer | |
| VariableF String | |
| BinaryFuncF String a a | |
| SymbolicFuncF String [a] | 
Instances
type SimpleExpr = Fix SimpleExprF Source #
Simple expression type, see tutorial
type Expr = ListOf SimpleExpr Source #
Expression typeclass.
 It includes SimpleExpr as well as list and tuples of SimpleExpr etc.
Auxiliary functions
class ListOf inner outer Source #
Entity that is representable as a list of in general other entities.
 In particular, X is a list of single [X], see the example below.
Examples of usage
>>>data Atom = Atom String deriving Show>>>type Particle = ListOf Atom
>>>content (Atom "He") :: [Atom][Atom "He"]
>>>content (Atom "H", Atom "H") :: [Atom][Atom "H",Atom "H"]
>>>content [Atom "H", Atom "O", Atom "H"] :: [Atom][Atom "H",Atom "O",Atom "H"]
Minimal complete definition
Instances
| ListOf inner () Source # | |
| Defined in Debug.SimpleExpr.Expr | |
| ListOf inner inner Source # | |
| Defined in Debug.SimpleExpr.Expr | |
| ListOf inner outer => ListOf inner [outer] Source # | |
| Defined in Debug.SimpleExpr.Expr | |
| (ListOf inner outer1, ListOf inner outer2) => ListOf inner (outer1, outer2) Source # | |
| Defined in Debug.SimpleExpr.Expr | |
| (ListOf inner outer1, ListOf inner outer2, ListOf inner outer3) => ListOf inner (outer1, outer2, outer3) Source # | |
| Defined in Debug.SimpleExpr.Expr | |
| (ListOf inner outer1, ListOf inner outer2, ListOf inner outer3, ListOf inner outer4) => ListOf inner (outer1, outer2, outer3, outer4) Source # | |
| Defined in Debug.SimpleExpr.Expr | |
| (ListOf inner outer1, ListOf inner outer2, ListOf inner outer3, ListOf inner outer4, ListOf inner outer5) => ListOf inner (outer1, outer2, outer3, outer4, outer5) Source # | |
| Defined in Debug.SimpleExpr.Expr | |
content :: ListOf inner outer => outer -> [inner] Source #
Returns a list of entities the argument consists of.
dependencies :: SimpleExpr -> [SimpleExpr] Source #
Returns the list of head dependencies of an expression.
Examples of usage
>>>import Prelude (($), id)>>>import NumHask ((+), (*))
>>>dependencies (variable "x" + (variable "y" * variable "z"))[x,y·z]
showWithBrackets :: SimpleExpr -> String Source #
Shows expression adding brackets if it is needed for a context.