module Language.Drasil.Printing.Import.Space where
import Language.Drasil (dbl, Space(..))
import qualified Language.Drasil.Printing.AST as P
import Language.Drasil.Printing.PrintingInformation (PrintingInformation)
import Language.Drasil.Printing.Import.Expr (expr)
import Data.List (intersperse)
import Data.List.NonEmpty (toList)
space :: PrintingInformation -> Space -> P.Expr
space :: PrintingInformation -> Space -> Expr
space PrintingInformation
_ Space
Integer = Ops -> Expr
P.MO Ops
P.Integer
space PrintingInformation
_ Space
Rational = Ops -> Expr
P.MO Ops
P.Rational
space PrintingInformation
_ Space
Real = Ops -> Expr
P.MO Ops
P.Real
space PrintingInformation
_ Space
Natural = Ops -> Expr
P.MO Ops
P.Natural
space PrintingInformation
_ Space
Boolean = Ops -> Expr
P.MO Ops
P.Boolean
space PrintingInformation
_ Space
Char = String -> Expr
P.Ident String
"Char"
space PrintingInformation
_ Space
String = String -> Expr
P.Ident String
"String"
space PrintingInformation
_ (Vect Space
_) = forall a. HasCallStack => String -> a
error String
"Vector space not translated"
space PrintingInformation
_ Matrix {} = forall a. HasCallStack => String -> a
error String
"Matrix space not translated"
space PrintingInformation
_ (Array Space
_) = forall a. HasCallStack => String -> a
error String
"Array space not translated"
space PrintingInformation
_ (Actor String
s) = String -> Expr
P.Ident String
s
space PrintingInformation
sm (DiscreteD [Double]
l) = Fence -> Fence -> Expr -> Expr
P.Fenced Fence
P.Curly Fence
P.Curly forall a b. (a -> b) -> a -> b
$ [Expr] -> Expr
P.Row forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a]
intersperse (Ops -> Expr
P.MO Ops
P.Comma) forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. (a -> b -> c) -> b -> a -> c
flip Expr -> PrintingInformation -> Expr
expr PrintingInformation
sm forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall r. LiteralC r => Double -> r
dbl) [Double]
l
space PrintingInformation
_ (DiscreteS [String]
l) = Fence -> Fence -> Expr -> Expr
P.Fenced Fence
P.Curly Fence
P.Curly forall a b. (a -> b) -> a -> b
$ [Expr] -> Expr
P.Row forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a]
intersperse (Ops -> Expr
P.MO Ops
P.Comma) forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map String -> Expr
P.Str [String]
l
space PrintingInformation
_ Space
Void = forall a. HasCallStack => String -> a
error String
"Void not translated"
space PrintingInformation
sm (Function NonEmpty Space
i Space
t) = [Expr] -> Expr
P.Row forall a b. (a -> b) -> a -> b
$
forall a. a -> [a] -> [a]
intersperse (Ops -> Expr
P.MO Ops
P.Cross) (forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Space -> Expr
space PrintingInformation
sm) forall a b. (a -> b) -> a -> b
$ forall a. NonEmpty a -> [a]
toList NonEmpty Space
i) forall a. [a] -> [a] -> [a]
++
[Ops -> Expr
P.MO Ops
P.RArrow, PrintingInformation -> Space -> Expr
space PrintingInformation
sm Space
t]