{-# LANGUAGE NoMonomorphismRestriction#-} {-# LANGUAGE NoImplicitPrelude #-} module Bamboo.Theme.Blueprint.Helper where import Bamboo.Env import Bamboo.Helper.ByteString import Data.ByteString import Data.Default import Hack import Hack.Contrib.Constants import Hack.Contrib.Response import MPS.Heavy import Text.XHtml.Strict hiding (p, meta, body) import qualified Prelude as P import qualified Text.XHtml.Strict as Html id :: String -> HtmlAttr id = identifier css_link :: String -> Html js_link :: String -> Html js_src :: String -> Html rss_link :: String -> Html favicon_link :: String -> Html css_link l = itag "link" ! [rel "stylesheet", thetype "text/css", href l] js_link l = itag "script" ! [thetype "text/javascript", src l] js_src s = tag "script" ! [thetype "text/javascript"] << s favicon_link l = itag "link" ! [rel "icon", thetype "image/png", href l] rss_link l = itag "link" ! [rel "alternate", thetype "application/rss+xml", href l, title "RSS 2.0"] div_id :: String -> Html -> Html div_id s = thediv ! [id s] div_class :: String -> Html -> Html div_class s = thediv ! [theclass s] div_class_id :: String -> String -> Html -> Html div_class_id x y = thediv ! [theclass x, id y] meta_tag :: Html meta_tag = Html.meta ! [httpequiv "Content-Type", content "text/html; charset=utf-8"] ie_tag :: (Show a) => a -> Html ie6_tag :: (Show a) => a -> Html ie7_tag :: (Show a) => a -> Html ie_tag x = ("").primHtml ie6_tag x = ("").primHtml ie7_tag x = ("").primHtml xml_header :: String xml_header = "\n" render_html :: Html -> ByteString render_html = renderHtml > unescape_unicode_xml > to_sb output_html :: Html -> IO Response output_html = render_html > output_plain_html render_rss :: String -> ByteString render_rss = (xml_header ++) > unescape_unicode_xml > to_sb output_plain_html :: ByteString -> IO Response output_plain_html x = def .set_status 200 .set_body (x.to_lb) .set_content_type _TextHtmlUTF8 .return output_plain_rss :: ByteString -> IO Response output_plain_rss = output_plain_html > (^ set_content_type "application/rss+xml") html_if :: Bool -> Html -> Html html_if b x = if b then x else empty_html -- html alias img :: Html space_html :: Html img = image space_html = primHtml " " span :: Html -> Html div :: Html -> Html d :: Html -> Html ul :: Html -> Html span = thespan div = thediv d = div ul = ulist klass :: String -> HtmlAttr klass = theclass c, i:: String -> Html -> Html c x = d ! [klass x] i x = d ! [id x] ic, ci:: String -> String -> Html -> Html ic x y = d ! [id x, klass y] ci x y = ic y x link :: String -> Html -> HotLink link = hotlink