{-# LANGUAGE NoMonomorphismRestriction#-} {-# LANGUAGE NoImplicitPrelude #-} module Bamboo.Theme.MiniHTML5.Widget.Template (page) where import Bamboo.Theme.MiniHTML5.Env hiding (navigation, sidebar) import Bamboo.Helper.StateHelper hiding (uri) import Bamboo.Type.State import Web.HCheat import Text.HTML.Moe.DSL.Kawaii import Data.ByteString.Lazy.Char8 (fromChunks) import Bamboo.Theme.MiniHTML5.Widget.Navigation import Bamboo.Theme.MiniHTML5.Widget.Sidebar import Bamboo.Theme.MiniHTML5.Widget.Helper import qualified Bamboo.Type.Config as C import qualified Bamboo.Type.State as S import qualified Bamboo.Type.Theme as T import Hack import Text.HTML.Moe.Type (Attribute) charset :: String -> Attribute charset = attr "charset" role :: String -> Attribute role = _class template, page :: State -> MoeUnit -> Response template s x = html_response - fromChunks - return - render' - do raw doc_type html' - do head' - do let apply_if f g y = if f y then g y else y root = (s.env.slashed_script_name /) page_title = s.config.blog_title ++ s.S.resource_title.apply_if (null > not) (" / " ++) meta [charset "utf-8"] -- google chrome frame for ie meta [http_equiv "X-UA-Compatible", content "chrome=1"] title' - str - page_title link [rel "icon", _type "image/png", href - root - s.config.favicon] link [rel "alternate", _type "application/rss+xml", href - rss_url_link_pair s .fst, attr "title" "RSS 2.0"] s.config.theme_config.T.css.mapM_ (root > css) s.config.theme_config.T.js.mapM_(root > js) -- html5 enabler for ie prim "" body' - do header [role "banner"] - do div [_class "title"] - str - s.config.blog_title div [_class "sub-title"] - str - s.config.blog_subtitle when (has_extension Search) - form [action "/search", method "get", role "search"] - input [name "s", id "s", _type "text", value ""] navigation s div [id "page"] - do section [role "posts"] - x sidebar s footer' - do case s.config.C.footer of Just y -> y.markup.show_html Nothing -> do str - "©2009 " ++ s.config.blog_title br' str - "Powered by " a [href - s.config.bamboo_url] - str "Bamboo" str - " using " a [href "http://www.haskell.org/"] - str "Haskell" when (has_extension Analytics) - raw - analytics - s.config.analytics_account_id page = template