{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} {-# OPTIONS_GHC -F -pgmFtrhsx #-} module AppView where import AppState import HSP import System.Locale (defaultTimeLocale) import System.Time (formatCalendarTime, toUTCTime) import Control.Monad.Trans (MonadIO) import Happstack.Server.HStringTemplate (webST) import Happstack.Server.HSP.HTML (webHSP) -- Convenience Functions dateStr ct = formatCalendarTime defaultTimeLocale "%a, %B %d, %Y at %H:%M:%S (UTC)" (toUTCTime ct) -- Main Implementation instance (XMLGenerator m) => (EmbedAsChild m (GuestBookEntry, Bool)) where asChild ((GuestBookEntry author message date), alt) = <%
  • <% author %> said:

    <% map p (lines message) %>
    <% dateStr date %>
  • %> where p str =

    <% str %>

    instance (XMLGenerator m) => (EmbedAsChild m GuestBook) where asChild (GuestBook entries) = <%

    Words of Wisdom

    %> renderFromBody title body = webHSP $ pageFromBody title body pageFromBody :: (EmbedAsChild (HSPT' IO) xml) => String -> xml -> HSP XML pageFromBody title body = withMetaData html4Strict $ <% title %>
    14
    Feb

    Happstack Guestbook

    Hey congrats! You're using Happstack 0.2. 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 now = do webST "readme" [("time", dateStr now)]