Copyright | (c) Kristof Bastiaensen, 2015 |
---|---|
License | BSD-3 |
Maintainer | kristof@resonata.be |
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
This module implements an equation solver that solves and evaluates expressions on the fly. It is based on Prof. D.E.Knuth's metafont. The goal of mfsolve is to make the solver useful in an interactive program, by enhancing the bidirectionality of the solver. Like metafont, it can solve linear equations, and evaluate nonlinear expressions. In addition to metafont, it also solves for angles, and makes the solution independend of the order of the equations.
The Expr
datatype allows for calculations with constants and unknown
variables. The Dependencies
datatype contains all dependencies and known equations.
Examples:
Let's define some variables. The SimpleVar
type is a simple wrapper
around String
to provide nice output.
let [x, y, t, a] = map (makeVariable . SimpleVar) ["x", "y", "t", "a"]
Solve linear equations:
showVars $ solveEqs emptyDeps [ 2*x + y === 5, x - y === 1]
x = 2.0 y = 1.0
Solve for angle (pi/4):
showVars $ solveEqs emptyDeps [ sin(t) === 1/sqrt(2) ]
t = 0.7853981633974484
Solve for angle (pi/3) and amplitude:
showVars $ solveEqs emptyDeps [ a*sin(x) === sqrt 3, a*cos(x) === 1 ]
x = 1.0471975511965979 a = 2.0
Allow nonlinear expression with unknown variables:
showVars $ solveEqs emptyDeps [ sin(sqrt(x)) === y, x === 2]
x = 2.0 y = 0.9877659459927355
Find the angle and amplitude when using a rotation matrix:
showVars $ solveEqs emptyDeps [ a*cos t*x - a*sin t*y === 30, a*sin t*x + a*cos t*y === 40, x === 10, y === 10 ]
x = 10.0 y = 10.0 t = 0.14189705460416402 a = 3.5355339059327373
- data SimpleExpr v n
- = SEBin BinaryOp (SimpleExpr v n) (SimpleExpr v n)
- | SEUn UnaryOp (SimpleExpr v n)
- | Var v
- | Const n
- data Expr v n
- data LinExpr v n = LinExpr n [(v, n)]
- data UnaryOp
- data BinaryOp
- data Dependencies v n
- data DepError n
- newtype SimpleVar = SimpleVar String
- getKnown :: (Eq v, Hashable v) => Dependencies v n -> v -> Either [v] n
- knownVars :: Dependencies v n -> [(v, n)]
- varDefined :: (Eq v, Hashable v) => Dependencies v n -> v -> Bool
- nonlinearEqs :: (Ord n, Ord v, Floating n) => Dependencies v n -> [Expr v n]
- dependendVars :: Eq n => Dependencies v n -> [(v, LinExpr v n)]
- simpleExpr :: (Num n, Eq n) => Expr v n -> SimpleExpr v n
- emptyDeps :: Dependencies v n
- makeVariable :: Num n => v -> Expr v n
- makeConstant :: n -> Expr v n
- (===) :: (Hashable n, Hashable v, RealFrac (Phase n), Ord v, Floating n) => Expr v n -> Expr v n -> Dependencies v n -> Either (DepError n) (Dependencies v n)
- (=&=) :: (Hashable n, Hashable v, RealFrac (Phase n), Ord v, Floating n) => (Expr v n, Expr v n) -> (Expr v n, Expr v n) -> Dependencies v n -> Either (DepError n) (Dependencies v n)
- solveEqs :: Dependencies v n -> [Dependencies v n -> Either (DepError n) (Dependencies v n)] -> Either (DepError n) (Dependencies v n)
- showVars :: (Show n, Show v, Show a, Ord n, Ord v, Floating n) => Either (DepError a) (Dependencies v n) -> IO ()
Documentation
data SimpleExpr v n Source
A simplified datatype representing an expression
SEBin BinaryOp (SimpleExpr v n) (SimpleExpr v n) | |
SEUn UnaryOp (SimpleExpr v n) | |
Var v | |
Const n |
An mathematical expression of several variables.
A linear expression of several variables.
For example: 2*a + 3*b + 2
would be represented as
LinExpr 2 [(a, 2), (b, 3)]
.
LinExpr n [(v, n)] |
data Dependencies v n Source
An opaque datatype containing the dependencies of each variable. A variable who's dependency is just a number is called known. A variables which depends on other variables is called dependend. A variable which is neither known or dependend is called independend. A variable can only depend on other independend variables. It also contains nonlinear equations which it couldn't reduce to a linear equation yet.
InconsistentEq n |
|
RedundantEq |
|
getKnown :: (Eq v, Hashable v) => Dependencies v n -> v -> Either [v] n Source
Return the value of the variable, or a list of variables it depends on. Only linear dependencies are shown.
knownVars :: Dependencies v n -> [(v, n)] Source
Return all known variables.
varDefined :: (Eq v, Hashable v) => Dependencies v n -> v -> Bool Source
Return True if the variable is known or dependend.
nonlinearEqs :: (Ord n, Ord v, Floating n) => Dependencies v n -> [Expr v n] Source
Give all nonlinear equations as an Expr
equal to 0.
dependendVars :: Eq n => Dependencies v n -> [(v, LinExpr v n)] Source
Return all dependend variables with their dependencies.
simpleExpr :: (Num n, Eq n) => Expr v n -> SimpleExpr v n Source
Convert an Expr
to a SimpleExpr
.
emptyDeps :: Dependencies v n Source
An empty set of dependencies.
makeVariable :: Num n => v -> Expr v n Source
Create an expression from a variable
makeConstant :: n -> Expr v n Source
Create an expression from a constant
(===) :: (Hashable n, Hashable v, RealFrac (Phase n), Ord v, Floating n) => Expr v n -> Expr v n -> Dependencies v n -> Either (DepError n) (Dependencies v n) infixr 1 Source
Make the expressions on both sides equal, and add the result to the Set of dependencies.
(=&=) :: (Hashable n, Hashable v, RealFrac (Phase n), Ord v, Floating n) => (Expr v n, Expr v n) -> (Expr v n, Expr v n) -> Dependencies v n -> Either (DepError n) (Dependencies v n) infixr 1 Source
Make the pairs of expressions on both sides equal, and add the result to the Set of dependencies. No error is signaled if the equation for one of the sides is redundant for example in (x, 0) == (y, 0).
solveEqs :: Dependencies v n -> [Dependencies v n -> Either (DepError n) (Dependencies v n)] -> Either (DepError n) (Dependencies v n) Source
Solve a list of equations in order. Returns either a new set of dependencies, or signals an error.