module Quantum.Synthesis.SymReal where
import Quantum.Synthesis.ArcTan2
import Control.Monad
import Data.Char (isDigit)
import Data.Number.FixedPrec
import Text.ParserCombinators.ReadP
import Data.Ratio
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
deriving (Eq)
instance Show SymReal where
showsPrec d (Const x) = showsPrec d x
showsPrec d (Decimal x s) = showString s
showsPrec d (Plus x y) = showParen (d > 6) $ showsPrec 6 x . showString "+" . showsPrec 6 y
showsPrec d (Minus x y) = showParen (d > 6) $ showsPrec 6 x . showString "-" . showsPrec 7 y
showsPrec d (Times x y) = showParen (d > 7) $ showsPrec 7 x . showString "*" . showsPrec 7 y
showsPrec d (Div x y) = showParen (d > 7) $ showsPrec 7 x . showString "/" . showsPrec 8 y
showsPrec d (Power x y) = showParen (d > 8) $ showsPrec 9 x . showString "**" . showsPrec 9 y
showsPrec d (Negate x) = showParen (d > 5) $ showString "-" . showsPrec 7 x
showsPrec d (Abs x) = showParen (d > 10) $ showString "abs " . showsPrec 11 x
showsPrec d (Signum x) = showParen (d > 10) $ showString "signum " . showsPrec 11 x
showsPrec d (Recip x) = showParen (d > 7) $ showString "1/" . showsPrec 8 x
showsPrec d Pi = showString "pi"
showsPrec d Euler = showString "e"
showsPrec d (Exp x) = showParen (d > 10) $ showString "exp " . showsPrec 11 x
showsPrec d (Sqrt x) = showParen (d > 10) $ showString "sqrt " . showsPrec 11 x
showsPrec d (Log x) = showParen (d > 10) $ showString "log " . showsPrec 11 x
showsPrec d (Sin x) = showParen (d > 10) $ showString "sin " . showsPrec 11 x
showsPrec d (Tan x) = showParen (d > 10) $ showString "tan " . showsPrec 11 x
showsPrec d (Cos x) = showParen (d > 10) $ showString "cos " . showsPrec 11 x
showsPrec d (ASin x) = showParen (d > 10) $ showString "asin " . showsPrec 11 x
showsPrec d (ATan x) = showParen (d > 10) $ showString "atan " . showsPrec 11 x
showsPrec d (ACos x) = showParen (d > 10) $ showString "acos " . showsPrec 11 x
showsPrec d (Sinh x) = showParen (d > 10) $ showString "sinh " . showsPrec 11 x
showsPrec d (Tanh x) = showParen (d > 10) $ showString "tanh " . showsPrec 11 x
showsPrec d (Cosh x) = showParen (d > 10) $ showString "cosh " . showsPrec 11 x
showsPrec d (ASinh x) = showParen (d > 10) $ showString "asinh " . showsPrec 11 x
showsPrec d (ATanh x) = showParen (d > 10) $ showString "atanh " . showsPrec 11 x
showsPrec d (ACosh x) = showParen (d > 10) $ showString "acosh " . showsPrec 11 x
showsPrec d (ArcTan2 y x) = showParen (d > 10) $ showString "arctan2 " . showsPrec 11 y . showString " " . showsPrec 11 x
instance Num SymReal where
(+) = Plus
(*) = Times
() = Minus
negate = Negate
abs = Abs
signum = Signum
fromInteger = Const
instance Fractional SymReal where
(/) = Div
recip = Recip
fromRational x = Const (numerator x) `Div` Const (denominator x)
instance Floating SymReal where
pi = Pi
exp = Exp
sqrt = Sqrt
log = Log
(**) = Power
logBase x y = log y / log x
sin = Sin
tan = Tan
cos = Cos
asin = ASin
atan = ATan
acos = ACos
sinh = Sinh
tanh = Tanh
cosh = Cosh
asinh = ASinh
atanh = ATanh
acosh = ACosh
instance ArcTan2 SymReal where
arctan2 y x = ArcTan2 y x
class ToReal a where
to_real :: (Floating r, ArcTan2 r) => a -> r
instance ToReal SymReal where
to_real (Const x) = fromInteger x
to_real (Decimal x s) = fromRational x
to_real (Plus x y) = to_real x + to_real y
to_real (Minus x y) = to_real x to_real y
to_real (Times x y) = to_real x * to_real y
to_real (Negate x) = (to_real x)
to_real (Abs x) = abs (to_real x)
to_real (Signum x) = signum (to_real x)
to_real (Div x y) = to_real x / to_real y
to_real (Recip x) = recip (to_real x)
to_real Pi = pi
to_real Euler = exp 1
to_real (Exp x) = exp (to_real x)
to_real (Sqrt x) = sqrt (to_real x)
to_real (Log x) = log (to_real x)
to_real (Power x y) = to_real x ** to_real y
to_real (Sin x) = sin (to_real x)
to_real (Tan x) = tan (to_real x)
to_real (Cos x) = cos (to_real x)
to_real (ASin x) = asin (to_real x)
to_real (ATan x) = atan (to_real x)
to_real (ACos x) = acos (to_real x)
to_real (Sinh x) = sinh (to_real x)
to_real (Tanh x) = tanh (to_real x)
to_real (Cosh x) = cosh (to_real x)
to_real (ASinh x) = asinh (to_real x)
to_real (ATanh x) = atanh (to_real x)
to_real (ACosh x) = acosh (to_real x)
to_real (ArcTan2 y x) = arctan2 (to_real y) (to_real x)
instance ToReal Rational where
to_real = fromRational
instance ToReal Integer where
to_real = fromInteger
instance ToReal Int where
to_real = fromIntegral
instance ToReal Double where
to_real = fromRational . toRational
instance ToReal Float where
to_real = fromRational . toRational
instance (Precision e) => ToReal (FixedPrec e) where
to_real = fromRational . toRational
instance ToReal String where
to_real x = case parse_SymReal x of
Just n -> to_real n
Nothing -> error "ToReal String: string does not parse"
dynamic_fixedprec :: forall a r.(ToReal r) => Integer -> (forall e.(Precision e) => FixedPrec e -> a) -> r -> a
dynamic_fixedprec d f x = loop d (undefined :: P0)
where
loop :: forall e.(Precision e) => Integer -> e -> a
loop d e
| d >= 1000 = loop (d1000) (undefined :: PPlus1000 e)
| d >= 100 = loop (d100) (undefined :: PPlus100 e)
| d >= 10 = loop (d10) (undefined :: PPlus10 e)
| d > 0 = loop (d1) (undefined :: PPlus1 e)
| otherwise = f (to_real x :: FixedPrec e)
dynamic_fixedprec2 :: forall a r s.(ToReal r, ToReal s) => Integer -> (forall e.(Precision e) => FixedPrec e -> FixedPrec e -> a) -> r -> s -> a
dynamic_fixedprec2 d f x y = loop d (undefined :: P0)
where
loop :: forall e.(Precision e) => Integer -> e -> a
loop d e
| d >= 1000 = loop (d1000) (undefined :: PPlus1000 e)
| d >= 100 = loop (d100) (undefined :: PPlus100 e)
| d >= 10 = loop (d10) (undefined :: PPlus10 e)
| d > 0 = loop (d1) (undefined :: PPlus1 e)
| otherwise = f (to_real x :: FixedPrec e) (to_real y :: FixedPrec e)
integer :: ReadP SymReal
integer = do
s <- munch1 isDigit
let n = read s
return (Const (fromInteger n))
float :: ReadP SymReal
float = do
(s1, _) <- gather $ do
munch isDigit
char '.'
(s2, _) <- gather $ do
munch isDigit
when (length s1 == 0 && length s2 == 0) $ do
pfail
let num = read (s1++s2) :: Integer
let denom = 10^(length s2)
let s1' = if s1 == [] then "0" else s1
let s2' = if s2 == [] then "0" else s2
return (Decimal (num % denom) (s1' ++ "." ++ s2'))
const_pi :: ReadP SymReal
const_pi = do
string "pi"
return Pi
const_e :: ReadP SymReal
const_e = do
string "e"
return Euler
negative :: ReadP (SymReal -> SymReal)
negative = do
string "-"
skipSpaces
return Negate
positive :: ReadP (SymReal -> SymReal)
positive = do
string "+"
skipSpaces
return id
plus_term :: ReadP (SymReal -> SymReal)
plus_term = do
skipSpaces
string "+"
skipSpaces
n2 <- exp7
return (\n1 -> Plus n1 n2)
minus_term :: ReadP (SymReal -> SymReal)
minus_term = do
skipSpaces
string "-"
skipSpaces
n2 <- exp7
return (\n1 -> Minus n1 n2)
times_term :: ReadP (SymReal -> SymReal)
times_term = do
skipSpaces
string "*"
skipSpaces
n2 <- exp8
return (\n1 -> Times n1 n2)
div_term :: ReadP (SymReal -> SymReal)
div_term = do
skipSpaces
string "/"
skipSpaces
n2 <- exp8
return (\n1 -> Div n1 n2)
power_term :: ReadP (SymReal -> SymReal)
power_term = do
n1 <- exp10
skipSpaces
string "**" +++ string "^"
skipSpaces
return (\n2 -> Power n1 n2)
unary_fun :: ReadP SymReal
unary_fun = do
skipSpaces
op <- unary_op
skipSpaces
n <- exp10
return (op n)
unary_op :: ReadP (SymReal -> SymReal)
unary_op =
choice [ do { string s; return op } | (s, op) <- ops ]
where
ops = [ ("abs", Abs),
("signum", Signum),
("recip", Recip),
("exp", Exp),
("sqrt", Sqrt),
("log", Log),
("sin", Sin),
("tan", Tan),
("cos", Cos),
("asin", ASin),
("atan", ATan),
("acos", ACos),
("sinh", Sinh),
("tanh", Tanh),
("cosh", Cosh),
("asinh", ASinh),
("atanh", ATanh),
("acosh", ACosh) ]
binary_fun :: ReadP SymReal
binary_fun = do
skipSpaces
op <- binary_op
skipSpaces
n <- exp10
skipSpaces
m <- exp10
return (op n m)
binary_op :: ReadP (SymReal -> SymReal -> SymReal)
binary_op =
choice [ do { string s; return op } | (s, op) <- ops ]
where
ops = [ ("arctan2", ArcTan2) ]
exp6 :: ReadP SymReal
exp6 = do
sign <- option id (negative +++ positive)
n1 <- exp7
ops <- many $ do
plus_term +++ minus_term
return (foldl (\x f -> f x) (sign n1) ops)
exp7 :: ReadP SymReal
exp7 = do
n1 <- exp8
ops <- many $ do
times_term +++ div_term
return (foldl (\x f -> f x) n1 ops)
exp8 :: ReadP SymReal
exp8 = do
ops <- many $ do
power_term
n2 <- exp10
return (foldr (\f x -> f x) n2 ops)
exp10 :: ReadP SymReal
exp10 = parenthesized +++ const_pi +++ const_e +++ integer +++ float +++ unary_fun +++ binary_fun
parenthesized :: ReadP SymReal
parenthesized = do
string "("
skipSpaces
n <- exp6
skipSpaces
string ")"
return n
expression :: ReadP SymReal
expression = do
skipSpaces
s <- exp6
skipSpaces
eof
return s
parse_SymReal :: String -> Maybe SymReal
parse_SymReal s =
case readP_to_S expression s of
(h, ""):_ -> Just h
_ -> Nothing