{-# LANGUAGE NoImplicitPrelude #-} module Bamboo.Theme.MiniHTML5.Atom.Post where import Bamboo.Helper.StateHelper hiding (uri) import Bamboo.Model.Post import qualified Bamboo.Model.Post as P import Data.List (intersperse) import Bamboo.Theme.MiniHTML5.Env hiding (name, style) import Bamboo.Theme.MiniHTML5.Widget.Helper data RenderStyle = Summary | Full entry' :: State -> RenderStyle -> Post -> MoeUnit entry' s style x = article' - do header' - a [href - s.env.slashed_script_name / x.uri] - do str - x.P.title aside' - do span [_class "time"] - str - post_date when (x.tags.null.not) - do span' - str " | Published in" nav' - ul' - x.tags.map (tag_link s > li').intersperse (str ", ").sequence_ {- when (x.comment_size.is 0.not) - do span' - do str " | " a [href - x.uri / "#comments"] - str - x.comment_size.show ++ " Comments" -} show_content style .show_html where show_content Summary = x.markup_summary show_content Full = x.markup post_date = x.date.format_time "%b %e, %Y" entry :: State -> Post -> MoeUnit entry s = render_summary s (s.config.summary_for_root) render_summary :: State -> Bool -> Post -> MoeUnit render_summary s t = if t then entry' s Summary else entry' s Full