{-# LANGUAGE PatternGuards, OverloadedStrings #-}
module Text.HTML.TagSoup.Render
    (
    renderTags, renderTagsOptions, escapeHTML,
    RenderOptions(..), renderOptions
    ) where
import Text.HTML.TagSoup.Entity
import Text.HTML.TagSoup.Type
import Text.StringLike
data RenderOptions str = RenderOptions
    {optEscape :: str -> str        
    ,optMinimize :: str -> Bool     
    ,optRawTag :: str -> Bool      
    }
escapeHTML :: StringLike str => str -> str
escapeHTML = fromString . escapeXML . toString
renderOptions :: StringLike str => RenderOptions str
renderOptions = RenderOptions escapeHTML (\x -> toString x == "br") (\x -> toString x == "script")
renderTags :: StringLike str => [Tag str] -> str
renderTags = renderTagsOptions renderOptions
renderTagsOptions :: StringLike str => RenderOptions str -> [Tag str] -> str
renderTagsOptions opts = strConcat . tags
    where
        ss x = [x]
        tags (TagOpen name atts:TagClose name2:xs)
            | name == name2 && optMinimize opts name = open name atts " /" ++ tags xs
        tags (TagOpen name atts:xs)
            | Just ('?',_) <- uncons name = open name atts " ?" ++ tags xs
            | optRawTag opts name =
                let (a,b) = break (== TagClose name) (TagOpen name atts:xs)
                in concatMap (\x -> case x of TagText s -> [s]; _ -> tag x) a ++ tags b
        tags (x:xs) = tag x ++ tags xs
        tags [] = []
        tag (TagOpen name atts) = open name atts ""
        tag (TagClose name) = ["</", name, ">"]
        tag (TagText text) = [txt text]
        tag (TagComment text) = ss "<!--" ++ com text ++ ss "-->"
        tag _ = ss ""
        txt = optEscape opts
        open name atts shut = ["<",name] ++ concatMap att atts ++ [shut,">"]
        att ("","") = [" \"\""]
        att (x ,"") = [" ", x]
        att ("", y) = [" \"",txt y,"\""]
        att (x , y) = [" ",x,"=\"",txt y,"\""]
        com xs | Just ('-',xs) <- uncons xs, Just ('-',xs) <- uncons xs, Just ('>',xs) <- uncons xs = "-- >" : com xs
        com xs = case uncons xs of
            Nothing -> []
            Just (x,xs) -> fromChar x : com xs