Safe Haskell | Safe |
---|---|
Language | Haskell98 |
This module provides a symbolic representation of real number expressions, as well as a type class of things that can be converted to arbitrary precision real numbers.
- data SymReal
- = Const Integer
- | Decimal Rational String
- | Plus SymReal SymReal
- | Minus SymReal SymReal
- | Times SymReal SymReal
- | Div SymReal SymReal
- | Negate SymReal
- | Abs SymReal
- | Signum SymReal
- | Recip SymReal
- | Pi
- | Euler
- | Exp SymReal
- | Sqrt SymReal
- | Log SymReal
- | Power SymReal SymReal
- | Sin SymReal
- | Tan SymReal
- | Cos SymReal
- | ASin SymReal
- | ATan SymReal
- | ACos SymReal
- | Sinh SymReal
- | Tanh SymReal
- | Cosh SymReal
- | ASinh SymReal
- | ATanh SymReal
- | ACosh SymReal
- | ArcTan2 SymReal SymReal
- class ToReal a where
- dynamic_fixedprec :: forall a r. ToReal r => Integer -> (forall e. Precision e => FixedPrec e -> a) -> r -> a
- dynamic_fixedprec2 :: forall a r s. (ToReal r, ToReal s) => Integer -> (forall e. Precision e => FixedPrec e -> FixedPrec e -> a) -> r -> s -> a
- integer :: ReadP SymReal
- float :: ReadP SymReal
- const_pi :: ReadP SymReal
- const_e :: ReadP SymReal
- negative :: ReadP (SymReal -> SymReal)
- positive :: ReadP (SymReal -> SymReal)
- plus_term :: ReadP (SymReal -> SymReal)
- minus_term :: ReadP (SymReal -> SymReal)
- times_term :: ReadP (SymReal -> SymReal)
- div_term :: ReadP (SymReal -> SymReal)
- power_term :: ReadP (SymReal -> SymReal)
- unary_fun :: ReadP SymReal
- unary_op :: ReadP (SymReal -> SymReal)
- binary_fun :: ReadP SymReal
- binary_op :: ReadP (SymReal -> SymReal -> SymReal)
- exp6 :: ReadP SymReal
- exp7 :: ReadP SymReal
- exp8 :: ReadP SymReal
- exp10 :: ReadP SymReal
- parenthesized :: ReadP SymReal
- expression :: ReadP SymReal
- parse_SymReal :: String -> Maybe SymReal
Symbolic real number expressions
A type to represent symbolic expressions for real numbers.
Caution: equality ==
at this type denotes symbolic equality of
expressions, not equality of the defined real numbers.
Const Integer | An integer constant. |
Decimal Rational String | A decimal constant. This has a rational value and a string representation. |
Plus SymReal SymReal | x |
Minus SymReal SymReal | x |
Times SymReal SymReal | x |
Div SymReal SymReal | x |
Negate SymReal | −x. |
Abs SymReal | |x|. |
Signum SymReal | signum(x). |
Recip SymReal | 1/x. |
Pi | π. |
Euler | e. |
Exp SymReal | ex. |
Sqrt SymReal | |*+~.|==x. |
Log SymReal | log x. |
Power SymReal SymReal | xy. |
Sin SymReal | sin x. |
Tan SymReal | cos x. |
Cos SymReal | cos x. |
ASin SymReal | asin x. |
ATan SymReal | atan x. |
ACos SymReal | acos x. |
Sinh SymReal | sinh x. |
Tanh SymReal | tanh x. |
Cosh SymReal | cosh x. |
ASinh SymReal | asinh x. |
ATanh SymReal | atanh x. |
ACosh SymReal | acosh x. |
ArcTan2 SymReal SymReal | arctan2 x y. |
Conversion to real number types
A type class for things that can be converted to a real number at arbitrary precision.
Dynamic conversion to FixedPrec
dynamic_fixedprec :: forall a r. ToReal r => Integer -> (forall e. Precision e => FixedPrec e -> a) -> r -> a Source #
It would be useful to have a function for converting a symbolic real number to a fixed-precision real number with a chosen precision, such that the precision e depends on a parameter d:
to_fixedprec :: (ToReal r) => Integer -> r -> FixedPrec e to_fixedprec d x = ...
However, since e is a type, d is a term, and Haskell is not dependently typed, this cannot be done directly.
The function dynamic_fixedprec
is the closest thing we have to a
workaround. The call dynamic_fixedprec
d f x calls
f(x'), where x' is the value x converted to d digits of
precision. In other words, we have
dynamic_fixedprec d f x = f (to_fixedprec d x),
with the restriction that the precision e cannot occur freely in the result type of f.
dynamic_fixedprec2 :: forall a r s. (ToReal r, ToReal s) => Integer -> (forall e. Precision e => FixedPrec e -> FixedPrec e -> a) -> r -> s -> a Source #
Like dynamic_fixedprec
, but take two real number arguments. In
terms of the fictitious function to_fixedprec
, we have:
dynamic_fixedprec2 d f x y = f (to_fixedprec d x) (to_fixedprec d y).
A parser for real number expressions
Grammar specification
Each function in this section corresponds to a production rule
for a context-free grammar. The type of each function is ReadP
a, where a is the type of the semantic value produced by the
grammar for that expression.
The parser uses simple precedences.
- Unary "+" and "−" have precedence 6.
- Binary "+" and "−" have precedence 6 and are left associative.
- Binary "*" and "/" have precedence 7 and are left associative.
- Binary "**" and "^" have precedence 8 and are right associative.
- All unary operators other than "+" and "−" have precedence 10.
We use exp6 to denote an expression whose top-level operator has precedence 6 or higher, exp7 to denote an expression whose top-level operator has precedence 7 or higher, and so on.
We also allow whitespace between lexicographic entities. For simplicity, whitespace is not shown in the production rules, although it appears in the code.
float :: ReadP SymReal Source #
float ::= digit* "." digit*.
There must be at least one digit, either before or after the decimal point.
binary_fun :: ReadP SymReal Source #
binary_fun ::= binary_op exp10 exp10.
exp6 :: ReadP SymReal Source #
exp6 ::= (negative | positive)? exp7 ( plus_term | minus_term )*.
An expression whose top-level operator has precedence 6 or above. The operators of precedence 6 are "+" and "−".
exp7 :: ReadP SymReal Source #
exp7 ::= exp8 ( times_term | div_term )*.
An expression whose top-level operator has precedence 7 or above. The operators of precedence 6 are "*" and "/".
exp8 :: ReadP SymReal Source #
exp8 ::= ( power_term )* exp10
An expression whose top-level operator has precedence 8 or above. The operators of precedence 6 are "**" and "^".
exp10 :: ReadP SymReal Source #
exp10 ::= parenthesized | const_pi | const_e | integer | float | unary_fun | binary_fun.
An expression whose top-level operator has precedence 10 or above. Such expressions are constants, applications of unary operators (except unary "−" and "+"), and parenthesized expressions.
parenthesized :: ReadP SymReal Source #
parenthesized ::= "(" exp6 ")".
expression :: ReadP SymReal Source #
expression ::= exp6 end-of-line.
This is a top-level expression.