mfsolve-0.3.2.0: Equation solver and calculator à la metafont

Copyright(c) Kristof Bastiaensen 2015
LicenseBSD-3
Maintainerkristof@resonata.be
Stabilityunstable
Portabilityghc
Safe HaskellNone
LanguageHaskell98

Math.MFSolve

Contents

Description

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, since the Show instance for String outputs quotation marks.

let [x, y, t, a] = map (makeVariable . SimpleVar) ["x", "y", "t", "a"]

Solve linear equations:

showVars $ flip execSolver noDeps $ do
  2*x + y === 5
  x - y   === 1
x = 2.0
y = 1.0

Solve for angle (pi/4):

showVars $ flip execSolver noDeps $ sin(t) === 1/sqrt(2)
t = 0.7853981633974484

Solve for angle (pi/3) and amplitude:

showVars $ flip execSolver noDeps $ do
  a*sin(x) === sqrt 3
  a*cos(x) === 1
x = 1.0471975511965979
a = 2.0

Allow nonlinear expression with unknown variables:

showVars $ flip execSolver noDeps $ do
  sin(sqrt(x)) === y
  x === 2
x = 2.0
y = 0.9877659459927355

Find the angle and amplitude when using a rotation matrix:

showVars $ flip execSolver noDeps $ do
  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

Synopsis

Expressions

data SimpleExpr v n Source #

A simplified datatype representing an expression. This can be used to inspect the structure of a Expr, which is hidden.

Constructors

SEBin BinaryOp (SimpleExpr v n) (SimpleExpr v n) 
SEUn UnaryOp (SimpleExpr v n) 
Var v 
Const n 

Instances

(Show v, Ord n, Show n, Num n, Eq n) => Show (SimpleExpr v n) Source # 

Methods

showsPrec :: Int -> SimpleExpr v n -> ShowS #

show :: SimpleExpr v n -> String #

showList :: [SimpleExpr v n] -> ShowS #

data Expr v n Source #

A mathematical expression of several variables. Several Numeric instances (Num, Floating and Fractional) are provided, so doing calculations over Expr is more convenient.

Instances

(Floating n, Ord n, Ord v) => Floating (Expr v n) Source # 

Methods

pi :: Expr v n #

exp :: Expr v n -> Expr v n #

log :: Expr v n -> Expr v n #

sqrt :: Expr v n -> Expr v n #

(**) :: Expr v n -> Expr v n -> Expr v n #

logBase :: Expr v n -> Expr v n -> Expr v n #

sin :: Expr v n -> Expr v n #

cos :: Expr v n -> Expr v n #

tan :: Expr v n -> Expr v n #

asin :: Expr v n -> Expr v n #

acos :: Expr v n -> Expr v n #

atan :: Expr v n -> Expr v n #

sinh :: Expr v n -> Expr v n #

cosh :: Expr v n -> Expr v n #

tanh :: Expr v n -> Expr v n #

asinh :: Expr v n -> Expr v n #

acosh :: Expr v n -> Expr v n #

atanh :: Expr v n -> Expr v n #

log1p :: Expr v n -> Expr v n #

expm1 :: Expr v n -> Expr v n #

log1pexp :: Expr v n -> Expr v n #

log1mexp :: Expr v n -> Expr v n #

(Floating n, Ord n, Ord v) => Fractional (Expr v n) Source # 

Methods

(/) :: Expr v n -> Expr v n -> Expr v n #

recip :: Expr v n -> Expr v n #

fromRational :: Rational -> Expr v n #

(Floating n, Ord n, Ord v) => Num (Expr v n) Source # 

Methods

(+) :: Expr v n -> Expr v n -> Expr v n #

(-) :: Expr v n -> Expr v n -> Expr v n #

(*) :: Expr v n -> Expr v n -> Expr v n #

negate :: Expr v n -> Expr v n #

abs :: Expr v n -> Expr v n #

signum :: Expr v n -> Expr v n #

