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 _ Integer = Ops -> Expr
P.MO Ops
P.Integer
space _ Rational = Ops -> Expr
P.MO Ops
P.Rational
space _ Real = Ops -> Expr
P.MO Ops
P.Real
space _ Natural = Ops -> Expr
P.MO Ops
P.Natural
space _ Boolean = Ops -> Expr
P.MO Ops
P.Boolean
space _ Char = String -> Expr
P.Ident "Char"
space _ String = String -> Expr
P.Ident "String"
space _ Radians = String -> Expr
forall a. HasCallStack => String -> a
error "Radians not translated"
space _ (Vect _) = String -> Expr
forall a. HasCallStack => String -> a
error "Vector space not translated"
space _ (Array _) = String -> Expr
forall a. HasCallStack => String -> a
error "Array space not translated"
space _ (Actor s :: String
s) = String -> Expr
P.Ident String
s
space sm :: PrintingInformation
sm (DiscreteD l :: [Double]
l) = Fence -> Fence -> Expr -> Expr
P.Fenced Fence
P.Curly Fence
P.Curly (Expr -> Expr) -> Expr -> Expr
forall a b. (a -> b) -> a -> b
$ [Expr] -> Expr
P.Row ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ Expr -> [Expr] -> [Expr]
forall a. a -> [a] -> [a]
intersperse (Ops -> Expr
P.MO Ops
P.Comma) ([Expr] -> [Expr]) -> [Expr] -> [Expr]
forall a b. (a -> b) -> a -> b
$ (Double -> Expr) -> [Double] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map ((Expr -> PrintingInformation -> Expr)
-> PrintingInformation -> Expr -> Expr
forall a b c. (a -> b -> c) -> b -> a -> c
flip Expr -> PrintingInformation -> Expr
expr PrintingInformation
sm (Expr -> Expr) -> (Double -> Expr) -> Double -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Expr
forall r. LiteralC r => Double -> r
dbl) [Double]
l
space _ (DiscreteS l :: [String]
l) = Fence -> Fence -> Expr -> Expr
P.Fenced Fence
P.Curly Fence
P.Curly (Expr -> Expr) -> Expr -> Expr
forall a b. (a -> b) -> a -> b
$ [Expr] -> Expr
P.Row ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ Expr -> [Expr] -> [Expr]
forall a. a -> [a] -> [a]
intersperse (Ops -> Expr
P.MO Ops
P.Comma) ([Expr] -> [Expr]) -> [Expr] -> [Expr]
forall a b. (a -> b) -> a -> b
$ (String -> Expr) -> [String] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map String -> Expr
P.Str [String]
l
space _ Void = String -> Expr
forall a. HasCallStack => String -> a
error "Void not translated"
space sm :: PrintingInformation
sm (Function i :: NonEmpty Space
i t :: Space
t) = [Expr] -> Expr
P.Row ([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$
Expr -> [Expr] -> [Expr]
forall a. a -> [a] -> [a]
intersperse (Ops -> Expr
P.MO Ops
P.Cross) ((Space -> Expr) -> [Space] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Space -> Expr
space PrintingInformation
sm) ([Space] -> [Expr]) -> [Space] -> [Expr]
forall a b. (a -> b) -> a -> b
$ NonEmpty Space -> [Space]
forall a. NonEmpty a -> [a]
toList NonEmpty Space
i) [Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++
[Ops -> Expr
P.MO Ops
P.RArrow, PrintingInformation -> Space -> Expr
space PrintingInformation
sm Space
t]