Safe Haskell | Safe-Infered |
---|
This is the top level module which exports the API
- sym :: String -> Expr a
- symDependent :: String -> Expr a -> Expr a
- symDependentN :: String -> Expr a -> Int -> Expr a
- rad :: (Num a, Ord a, Hashable a) => Expr a -> [Expr a] -> [Expr a]
- data Expr a
- toFunGraph :: (Eq a, Hashable a, Show a, ToFunGraph b, ToFunGraph c, NumT b ~ a, NumT c ~ a) => b -> c -> IO (FunGraph a)
- cse :: (Eq a, Hashable a) => FunGraph a -> FunGraph a
- previewGraph :: (Ord a, Show a) => FunGraph a -> IO ()
- previewGraph' :: (Ord a, Show a) => FunGraph a -> IO ()
- data a :* b = a :* b
primitives
symDependent :: String -> Expr a -> Expr aSource
Symbolic scalar which is a function of some independent variable, like time. . This lets you do d(f(g(t)))/dt == f'(g(t))*g'(t)
symDependentN :: String -> Expr a -> Int -> Expr aSource
same as symDependent but it can start as the Nth derivative
operations
symbolic expression type
Typeable1 Expr | |
Eq a => Eq (Expr a) | |
(Floating a, Ord a) => Floating (Expr a) | |
(Fractional a, Ord a) => Fractional (Expr a) | |
(Data a, Floating a) => Data (Expr a) | |
(Num a, Ord a) => Num (Expr a) | |
Show a => Show (Expr a) | |
Hashable a => Hashable (Expr a) | |
MuRef (Expr a) | |
ToFunGraph [[Expr a]] | |
ToFunGraph [Expr a] | |
ToFunGraph (Expr a) |
construct FunGraphs
toFunGraph :: (Eq a, Hashable a, Show a, ToFunGraph b, ToFunGraph c, NumT b ~ a, NumT c ~ a) => b -> c -> IO (FunGraph a)Source
Take inputs and outputs which are of classes ToFunGraph (heterogenous lists of Expr a
)
and traverse the outputs reifying all expressions and creating a hashmap of StableNames (stable pointers).
Once the hashmap is created, lookup the provided inputs and return a FunGraph which contains an
expression graph, input/output indices, and other useful functions. StableNames is non-deterministic
so this function may return graphs with more or fewer CSE's eliminated.
If CSE is then performed on the graph, the result is deterministic.
show/summarize FunGraphs
previewGraph' :: (Ord a, Show a) => FunGraph a -> IO ()Source
show a nice Dot graph with labeled edges
compile and link function
Heterogenous inputs/outputs
a :* b |
(Show a, Show b) => Show (:* a b) | |
(ToFunGraph a, ToFunGraph b, ~ * (NumT a) (NumT b)) => ToFunGraph (:* a b) |