module BrownPLT.Html.Syntax
(
HtmlId,AttributeValue, Attribute (..), Html (..)
, Script (..)
, attributeValue, attributeUpdate, attributeSet, isAttributeExpr
) where
import Text.ParserCombinators.Parsec (CharParser, SourcePos)
import Text.PrettyPrint.HughesPJ (Doc)
import Data.Generics (Data, Typeable)
type HtmlId = String
type AttributeValue = String
data Attribute a s
= Attribute HtmlId AttributeValue a
| AttributeExpr a HtmlId s String
deriving (Show,Eq,Typeable,Data)
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
deriving (Show,Eq,Typeable,Data)
class Script t where
prettyPrintScript :: t -> Doc
parseScriptBlock:: [Attribute SourcePos t] -> CharParser a t
parseInlineScript:: Maybe (CharParser a t)
parseAttributeScript:: Maybe (CharParser a t)
isAttributeExpr (AttributeExpr _ _ _ _) = True
isAttributeExpr _ = False
attributeValue:: HtmlId -> [Attribute a s] -> Maybe String
attributeValue name [] = Nothing
attributeValue name ((AttributeExpr pos name' expr init):rest) =
if name == name' then Nothing
else attributeValue name rest
attributeValue name ((Attribute name' value _):rest) =
if name == name' then Just value
else attributeValue name rest
attributeSet:: HtmlId -> String -> [Attribute a s] -> [Attribute a s]
attributeSet n v attrs = attributeUpdate n (\_ -> v) attrs
attributeUpdate:: HtmlId -> (String -> String) -> [Attribute a s]
-> [Attribute a s]
attributeUpdate n f [] =
[Attribute n (f "") (error "attributeUpdate--no value")]
attributeUpdate n _ ((AttributeExpr _ _ _ _):_) =
error $ "attributeUpdate: " ++ n ++ " is an expression-attribute."
attributeUpdate n f ((Attribute n' v p):attrs) =
if n' == n then (Attribute n (f v) p):attrs
else (Attribute n' v p):(attributeUpdate n f attrs)