{-#LANGUAGE DeriveFunctor #-}
module Text.Ginger.AST
where
import Data.Text (Text)
import qualified Data.Text as Text
import Text.Ginger.Html
import Data.Scientific (Scientific)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
type VarName = Text
data Template a
= Template
{ templateBody :: Statement a
, templateBlocks :: HashMap VarName (Block a)
, templateParent :: Maybe (Template a)
}
deriving (Show, Functor)
data Macro a
= Macro { macroArgs :: [VarName], macroBody :: Statement a }
deriving (Show, Functor)
data Block a
= Block { blockBody :: Statement a }
deriving (Show, Functor)
data Statement a
= MultiS a [Statement a]
| ScopedS a (Statement a)
| IndentS a (Expression a) (Statement a)
| LiteralS a Html
| InterpolationS a (Expression a)
| ExpressionS a (Expression a)
| IfS a (Expression a) (Statement a) (Statement a)
| SwitchS a (Expression a) [((Expression a), (Statement a))] (Statement a)
| ForS a (Maybe VarName) VarName (Expression a) (Statement a)
| SetVarS a VarName (Expression a)
| DefMacroS a VarName (Macro a)
| BlockRefS a VarName
| PreprocessedIncludeS a (Template a)
| NullS a
| TryCatchS a (Statement a) [CatchBlock a] (Statement a)
deriving (Show, Functor)
stmtAnnotation (MultiS a _) = a
stmtAnnotation (ScopedS a _) = a
stmtAnnotation (IndentS a _ _) = a
stmtAnnotation (LiteralS a _) = a
stmtAnnotation (InterpolationS a _) = a
stmtAnnotation (ExpressionS a _) = a
stmtAnnotation (IfS a _ _ _) = a
stmtAnnotation (SwitchS a _ _ _) = a
stmtAnnotation (ForS a _ _ _ _) = a
stmtAnnotation (SetVarS a _ _) = a
stmtAnnotation (DefMacroS a _ _) = a
stmtAnnotation (BlockRefS a _) = a
stmtAnnotation (PreprocessedIncludeS a _) = a
stmtAnnotation (NullS a) = a
stmtAnnotation (TryCatchS a _ _ _) = a
data CatchBlock a =
Catch
{ catchWhat :: Maybe Text
, catchCaptureAs :: Maybe VarName
, catchBody :: Statement a
}
deriving (Show, Functor)
data Expression a
= StringLiteralE a Text
| NumberLiteralE a Scientific
| BoolLiteralE a Bool
| NullLiteralE a
| VarE a VarName
| ListE a [(Expression a)]
| ObjectE a [((Expression a), (Expression a))]
| MemberLookupE a (Expression a) (Expression a)
| CallE a (Expression a) [(Maybe Text, (Expression a))]
| LambdaE a [Text] (Expression a)
| TernaryE a (Expression a) (Expression a) (Expression a)
| DoE a (Statement a)
deriving (Show, Functor)
exprAnnotation (StringLiteralE a _) = a
exprAnnotation (NumberLiteralE a _) = a
exprAnnotation (BoolLiteralE a _) = a
exprAnnotation (NullLiteralE a) = a
exprAnnotation (VarE a _) = a
exprAnnotation (ListE a _) = a
exprAnnotation (ObjectE a _) = a
exprAnnotation (MemberLookupE a _ _) = a
exprAnnotation (CallE a _ _) = a
exprAnnotation (LambdaE a _ _) = a
exprAnnotation (TernaryE a _ _ _) = a
exprAnnotation (DoE a _) = a
class Annotated f where
annotation :: f p -> p
instance Annotated Expression where
annotation = exprAnnotation
instance Annotated Statement where
annotation = stmtAnnotation
instance Annotated Block where
annotation = annotation . blockBody
instance Annotated Macro where
annotation = annotation . macroBody
instance Annotated Template where
annotation = annotation . templateBody