fromInteger :: Integer -> Expr v n #

(Ord n, Num n, Eq n, Show v, Show n) => Show (Expr v n) Source # 

Methods

showsPrec :: Int -> Expr v n -> ShowS #

show :: Expr v n -> String #

showList :: [Expr v n] -> ShowS #

Generic (Expr v n) Source # 

Associated Types

type Rep (Expr v n) :: * -> * #

Methods

from :: Expr v n -> Rep (Expr v n) x #

to :: Rep (Expr v n) x -> Expr v n #

(Hashable v, Hashable n) => Hashable (Expr v n) Source # 

Methods

hashWithSalt :: Int -> Expr v n -> Int #

hash :: Expr v n -> Int #

type Rep (Expr v n) Source # 
type Rep (Expr v n)

data LinExpr v n Source #

A linear expression of several variables. For example: 2*a + 3*b + 2 would be represented as LinExpr 2 [(a, 2), (b, 3)].

Constructors

LinExpr n [(v, n)] 

Instances

(Eq v, Eq n) => Eq (LinExpr v n) Source # 

Methods

(==) :: LinExpr v n -> LinExpr v n -> Bool #

(/=) :: LinExpr v n -> LinExpr v n -> Bool #

(Show v, Show n) => Show (LinExpr v n) Source # 

Methods

showsPrec :: Int -> LinExpr v n -> ShowS #

show :: LinExpr v n -> String #

showList :: [LinExpr v n] -> ShowS #

Generic (LinExpr v n) Source # 

Associated Types

type Rep (LinExpr v n) :: * -> * #

Methods

from :: LinExpr v n -> Rep (LinExpr v n) x #

to :: Rep (LinExpr v n) x -> LinExpr v n #

(Hashable v, Hashable n) => Hashable (LinExpr v n) Source # 

Methods

hashWithSalt :: Int -> LinExpr v n -> Int #

hash :: LinExpr v n -> Int #

type Rep (LinExpr v n) Source # 
type Rep (LinExpr v n) = D1 (MetaData "LinExpr" "Math.MFSolve" "mfsolve-0.3.2.0-J7SZ9Kp9Pe2IAwq1BbAf3H" False) (C1 (MetaCons "LinExpr" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 n)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(v, n)]))))

data UnaryOp Source #

Constructors

Sin

sine

Cos

cosine

Abs

absolute value

Recip

reciprocal (1/x)

Signum

sign

Exp

natural exponential (e^x)

Log

natural logarithm (log x)

Cosh

hyperbolic cosine

Atanh

inverse hyperbolic tangent

Tan

tangent

Tanh

hyperbolic tangent

Sinh

hyperbolic sine

Asin

inverse sine

Acos

inverse cosine

Asinh

inverse hyperbolic sine

Acosh

inverse hyperbolic cosine

Atan

inverse tangent

Instances

Eq UnaryOp Source # 

Methods

(==) :: UnaryOp -> UnaryOp -> Bool #

(/=) :: UnaryOp -> UnaryOp -> Bool #

Show UnaryOp Source # 
Generic UnaryOp Source # 

Associated Types

type Rep UnaryOp :: * -> * #

Methods

from :: UnaryOp -> Rep UnaryOp x #

to :: Rep UnaryOp x -> UnaryOp #

Hashable UnaryOp Source # 

Methods

hashWithSalt :: Int -> UnaryOp -> Int #

hash :: UnaryOp -> Int #

type Rep UnaryOp Source # 
type Rep UnaryOp = D1 (MetaData "UnaryOp" "Math.MFSolve" "mfsolve-0.3.2.0-J7SZ9Kp9Pe2IAwq1BbAf3H" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Sin" PrefixI False) U1) (C1 (MetaCons "Cos" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Abs" PrefixI False) U1) (C1 (MetaCons "Recip" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Signum" PrefixI False) U1) (C1 (MetaCons "Exp" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Log" PrefixI False) U1) (C1 (MetaCons "Cosh" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Atanh" PrefixI False) U1) (C1 (MetaCons "Tan" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Tanh" PrefixI False) U1) (C1 (MetaCons "Sinh" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Asin" PrefixI False) U1) (C1 (MetaCons "Acos" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Asinh" PrefixI False) U1) ((:+:) (C1 (MetaCons "Acosh" PrefixI False) U1) (C1 (MetaCons "Atan" PrefixI False) U1))))))

