{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} {-# OPTIONS_GHC -F -pgmFtrhsx #-} module App.View where import HSP import System.Locale (defaultTimeLocale) import System.Time (ClockTime(..), formatCalendarTime, toUTCTime) import Control.Monad.Trans (MonadIO) import Happstack.Server (Response) import Happstack.Server.HStringTemplate (webST) import Happstack.Server.HSP.HTML (webHSP) -- * Convenience Functions dateStr :: ClockTime -> String dateStr ct = formatCalendarTime defaultTimeLocale "%a, %B %d, %Y at %H:%M:%S (UTC)" (toUTCTime ct) -- * Main Implementation renderFromBody :: (MonadIO m, EmbedAsChild (HSPT' IO) xml) => String -> xml -> m Response renderFromBody title = webHSP . pageFromBody title pageFromBody :: (EmbedAsChild (HSPT' IO) xml) => String -> xml -> HSP XML pageFromBody title body = withMetaData html4Strict $ <% title %>

Links

14
Feb

Happstack Guestbook

Hey congrats! You're using Happstack 0.3. This is a guestbook example which you can freely change to your whims and fancies.

This page is written using Haskell Server Pages (HSP). For an example of a page using HStringTemplate, look at the dynamic README.

Leave a message for the next visitor here...




<% body %>
renderREADME :: (MonadIO m) => ClockTime -> m Response renderREADME now = webST "readme" [("time", dateStr now)]