module HSP.HTML4
(
renderAsHTML
, htmlEscapeChars
, html4Strict
, html4StrictFrag
) where
import Data.List (intersperse)
import Data.Monoid ((<>), mconcat)
import Data.String (fromString)
import Data.Text.Lazy.Builder (Builder, fromLazyText, singleton, toLazyText)
import Data.Text.Lazy (Text)
import HSP.XML ( Attribute(..), Attributes, AttrValue(..), Children
, NSName, XML(..), XMLMetaData(..))
import HSP.XML.PCDATA (escaper)
data TagType = Open | Close
htmlEscapeChars :: [(Char, Builder)]
htmlEscapeChars = [
('&', fromString "amp" ),
('\"', fromString "quot" ),
('<', fromString "lt" ),
('>', fromString "gt" )
]
renderTag :: TagType -> Int -> NSName -> Attributes -> Builder
renderTag typ n name attrs =
let (start,end) = case typ of
Open -> (singleton '<', singleton '>')
Close -> (fromString "</", singleton '>')
nam = showName name
as = renderAttrs attrs
in mconcat [start, nam, as, end]
where renderAttrs :: Attributes -> Builder
renderAttrs [] = nl
renderAttrs attrs' = singleton ' ' <> mconcat ats <> nl
where ats = intersperse (singleton ' ') $ fmap renderAttr attrs'
renderAttr :: Attribute -> Builder
renderAttr (MkAttr (nam, (Value needsEscape val))) =
showName nam <> singleton '=' <> renderAttrVal (if needsEscape then (escaper htmlEscapeChars val) else fromLazyText val)
renderAttr (MkAttr (nam, NoValue)) = showName nam
renderAttrVal :: Builder -> Builder
renderAttrVal s = singleton '\"' <> s <> singleton '\"'
showName (Nothing, s) = fromLazyText s
showName (Just d, s) = fromLazyText d <> singleton ':' <> fromLazyText s
nl = singleton '\n' <> fromString (replicate n ' ')
renderElement :: Int -> XML -> Builder
renderElement n (Element name attrs children) =
let open = renderTag Open n name attrs
cs = renderChildren n children
close = renderTag Close n name []
in open <> cs <> close
where renderChildren :: Int -> Children -> Builder
renderChildren n' cs = mconcat $ map (renderAsHTML' (n'+2)) cs
renderElement _ _ = error "internal error: renderElement only suports the Element constructor."
renderAsHTML' :: Int -> XML -> Builder
renderAsHTML' _ (CDATA needsEscape cd) = if needsEscape then (escaper htmlEscapeChars cd) else fromLazyText cd
renderAsHTML' n elm@(Element name@(Nothing,nm) attrs children)
| nm == "area" = renderTagEmpty children
| nm == "base" = renderTagEmpty children
| nm == "br" = renderTagEmpty children
| nm == "col" = renderTagEmpty children
| nm == "hr" = renderTagEmpty children
| nm == "img" = renderTagEmpty children
| nm == "input" = renderTagEmpty children
| nm == "link" = renderTagEmpty children
| nm == "meta" = renderTagEmpty children
| nm == "param" = renderTagEmpty children
| nm == "script" = renderElement n (Element name attrs (map asCDATA children))
| nm == "style" = renderElement n (Element name attrs (map asCDATA children))
where
renderTagEmpty [] = renderTag Open n name attrs
renderTagEmpty _ = renderElement n elm
asCDATA :: XML -> XML
asCDATA (CDATA _ cd) = (CDATA False cd)
asCDATA o = o
renderAsHTML' n e = renderElement n e
renderAsHTML :: XML -> Text
renderAsHTML xml = toLazyText $ renderAsHTML' 0 xml
html4Strict :: Maybe XMLMetaData
html4Strict = Just $
XMLMetaData { doctype = (True, "<!DOCTYPE HTML PUBLIC \"-//W3C//DTD HTML 4.01//EN\" \"http://www.w3.org/TR/html4/strict.dtd\">\n")
, contentType = "text/html;charset=utf-8"
, preferredRenderer = renderAsHTML' 0
}
html4StrictFrag :: Maybe XMLMetaData
html4StrictFrag = Just $
XMLMetaData { doctype = (False, "<!DOCTYPE HTML PUBLIC \"-//W3C//DTD HTML 4.01//EN\" \"http://www.w3.org/TR/html4/strict.dtd\">\n")
, contentType = "text/html;charset=utf-8"
, preferredRenderer = renderAsHTML' 0
}