data BinaryOp Source #

Constructors

Add

Addition

Mul

Multiplication

newtype SimpleVar Source #

Constructors

SimpleVar String 

Instances

Eq SimpleVar Source # 
Ord SimpleVar Source # 
Show SimpleVar Source #

A simple String wrapper, which will print formulas more cleanly.

Generic SimpleVar Source # 

Associated Types

type Rep SimpleVar :: * -> * #

Hashable SimpleVar Source # 
type Rep SimpleVar Source # 
type Rep SimpleVar = D1 (MetaData "SimpleVar" "Math.MFSolve" "mfsolve-0.3.2.0-J7SZ9Kp9Pe2IAwq1BbAf3H" True) (C1 (MetaCons "SimpleVar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

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

evalExpr :: Floating n => (v -> n) -> SimpleExpr v n -> n Source #

Evaluate the expression given a variable substitution.

fromSimple :: (Floating n, Ord n, Ord v) => SimpleExpr v n -> Expr v n Source #

Make a expression from a simple expression.

toSimple :: (Num n, Eq n) => Expr v n -> SimpleExpr v n Source #

Convert an Expr to a SimpleExpr.

evalSimple :: Floating m => (n -> m) -> (v -> m) -> SimpleExpr v n -> m Source #

evaluate a simple expression using the given substitution.

hasVar :: (Num t, Eq v, Eq t) => v -> Expr v t -> Bool Source #

The expression contains the given variable.

mapSimple :: (Floating m, Floating n) => (n -> m) -> (v -> u) -> SimpleExpr v n -> SimpleExpr u m Source #

map a simple expression using the given substitution.

mapExpr :: (Floating m, Floating n, Ord u, Ord v, Eq n, Ord m) => (n -> m) -> (v -> u) -> Expr v n -> Expr u m Source #

map an expression using the given substitution.

Dependencies

data Dependencies v n Source #

This hidden datatype represents a system of equations. It contains linear dependencies on variables as well as nonlinear equations. The following terminology is used from metafont:

  • known variable: A variable who's dependency is just a number.
  • dependend variable: A variable which depends linearly on other variables.
  • independend variable: any other variable.

A dependend variable can only depend on other independend variables. Nonlinear equations will be simplified by substituting and evaluating known variables, or by reducing some trigonometric equations to linear equations.

Instances

(Show n, Floating n, Ord n, Ord v, Show v) => Show (Dependencies v n) Source # 
Monad m => MonadState (Dependencies v n) (MFSolverT v n m) Source # 

Methods

get :: MFSolverT v n m (Dependencies v n) #

put :: Dependencies v n -> MFSolverT v n m () #

state :: (Dependencies v n -> (a, Dependencies v n)) -> MFSolverT v n m a #

data DepError v n Source #

An error type for ===, =&= and addEquation:

Constructors

UndefinedVar v

The variable is not defined.

UnknownVar v n

The variable is defined but dependend an other variables.

InconsistentEq n (Expr v n)

The equation was reduced to the impossible equation `a == 0` for nonzero a, which means the equation is inconsistent with previous equations.

RedundantEq (Expr v n)

The equation was reduced to the redundant equation `0 == 0`, which means it doesn't add any information.

Instances

(Num n, Ord n, Show n, Show v) => Show (DepError v n) Source # 

Methods

showsPrec :: Int -> DepError v n -> ShowS #

show :: DepError v n -> String #

showList :: [DepError v n] -> ShowS #

(Ord n, Num n, Show v, Show n, Typeable * v, Typeable * n) => Exception (DepError v n) Source # 
Monad m => MonadError (DepError v n) (MFSolverT v n m) Source # 

Methods

throwError :: DepError v n -> MFSolverT v n m a #

catchError :: MFSolverT v n m a -> (DepError v n -> MFSolverT v n m a) -> MFSolverT v n m a #

noDeps :: Dependencies v n Source #

An empty system of equations.

addEquation :: (Hashable n, Hashable v, RealFrac (Phase n), Ord v, Floating n) => Dependencies v n -> Expr v n -> Either (DepError v n) (Dependencies v n) Source #

addEquation d e: Add the equation e = 0 to the system d.

eliminate :: (Hashable n, Show n, Hashable v, RealFrac (Phase n), Ord v, Show v, Floating n) => Dependencies v n -> v -> (Dependencies v n, [Expr v n]) Source #

Eliminate an variable from the equations. Returns the eliminated equations. Before elimination it performs substitution to minimize the number of eliminated equations.

Important: this function is still experimental and mostly untested.

getKnown :: (Eq v, Hashable v) => v -> Dependencies v n -> 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) => v -> Dependencies v n -> 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 #

Return all nonlinear equations e_i, where e_i = 0.

dependendVars :: Eq n => Dependencies v n -> [(v, LinExpr v n)] Source #

Return all dependend variables with their dependencies.

Monadic Interface

(===) :: (MonadState (Dependencies v n) m, MonadError (DepError v n) m, Eq v, Hashable v, Hashable n, RealFrac n, Floating n, Ord v) => Expr v n -> Expr v n -> m () infixr 1 Source #

Make the expressions on both sides equal

(=&=) :: (MonadState (Dependencies v n) m, MonadError (DepError v n) m, Eq v, Hashable v, Hashable n, RealFrac n, Floating n, Ord v) => (Expr v n, Expr v n) -> (Expr v n, Expr v n) -> m () infixr 1 Source #

Make the pairs of expressions on both sides equal. No error is signaled if the equation for one of the sides is Redundant for example in (x, 0) == (y, 0).

dependencies :: MonadState (Dependencies v n) m => m (Dependencies v n) Source #

Get the dependencies from a state monad. Specialized version of get.

getValue :: (MonadState (Dependencies v n) m, MonadError (DepError v n) m, Eq v, Hashable v) => v -> m n Source #

Return the value of the variable or throw an error.

getKnownM :: (MonadState (Dependencies v n) m, Hashable v, Eq v) => v -> m (Either [v] n) Source #

Monadic version of getKnown.

varDefinedM :: (MonadState (Dependencies v n) m, Hashable v, Eq v) => v -> m Bool Source #

Monadic version of varDefined.

eliminateM :: (MonadState (Dependencies v n) m, Hashable n, Hashable v, Show n, Show v, RealFrac n, Ord v, Floating n) => v -> m [Expr v n] Source #

Monadic version of eliminate.

ignore :: MonadError (DepError v n) m => m () -> m () Source #

Succeed even when trowing a RedundantEq error.

MFSolver monad

type MFSolver v n a = MFSolverT v n Identity a Source #

A monad for solving equations. Basicly just a state and exception monad over Dependencies and DepError.

runSolver :: MFSolver v n a -> Dependencies v n -> Either (DepError v n) (a, Dependencies v n) Source #

run the solver.

evalSolver :: MFSolver v n a -> Dependencies v n -> Either (DepError v n) a Source #

Return the result of solving the equations or an error.

execSolver :: MFSolver v n a -> Dependencies v n -> Either (DepError v n) (Dependencies v n) Source #

Run the solver and return the dependencies or an error.

unsafeSolve :: (Typeable n, Typeable v, Show n, Show v, Ord n, Num n) => Dependencies v n -> MFSolver v n a -> a Source #

Return the result of solving the equations, or throw the error as an exception.

showVars :: (Show n, Show v, Ord n, Ord v, Floating n) => Either (DepError v n) (Dependencies v n) -> IO () Source #

Show all variables and equations. Useful in combination with execSolver.

MFSolverT monad transformer

data MFSolverT v n m a Source #

A monad transformer for solving equations. Basicly just a state and exception monad transformer over Dependencies and DepError.

Instances

MonadReader s m => MonadReader s (MFSolverT v n m) Source # 

Methods

ask :: MFSolverT v n m s #

local :: (s -> s) -> MFSolverT v n m a -> MFSolverT v n m a #

reader :: (s -> a) -> MFSolverT v n m a #

MonadWriter s m => MonadWriter s (MFSolverT v n m) Source # 

Methods

writer :: (a, s) -> MFSolverT v n m a #

tell :: s -> MFSolverT v n m () #

listen :: MFSolverT v n m a -> MFSolverT v n m (a, s) #

pass :: MFSolverT v n m (a, s -> s) -> MFSolverT v n m a #

MonadTrans (MFSolverT v n) Source # 

Methods

lift :: Monad m => m a -> MFSolverT v n m a #

Monad m => MonadError (DepError v n) (MFSolverT v n m) Source # 

Methods

throwError :: DepError v n -> MFSolverT v n m a #

catchError :: MFSolverT v n m a -> (DepError v n -> MFSolverT v n m a) -> MFSolverT v n m a #

Monad m => MonadState (Dependencies v n) (MFSolverT v n m) Source # 

Methods

get :: MFSolverT v n m (Dependencies v n) #

put :: Dependencies v n -> MFSolverT v n m () #

state :: (Dependencies v n -> (a, Dependencies v n)) -> MFSolverT v n m a #

Monad m => Monad (MFSolverT v n m) Source # 

Methods

(>>=) :: MFSolverT v n m a -> (a -> MFSolverT v n m b) -> MFSolverT v n m b #

(>>) :: MFSolverT v n m a -> MFSolverT v n m b -> MFSolverT v n m b #

return :: a -> MFSolverT v n m a #

fail :: String -> MFSolverT v n m a #

Functor m => Functor (MFSolverT v n m) Source # 

Methods

fmap :: (a -> b) -> MFSolverT v n m a -> MFSolverT v n m b #

(<$) :: a -> MFSolverT v n m b -> MFSolverT v n m a #

Monad m => Applicative (MFSolverT v n m) Source # 

Methods

pure :: a -> MFSolverT v n m a #

(<*>) :: MFSolverT v n m (a -> b) -> MFSolverT v n m a -> MFSolverT v n m b #

(*>) :: MFSolverT v n m a -> MFSolverT v n m b -> MFSolverT v n m b #

(<*) :: MFSolverT v n m a -> MFSolverT v n m b -> MFSolverT v n m a #

MonadIO m => MonadIO (MFSolverT v n m) Source # 

Methods

liftIO :: IO a -> MFSolverT v n m a #

MonadCont m => MonadCont (MFSolverT v n m) Source # 

Methods

callCC :: ((a -> MFSolverT v n m b) -> MFSolverT v n m a) -> MFSolverT v n m a #

runSolverT :: MFSolverT v n m a -> Dependencies v n -> m (Either (DepError v n) (a, Dependencies v n)) Source #

evalSolverT :: Functor f => MFSolverT v n f b -> Dependencies v n -> f (Either (DepError v n) b) Source #

Return the result of solving the equations or an error. Monadic version.

execSolverT :: Functor m => MFSolverT v n m a -> Dependencies v n -> m (Either (DepError v n) (Dependencies v n)) Source #

Run the solver and return the dependencies or an error. Monadic version.

unsafeSolveT :: (Num n, Ord n, Show n, Show v, Typeable n, Typeable v, Monad m) => Dependencies v n -> MFSolverT v n m a -> m a Source #

Return the result of solving the equations, or throw the error as an exception. Monadic version.