module Data.SRTree.Print
( showExpr
, printExpr
, showTikz
, printTikz
, showPython
, printPython
, showLatex
, printLatex
)
where
import Control.Monad.Reader ( asks, runReader, Reader )
import Data.Char ( toLower )
import Data.SRTree.Internal
import Data.SRTree.Recursion
showExpr :: Fix SRTree -> String
showExpr :: Fix SRTree -> String
showExpr = forall (f :: * -> *) a. Functor f => (f a -> a) -> Fix f -> a
cata SRTree String -> String
alg
where
alg :: SRTree String -> String
alg (Var Int
ix) = Char
'x' forall a. a -> [a] -> [a]
: forall a. Show a => a -> String
show Int
ix
alg (Param Int
ix) = Char
't' forall a. a -> [a] -> [a]
: forall a. Show a => a -> String
show Int
ix
alg (Const Double
c) = forall a. Show a => a -> String
show Double
c
alg (Bin Op
op String
l String
r) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"(", String
l, String
" ", Op -> String
showOp Op
op, String
" ", String
r, String
")"]
alg (Uni Function
f String
t) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [forall a. Show a => a -> String
show Function
f, String
"(", String
t, String
")"]
printExpr :: Fix SRTree -> IO ()
printExpr :: Fix SRTree -> IO ()
printExpr = String -> IO ()
putStrLn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fix SRTree -> String
showExpr
showOp :: Op -> String
showOp Op
Add = String
"+"
showOp Op
Sub = String
"-"
showOp Op
Mul = String
"*"
showOp Op
Div = String
"/"
showOp Op
Power = String
"^"
{-# INLINE showOp #-}
showPython :: Fix SRTree -> String
showPython :: Fix SRTree -> String
showPython = forall (f :: * -> *) a. Functor f => (f a -> a) -> Fix f -> a
cata SRTree String -> String
alg
where
alg :: SRTree String -> String
alg (Var Int
ix) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"x[:, ", forall a. Show a => a -> String
show Int
ix, String
"]"]
alg (Param Int
ix) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"t[:, ", forall a. Show a => a -> String
show Int
ix, String
"]"]
alg (Const Double
c) = forall a. Show a => a -> String
show Double
c
alg (Bin Op
Power String
l String
r) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
l, String
" ** ", String
r]
alg (Bin Op
op String
l String
r) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"(", String
l, String
" ", Op -> String
showOp Op
op, String
" ", String
r, String
")"]
alg (Uni Function
f String
t) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [Function -> String
pyFun Function
f, String
"(", String
t, String
")"]
pyFun :: Function -> String
pyFun Function
Id = String
""
pyFun Function
Abs = String
"np.abs"
pyFun Function
Sin = String
"np.sin"
pyFun Function
Cos = String
"np.cos"
pyFun Function
Tan = String
"np.tan"
pyFun Function
Sinh = String
"np.sinh"
pyFun Function
Cosh = String
"np.cosh"
pyFun Function
Tanh = String
"np.tanh"
pyFun Function
ASin = String
"np.asin"
pyFun Function
ACos = String
"np.acos"
pyFun Function
ATan = String
"np.atan"
pyFun Function
ASinh = String
"np.asinh"
pyFun Function
ACosh = String
"np.acosh"
pyFun Function
ATanh = String
"np.atanh"
pyFun Function
Sqrt = String
"np.sqrt"
pyFun Function
Square = String
"np.square"
pyFun Function
Log = String
"np.log"
pyFun Function
Exp = String
"np.exp"
printPython :: Fix SRTree -> IO ()
printPython :: Fix SRTree -> IO ()
printPython = String -> IO ()
putStrLn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fix SRTree -> String
showPython
showLatex :: Fix SRTree -> String
showLatex :: Fix SRTree -> String
showLatex = forall (f :: * -> *) a. Functor f => (f a -> a) -> Fix f -> a
cata SRTree String -> String
alg
where
alg :: SRTree String -> String
alg (Var Int
ix) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"x_{, ", forall a. Show a => a -> String
show Int
ix, String
"}"]
alg (Param Int
ix) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"\\theta_{, ", forall a. Show a => a -> String
show Int
ix, String
"}"]
alg (Const Double
c) = forall a. Show a => a -> String
show Double
c
alg (Bin Op
Power String
l String
r) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
l, String
"^{", String
r, String
"}"]
alg (Bin Op
op String
l String
r) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"\\left(", String
l, String
" ", Op -> String
showOp Op
op, String
" ", String
r, String
"\\right)"]
alg (Uni Function
Abs String
t) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"\\left |", String
t, String
"\\right |"]
alg (Uni Function
f String
t) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [Function -> String
showLatexFun Function
f, String
"(", String
t, String
")"]
showLatexFun :: Function -> String
showLatexFun :: Function -> String
showLatexFun Function
f = forall a. Monoid a => [a] -> a
mconcat [String
"\\operatorname{", forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Function
f, String
"}"]
{-# INLINE showLatexFun #-}
printLatex :: Fix SRTree -> IO ()
printLatex :: Fix SRTree -> IO ()
printLatex = String -> IO ()
putStrLn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fix SRTree -> String
showLatex
showTikz :: Fix SRTree -> String
showTikz :: Fix SRTree -> String
showTikz = forall (f :: * -> *) a. Functor f => (f a -> a) -> Fix f -> a
cata SRTree String -> String
alg
where
roundN :: p -> a -> a
roundN p
n a
x = let ten :: a
ten = a
10forall a b. (Num a, Integral b) => a -> b -> a
^p
n in (forall a. Fractional a => a -> a -> a
/ a
ten) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (RealFrac a, Integral b) => a -> b
round forall a b. (a -> b) -> a -> b
$ a
xforall a. Num a => a -> a -> a
*a
ten
alg :: SRTree String -> String
alg (Var Int
ix) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"[$x_{, ", forall a. Show a => a -> String
show Int
ix, String
"}$]\n"]
alg (Param Int
ix) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"[$\\theta_{, ", forall a. Show a => a -> String
show Int
ix, String
"}$]\n"]
alg (Const Double
c) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"[$", forall a. Show a => a -> String
show (forall {a} {p}. (RealFrac a, Integral p) => p -> a -> a
roundN Integer
2 Double
c), String
"$]\n"]
alg (Bin Op
op String
l String
r) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"[", Op -> String
showOpTikz Op
op, String
l, String
r, String
"]\n"]
alg (Uni Function
f String
t) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"[", forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Function
f, String
t, String
"]\n"]
showOpTikz :: Op -> String
showOpTikz Op
Add = String
"+\n"
showOpTikz Op
Sub = String
"-\n"
showOpTikz Op
Mul = String
"×\n"
showOpTikz Op
Div = String
"÷\n"
showOpTikz Op
Power = String
"\\^{}\n"
printTikz :: Fix SRTree -> IO ()
printTikz = String -> IO ()
putStrLn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fix SRTree -> String
showTikz