Datatypes for HTML parameterized over an annotation type and a script type.
- type HtmlId = String
- type AttributeValue = String
- data Attribute a s
- = Attribute HtmlId AttributeValue a
- | AttributeExpr a HtmlId s String
- data Html a sc
- class Script t where
- prettyPrintScript :: t -> Doc
- parseScriptBlock :: [Attribute SourcePos t] -> CharParser a t
- parseInlineScript :: Maybe (CharParser a t)
- parseAttributeScript :: Maybe (CharParser a t)
- attributeValue :: HtmlId -> [Attribute a s] -> Maybe String
- attributeUpdate :: HtmlId -> (String -> String) -> [Attribute a s] -> [Attribute a s]
- attributeSet :: HtmlId -> String -> [Attribute a s] -> [Attribute a s]
- isAttributeExpr :: Attribute t t1 -> Bool
HTML Data Structures
type AttributeValue = StringSource
The Script class
A type t
of the Script
class can be parsed using Parsec
. t
is of
kind '* -> *', as the parsed AST should be annotated with souce locations
(see SourcePos
).
The big deal here is that we can embed a parser for some scripting language, (e.g. Javascript) into this HTML parser with ease, while preserving source locations. The Html datatype is parameterized over a script parser (an instance of Script).
prettyPrintScript :: t -> DocSource
parseScriptBlock :: [Attribute SourcePos t] -> CharParser a tSource
parseInlineScript :: Maybe (CharParser a t)Source
parseAttributeScript :: Maybe (CharParser a t)Source
Miscellaneous Functions
attributeValue :: HtmlId -> [Attribute a s] -> Maybe StringSource
Returns the value of the attribute in the list, or Nothing
if it doesn't
exist of the value is an inline-expression.
isAttributeExpr :: Attribute t t1 -> BoolSource