Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Slab.Syntax
provides data types to represent the syntax used by the Slab
language. It also provides small helpers functions to operate on the syntax.
Synopsis
- data Block
- = BlockDoctype
- | BlockElem Elem TrailingSym [Attr] [Block]
- | BlockText TextSyntax [Inline]
- | BlockInclude (Maybe Text) FilePath (Maybe [Block])
- | BlockFragmentDef Text [Text] [Block]
- | BlockFragmentCall Text TrailingSym [Attr] [Expr] [Block]
- | BlockFor Text (Maybe Text) Expr [Block]
- | BlockComment CommentType Text
- | BlockFilter Text Text
- | BlockRawElem Text [Block]
- | BlockDefault Text [Block]
- | BlockImport FilePath (Maybe [Block]) [Block]
- | BlockRun Text (Maybe [Block])
- | BlockReadJson Text FilePath (Maybe Value)
- | BlockAssignVar Text Expr
- | BlockIf Expr [Block] [Block]
- | BlockList [Block]
- | BlockCode Expr
- isDoctype :: Block -> Bool
- pasteBlocks :: Block -> Block -> Block
- setAttrs :: [Attr] -> [Block] -> [Block]
- setContent :: [Block] -> Block -> Block
- data CommentType
- data Elem
- = Html
- | Body
- | Div
- | Span
- | Br
- | Hr
- | H1
- | H2
- | H3
- | H4
- | H5
- | H6
- | Header
- | Head
- | Meta
- | Main
- | Link
- | A
- | P
- | Ul
- | Li
- | Title
- | Table
- | Thead
- | Tbody
- | Tr
- | Td
- | Dl
- | Dt
- | Dd
- | Footer
- | Figure
- | Form
- | Label
- | Blockquote
- | Button
- | Figcaption
- | Audio
- | Script
- | Style
- | Small
- | Source
- | Pre
- | Code
- | Img
- | IFrame
- | Input
- | I
- | Svg
- | Textarea
- | Canvas
- | Elem Text
- data TrailingSym
- data Attr
- data TextSyntax
- data Expr
- = Variable Text
- | Bool Bool
- | Int Int
- | SingleQuoteString Text
- | List [Expr]
- | Object [(Expr, Expr)]
- | Lookup Text Expr
- | Application Expr Expr
- | Add Expr Expr
- | Sub Expr Expr
- | Times Expr Expr
- | Divide Expr Expr
- | GreaterThan Expr Expr
- | LesserThan Expr Expr
- | Equal Expr Expr
- | Cons Expr Expr
- | Block Block
- | Frag [Text] Env [Block]
- | Thunk Env Expr
- | BuiltIn Text
- data Inline
- data Env = Env {
- envVariables :: [(Text, Expr)]
- emptyEnv :: Env
- displayEnv :: Env -> Text
- trailingSym :: Block -> TrailingSym
- freeVariables :: Expr -> [Text]
- thunk :: Env -> Expr -> Expr
- extractClasses :: [Block] -> [Text]
- extractFragments :: [Block] -> [BlockFragment]
- findFragment :: Text -> [BlockFragment] -> Maybe [Block]
- idNamesFromAttrs :: [Attr] -> [Text]
- classNamesFromAttrs :: [Attr] -> [Text]
- namesFromAttrs :: [Attr] -> [(Text, Text)]
- groupAttrs :: [Attr] -> [Attr]
Documentation
BlockDoctype | Only |
BlockElem Elem TrailingSym [Attr] [Block] | |
BlockText TextSyntax [Inline] | |
BlockInclude (Maybe Text) FilePath (Maybe [Block]) |
|
BlockFragmentDef Text [Text] [Block] | This doesn't exist in Pug. This is like a mixin than receive block arguments.
Or like a parent template that can be |
BlockFragmentCall Text TrailingSym [Attr] [Expr] [Block] | |
BlockFor Text (Maybe Text) Expr [Block] | |
BlockComment CommentType Text | |
BlockFilter Text Text | |
BlockRawElem Text [Block] | |
BlockDefault Text [Block] |
|
BlockImport FilePath (Maybe [Block]) [Block] | Similar to an anonymous fragment call, where the fragment body is the content of the referenced file. |
BlockRun Text (Maybe [Block]) | |
BlockReadJson Text FilePath (Maybe Value) | Allow to assign the content of a JSON file to a variable. The syntax
is specific to how Struct has a |
BlockAssignVar Text Expr | |
BlockIf Expr [Block] [Block] | |
BlockList [Block] | |
BlockCode Expr |
pasteBlocks :: Block -> Block -> Block Source #
Takes two blocks and returns a BlockList containing both, but peel the outer list of a and b if they are themselves BlockList.
setAttrs :: [Attr] -> [Block] -> [Block] Source #
Set attrs on a the first block, if it is a BlockElem.
data CommentType Source #
A "passthrough" comment will be included in the generated HTML.
Instances
Show CommentType Source # | |
Defined in Slab.Syntax showsPrec :: Int -> CommentType -> ShowS # show :: CommentType -> String # showList :: [CommentType] -> ShowS # | |
Eq CommentType Source # | |
Defined in Slab.Syntax (==) :: CommentType -> CommentType -> Bool # (/=) :: CommentType -> CommentType -> Bool # |
Html | |
Body | |
Div | |
Span | |
Br | |
Hr | |
H1 | |
H2 | |
H3 | |
H4 | |
H5 | |
H6 | |
Header | |
Head | |
Meta | |
Main | |
Link | |
A | |
P | |
Ul | |
Li | |
Title | |
Table | |
Thead | |
Tbody | |
Tr | |
Td | |
Dl | |
Dt | |
Dd | |
Footer | |
Figure | |
Form | |
Label | |
Blockquote | |
Button | |
Figcaption | |
Audio | |
Script | |
Style | |
Small | |
Source | |
Pre | |
Code | |
Img | |
IFrame | |
Input | |
I | |
Svg | |
Textarea | |
Canvas | |
Elem Text | Arbitrary element name, using the |
data TrailingSym Source #
Instances
Show TrailingSym Source # | |
Defined in Slab.Syntax showsPrec :: Int -> TrailingSym -> ShowS # show :: TrailingSym -> String # showList :: [TrailingSym] -> ShowS # | |
Eq TrailingSym Source # | |
Defined in Slab.Syntax (==) :: TrailingSym -> TrailingSym -> Bool # (/=) :: TrailingSym -> TrailingSym -> Bool # |
data TextSyntax Source #
Normal | The text follows an element on the same line. |
Pipe | The text follows a pipe character. Multiple lines each introduced by a
pipe symbol are grouped as a single |
Dot | The text is part of a text block following a trailing dot. |
Include | The text is the content of an include statement without a .slab extension. |
RunOutput | The text is the output of command. |
Instances
Show TextSyntax Source # | |
Defined in Slab.Syntax showsPrec :: Int -> TextSyntax -> ShowS # show :: TextSyntax -> String # showList :: [TextSyntax] -> ShowS # | |
Eq TextSyntax Source # | |
Defined in Slab.Syntax (==) :: TextSyntax -> TextSyntax -> Bool # (/=) :: TextSyntax -> TextSyntax -> Bool # |
Simple expression language.
Env | |
|
displayEnv :: Env -> Text Source #
trailingSym :: Block -> TrailingSym Source #
freeVariables :: Expr -> [Text] Source #
extractClasses :: [Block] -> [Text] Source #
extractFragments :: [Block] -> [BlockFragment] Source #
idNamesFromAttrs :: [Attr] -> [Text] Source #
classNamesFromAttrs :: [Attr] -> [Text] Source #
groupAttrs :: [Attr] -> [Attr] Source #
Group multiple classes or IDs in a single class or ID, and transform the
other attributes in SingleQuoteString
s.