{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Yesod.Hamlet ( -- * Hamlet library Hamlet , hamlet , HtmlContent (..) , htmlContentToText -- * Convert to something displayable , hamletToContent , hamletToRepHtml -- * Page templates , PageContent (..) ) where import Text.Hamlet import Text.Hamlet.Monad (outputHtml, htmlContentToText) import Yesod.Content import Yesod.Handler import Data.Convertible.Text import Web.Routes.Quasi (Routes) -- | Content for a web page. By providing this datatype, we can easily create -- generic site templates, which would have the type signature: -- -- > PageContent url -> Hamlet url IO () data PageContent url = PageContent { pageTitle :: HtmlContent , pageHead :: Hamlet url IO () , pageBody :: Hamlet url IO () } -- | Converts the given Hamlet template into 'Content', which can be used in a -- Yesod 'Response'. hamletToContent :: Hamlet (Routes master) IO () -> GHandler sub master Content hamletToContent h = do render <- getUrlRender return $ ContentEnum $ go render where go render iter seed = do res <- runHamlet h render seed $ iter' iter case res of Left x -> return $ Left x Right ((), x) -> return $ Right x iter' iter seed text = iter seed $ cs text -- | Wraps the 'Content' generated by 'hamletToContent' in a 'RepHtml'. hamletToRepHtml :: Hamlet (Routes master) IO () -> GHandler sub master RepHtml hamletToRepHtml = fmap RepHtml . hamletToContent instance Monad m => ConvertSuccess String (Hamlet url m ()) where convertSuccess = outputHtml . Unencoded . cs instance ConvertSuccess String HtmlContent where convertSuccess = Unencoded . cs