WebBits-0.9.2: JavaScript analysis toolsSource codeContentsIndex
WebBits.Html.Syntax
Contents
HTML Data Structures
The Script class
Miscellaneous Functions
Description
Datatypes for HTML parameterized over an annotation type and a script type.
Synopsis
type HtmlId = String
type AttributeValue = String
data Attribute a s
= Attribute HtmlId AttributeValue a
| AttributeExpr a HtmlId s String
data Html a sc
= Element HtmlId [Attribute a sc] [Html a sc] a
| Text String a
| Comment String a
| HtmlSeq [Html a sc]
| ProcessingInstruction String a
| InlineScript sc a String
| Script sc a
class Script t where
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]
HTML Data Structures
type HtmlId = StringSource
type AttributeValue = StringSource
data Attribute a s Source
Constructors
Attribute HtmlId AttributeValue a
AttributeExpr a HtmlId s String
show/hide Instances
data Html a sc Source
Constructors
Element HtmlId [Attribute a sc] [Html a sc] a
Text String a
Comment String a
HtmlSeq [Html a sc]must be a non-empty list
ProcessingInstruction String a
InlineScript sc a String
Script sc a
show/hide Instances
Typeable2 Html
Functor (Html a)
Traversable (Html a)
Foldable (Html a)
(Eq a, Eq sc) => Eq (Html a sc)
(Data a, Data sc) => Data (Html a sc)
(Show a, Show sc) => Show (Html a sc)
PrettyPrintable s => PrettyPrintable (Html a s)
The Script class
class Script t whereSource

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).

Methods
parseScriptBlock :: [Attribute SourcePos t] -> CharParser a tSource
parseInlineScript :: Maybe (CharParser a t)Source
parseAttributeScript :: Maybe (CharParser a t)Source
show/hide Instances
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.
attributeUpdate :: HtmlId -> (String -> String) -> [Attribute a s] -> [Attribute a s]Source
attributeSet :: HtmlId -> String -> [Attribute a s] -> [Attribute a s]Source
Produced by Haddock version 2.3.0