{-# LANGUAGE NoMonomorphismRestriction #-} module Text.HTML.Moe ( module Text.HTML.Moe.Element , module Text.HTML.Moe.Attribute , (/) , render ) where import Control.Monad.Writer (tell, execWriter) import Prelude hiding ((/), (-), head, (>), (.)) import MPS.Light ((-), (>), (.), join, times) import Text.HTML.Moe.Type hiding (name, value) import qualified Text.HTML.Moe.Type as T import Text.HTML.Moe.Element import Text.HTML.Moe.Attribute (/) :: MoeUnit (/) = return () render :: MoeUnit -> String render = execWriter > map render_element > join "\n" indent_space :: Int indent_space = 2 render_element' :: Int -> Element -> String render_element' _ (Raw x) = x render_element' n (Data x) = execWriter - do tell - (n * indent_space).times ' ' tell - escape - x tell - "\n" render_element' n x = execWriter - do tell - indent tell - "<" ++ x.T.name ++ "" tell - x.attributes.map render_attribute. join_attribute tell - ">" tell - "\n" tell - x.elements.map (render_element' (n+1)) .concat tell - indent tell - "" tell - "\n" where join_attribute xs = xs.map (" " ++) .concat indent = (n * indent_space).times ' ' render_element :: Element -> String render_element = render_element' 0 render_attribute :: Attribute -> String render_attribute x = x.key ++ "=" ++ "\"" ++ x.T.value.escape ++ "\"" escape :: String -> String escape = escape_html escape_html :: String -> String escape_html = concatMap fixChar where fixChar '&' = "&" fixChar '<' = "<" fixChar '>' = ">" fixChar '\'' = "'" fixChar '"' = """ fixChar x = [x]