Copyright | Copyright 2024 Yoo Chung |
---|---|
License | Apache-2.0 |
Maintainer | dev@chungyc.org |
Safe Haskell | None |
Language | GHC2021 |
Synopsis
- data Expression
- data UnaryFunction
- data BinaryFunction
- substitute :: Expression -> (Text -> Maybe Expression) -> Expression
- evaluate :: Floating a => Expression -> (Text -> Maybe a) -> Maybe a
- fractionalEvaluate :: (Eq a, Fractional a) => Expression -> (Text -> Maybe a) -> Maybe a
- toFunction :: Floating b => Expression -> (Text -> a -> b) -> a -> b
- getUnaryFunction :: Floating a => UnaryFunction -> a -> a
- getBinaryFunction :: Floating a => BinaryFunction -> a -> a -> a
- pattern Pi' :: Expression
- pattern Negate' :: Expression -> Expression
- pattern Abs' :: Expression -> Expression
- pattern Signum' :: Expression -> Expression
- pattern Exp' :: Expression -> Expression
- pattern Log' :: Expression -> Expression
- pattern Sqrt' :: Expression -> Expression
- pattern Sin' :: Expression -> Expression
- pattern Cos' :: Expression -> Expression
- pattern Tan' :: Expression -> Expression
- pattern Asin' :: Expression -> Expression
- pattern Acos' :: Expression -> Expression
- pattern Atan' :: Expression -> Expression
- pattern Sinh' :: Expression -> Expression
- pattern Cosh' :: Expression -> Expression
- pattern Tanh' :: Expression -> Expression
- pattern Asinh' :: Expression -> Expression
- pattern Acosh' :: Expression -> Expression
- pattern Atanh' :: Expression -> Expression
- pattern (:+:) :: Expression -> Expression -> Expression
- pattern (:*:) :: Expression -> Expression -> Expression
- pattern (:-:) :: Expression -> Expression -> Expression
- pattern (:/:) :: Expression -> Expression -> Expression
- pattern (:**:) :: Expression -> Expression -> Expression
- pattern LogBase' :: Expression -> Expression -> Expression
Representation
data Expression Source #
Symbolic representation of a mathematical expression.
It is an instance of the Num
, Fractional
, and Floating
type classes,
so normal Haskell expressions can be used, although the expressions
are limited to using the functions defined by these type classses.
The type is also an instance of the IsString
type class,
so symbols can be expressed as Haskell string with the OverloadedStrings
extension.
The structure of these values is intended to be visible.
>>>
2 :: Expression
Number 2>>>
"x" :: Expression
Symbol "x">>>
2 + sin "x" :: Expression
BinaryApply Add (Number 2) (UnaryApply Sin (Symbol "x"))
A somewhat more concise representation can be obtained using toHaskell
:
>>>
toHaskell $ 2 * "y" + sin "x"
"2 * y + sin x"
Number Integer | Represents a concrete number. |
Symbol Text | Represents a symbol, which could either be a variable or a constant. |
UnaryApply UnaryFunction Expression | Represents the application of an unary function. |
BinaryApply BinaryFunction Expression Expression | Represents the application of a binary function. |
Instances
data UnaryFunction Source #
Symbolic representation for unary functions.
Instances
Bounded UnaryFunction Source # | |||||
Defined in Symtegration.Symbolic | |||||
Enum UnaryFunction Source # | |||||
Defined in Symtegration.Symbolic succ :: UnaryFunction -> UnaryFunction # pred :: UnaryFunction -> UnaryFunction # toEnum :: Int -> UnaryFunction # fromEnum :: UnaryFunction -> Int # enumFrom :: UnaryFunction -> [UnaryFunction] # enumFromThen :: UnaryFunction -> UnaryFunction -> [UnaryFunction] # enumFromTo :: UnaryFunction -> UnaryFunction -> [UnaryFunction] # enumFromThenTo :: UnaryFunction -> UnaryFunction -> UnaryFunction -> [UnaryFunction] # | |||||
Generic UnaryFunction Source # | |||||
Defined in Symtegration.Symbolic
from :: UnaryFunction -> Rep UnaryFunction x # to :: Rep UnaryFunction x -> UnaryFunction # | |||||
Read UnaryFunction Source # | |||||
Defined in Symtegration.Symbolic readsPrec :: Int -> ReadS UnaryFunction # readList :: ReadS [UnaryFunction] # | |||||
Show UnaryFunction Source # | |||||
Defined in Symtegration.Symbolic showsPrec :: Int -> UnaryFunction -> ShowS # show :: UnaryFunction -> String # showList :: [UnaryFunction] -> ShowS # | |||||
Eq UnaryFunction Source # | |||||
Defined in Symtegration.Symbolic (==) :: UnaryFunction -> UnaryFunction -> Bool # (/=) :: UnaryFunction -> UnaryFunction -> Bool # | |||||
TextShow UnaryFunction Source # | |||||
Defined in Symtegration.Symbolic showbPrec :: Int -> UnaryFunction -> Builder showb :: UnaryFunction -> Builder showbList :: [UnaryFunction] -> Builder showtPrec :: Int -> UnaryFunction -> Text showt :: UnaryFunction -> Text showtList :: [UnaryFunction] -> Text showtlPrec :: Int -> UnaryFunction -> Text showtl :: UnaryFunction -> Text showtlList :: [UnaryFunction] -> Text | |||||
type Rep UnaryFunction Source # | |||||
Defined in Symtegration.Symbolic type Rep UnaryFunction = D1 ('MetaData "UnaryFunction" "Symtegration.Symbolic" "symtegration-0.4.0-731kqytrP2e45Ltbn6eY7b" 'False) ((((C1 ('MetaCons "Negate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Abs" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Signum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Log" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sqrt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Sin" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Cos" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tan" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Asin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Acos" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Atan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sinh" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Cosh" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tanh" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Asinh" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Acosh" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atanh" 'PrefixI 'False) (U1 :: Type -> Type)))))) |
data BinaryFunction Source #
Symbolic representation for binary functions.
Instances
Bounded BinaryFunction Source # | |||||
Defined in Symtegration.Symbolic | |||||
Enum BinaryFunction Source # | |||||
Defined in Symtegration.Symbolic succ :: BinaryFunction -> BinaryFunction # pred :: BinaryFunction -> BinaryFunction # toEnum :: Int -> BinaryFunction # fromEnum :: BinaryFunction -> Int # enumFrom :: BinaryFunction -> [BinaryFunction] # enumFromThen :: BinaryFunction -> BinaryFunction -> [BinaryFunction] # enumFromTo :: BinaryFunction -> BinaryFunction -> [BinaryFunction] # enumFromThenTo :: BinaryFunction -> BinaryFunction -> BinaryFunction -> [BinaryFunction] # | |||||
Generic BinaryFunction Source # | |||||
Defined in Symtegration.Symbolic
from :: BinaryFunction -> Rep BinaryFunction x # to :: Rep BinaryFunction x -> BinaryFunction # | |||||
Read BinaryFunction Source # | |||||
Defined in Symtegration.Symbolic readsPrec :: Int -> ReadS BinaryFunction # readList :: ReadS [BinaryFunction] # | |||||
Show BinaryFunction Source # | |||||
Defined in Symtegration.Symbolic showsPrec :: Int -> BinaryFunction -> ShowS # show :: BinaryFunction -> String # showList :: [BinaryFunction] -> ShowS # | |||||
Eq BinaryFunction Source # | |||||
Defined in Symtegration.Symbolic (==) :: BinaryFunction -> BinaryFunction -> Bool # (/=) :: BinaryFunction -> BinaryFunction -> Bool # | |||||
TextShow BinaryFunction Source # | |||||
Defined in Symtegration.Symbolic showbPrec :: Int -> BinaryFunction -> Builder showb :: BinaryFunction -> Builder showbList :: [BinaryFunction] -> Builder showtPrec :: Int -> BinaryFunction -> Text showt :: BinaryFunction -> Text showtList :: [BinaryFunction] -> Text showtlPrec :: Int -> BinaryFunction -> Text showtl :: BinaryFunction -> Text showtlList :: [BinaryFunction] -> Text | |||||
type Rep BinaryFunction Source # | |||||
Defined in Symtegration.Symbolic type Rep BinaryFunction = D1 ('MetaData "BinaryFunction" "Symtegration.Symbolic" "symtegration-0.4.0-731kqytrP2e45Ltbn6eY7b" 'False) ((C1 ('MetaCons "Add" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Multiply" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Subtract" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Divide" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Power" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LogBase" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Manipulation
:: Expression | Expression to apply substitution. |
-> (Text -> Maybe Expression) | Maps symbols to expressions they are to be substituted with. |
-> Expression | Expression with substitution applied. |
Substitute the symbols with the corresponding expressions they are mapped to. The symbols will be replaced as is; there is no special treatment if the expression they are replaced by also contains the same symbol.
>>>
toHaskell $ substitute ("x" + "y") (\case "x" -> Just ("a" * "b"); "y" -> Just 4)
"a * b + 4"
Computation
:: Floating a | |
=> Expression | Mathematical expression to evaluate. |
-> (Text -> Maybe a) | Maps symbols to concrete values. |
-> Maybe a | Evaluation result. |
Calculates the value for a mathematical expression for a given assignment of values to symbols.
For example, when \(x=5\), then \(2x+1=11\).
>>>
evaluate (2 * "x" + 1) (\case "x" -> Just 5)
Just 11.0
All symbols except for "pi"
in a mathematical expression must be assigned a value.
Otherwise, a value cannot be computed.
>>>
evaluate (2 * "x" + 1) (const Nothing)
Nothing
The symbol "pi"
is always used to represent \(\pi\),
and any assignment to "pi"
will be ignored.
For example, the following is \(\pi - \pi\), not \(100 - \pi\).
>>>
evaluate ("pi" - pi) (\case "x" -> Just 100)
Just 0.0
:: (Eq a, Fractional a) | |
=> Expression | Mathematical expression to evaluate. |
-> (Text -> Maybe a) | Maps symbols to concrete values. |
-> Maybe a | Evaluation result. |
Evaluates a mathematical expression with only operations available to Fractional
values.
In particular, this allows exact evaluations with Rational
values.
Nothing
will be returned if a function not supported by all Fractional
values
is used by the mathematical expression.
As an exception, the (**)
operator is allowed with constant integer exponents,
even though (**)
is not a function applicable to all Fractional
types.
For example,
>>>
let p = 1 / (3 * "x"**5 - 2 * "x" + 1) :: Expression
>>>
fractionalEvaluate p (\case "x" -> Just (2 / 7 :: Rational))
Just (16807 % 7299)
Compare against evaluate
, which cannot even use Rational
computations
because Rational
is not an instance of the Floating
type class:
>>>
evaluate p (\case "x" -> Just (2 / 7 :: Double))
Just 2.3026441978353196
:: Floating b | |
=> Expression | The expression to be converted into a function. |
-> (Text -> a -> b) | Maps how the argument to the function should be mapped to a value for a symbol. E.g., "x" could map the first element in a tuple as the value to use in its place. |
-> a | The function generated from the expression. |
-> b |
Returns a function based on a given expression. This requires a specification of how a symbol maps the argument to a value to be used in its place.
For example, the symbol "x" could use the argument as is as its value. I.e., "x" can be mapped to a function which maps the argument to itself.
>>>
let f = toFunction ("x" ** 2 + 1) (\case "x" -> id) :: Double -> Double
>>>
f 3 -- 3 ** 2 + 1
10.0>>>
f 10 -- 10 ** 2 + 1
101.0
For another example, "x" could map the first element from a tuple argument, and "y" could map the second element from the tuple argument. I.e., for a tuple argument to the function, the first element will be used as "x" and the second element will be used as "y".
>>>
let m = \case "x" -> (\(x,_) -> x); "y" -> (\(_,y) -> y)
>>>
let g = toFunction ("x" + 2 * "y") m :: (Double, Double) -> Double
>>>
g (3,4) -- 3 + 2 * 4
11.0>>>
g (7,1) -- 7 + 2 * 1
9.0
getUnaryFunction :: Floating a => UnaryFunction -> a -> a Source #
Returns a function corresponding to the symbolic representation of an unary function.
>>>
(getUnaryFunction Cos) pi == (cos pi :: Double)
True
getBinaryFunction :: Floating a => BinaryFunction -> a -> a -> a Source #
Returns a function corresponding to the symbolic representation of a binary function.
>>>
(getBinaryFunction Add) 2 5 == (2 + 5 :: Double)
True
Pattern synonyms
Pattern synonyms are defined to make it more convenient to pattern match on Expression
.
Constants
pattern Pi' :: Expression Source #
Unary functions
pattern Negate' :: Expression -> Expression Source #
pattern Abs' :: Expression -> Expression Source #
pattern Signum' :: Expression -> Expression Source #
pattern Exp' :: Expression -> Expression Source #
pattern Log' :: Expression -> Expression Source #
pattern Sqrt' :: Expression -> Expression Source #
pattern Sin' :: Expression -> Expression Source #
pattern Cos' :: Expression -> Expression Source #
pattern Tan' :: Expression -> Expression Source #
pattern Asin' :: Expression -> Expression Source #
pattern Acos' :: Expression -> Expression Source #
pattern Atan' :: Expression -> Expression Source #
pattern Sinh' :: Expression -> Expression Source #
pattern Cosh' :: Expression -> Expression Source #
pattern Tanh' :: Expression -> Expression Source #
pattern Asinh' :: Expression -> Expression Source #
pattern Acosh' :: Expression -> Expression Source #
pattern Atanh' :: Expression -> Expression Source #
Binary functions
pattern (:+:) :: Expression -> Expression -> Expression Source #
pattern (:*:) :: Expression -> Expression -> Expression Source #
pattern (:-:) :: Expression -> Expression -> Expression Source #
pattern (:/:) :: Expression -> Expression -> Expression Source #
pattern (:**:) :: Expression -> Expression -> Expression Source #
pattern LogBase' :: Expression -> Expression -> Expression Source #