module Bamboo.Theme.MiniHTML5.Helper where import Hack import Hack.Contrib.Utils import MPS.Env import MPS.Heavy (unescape_xml) import Prelude () import Data.Default import Hack.Contrib.Constants import Hack import Hack.Contrib.Response hiding (header) import MPS (u2b) import Data.ByteString.Lazy.Char8 (ByteString) import Data.ByteString.Lazy.UTF8 (fromString) import Text.XHtml.Strict (renderHtmlFragment, showHtmlFragment, HTML) import qualified Text.HTML.Moe as M import Text.HTML.Moe.Type (Attribute, MoeUnit) import Text.HTML.Yuuko import Text.HTML.Moe (prim, raw) slashed_script_name :: Env -> String slashed_script_name = script_name > ("/" /) doc_type :: String doc_type = "" xml_header :: String xml_header = "\n" home_nav :: String home_nav = "Home" href :: String -> Attribute href = u2b > escape_uri > M.href html_response :: ByteString -> Response html_response x = def .set_status 200 .set_content_type _TextHtmlUTF8 .set_body x render_rss :: String -> ByteString render_rss = (xml_header ++) > fromString rss_response :: ByteString -> Response rss_response = html_response > set_content_type "application/rss+xml" show_html :: (HTML a) => a -> MoeUnit show_html x = let r = x.showHtmlFragment in if r.yuuko "//pre".null then x.renderHtmlFragment.unescape_xml.prim else r.unescape_xml.raw