Removed Yesod.Hamlet (code does not compile)

This commit is contained in:
Michael Snoyman 2010-12-24 15:52:25 +02:00
parent a9e713921e
commit 9f7223ea5e
5 changed files with 39 additions and 63 deletions

View File

@ -75,6 +75,8 @@ import Data.Monoid (mempty)
import qualified Data.JSON.Types as J
import qualified Text.JSON.Enumerator as J
import Text.Hamlet (Html)
import Text.Blaze.Renderer.Utf8 (renderHtmlBuilder)
data Content = ContentBuilder Builder
| ContentEnum (forall a. Enumerator Builder IO a)
@ -103,6 +105,8 @@ instance ToContent String where
toContent = toContent . T.pack
instance ToContent J.Value where
toContent = ContentBuilder . J.renderValue
instance ToContent Html where
toContent = ContentBuilder . renderHtmlBuilder
-- | A function which gives targetted representations of content based on the
-- content-types the user accepts.

View File

@ -44,7 +44,6 @@ import qualified Paths_yesod_core
import Data.Version (showVersion)
import Yesod.Widget
import Yesod.Request
import Yesod.Hamlet
import qualified Network.Wai as W
import Yesod.Internal
import Web.ClientSession (getKey, defaultKeyFile)

View File

@ -1,59 +0,0 @@
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Yesod.Hamlet
( -- * Hamlet library
-- ** Hamlet
hamlet
, xhamlet
, Hamlet
, Html
, renderHamlet
, renderHtml
, string
, preEscapedString
, cdata
-- ** Julius
, julius
, Julius
, renderJulius
-- ** Cassius
, cassius
, Cassius
, renderCassius
-- * Convert to something displayable
, hamletToContent
, hamletToRepHtml
-- * Page templates
, PageContent (..)
)
where
import Text.Hamlet
import Text.Cassius
import Text.Julius
import Yesod.Content
import Yesod.Handler
-- | 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
data PageContent url = PageContent
{ pageTitle :: Html
, pageHead :: Hamlet url
, pageBody :: Hamlet url
}
-- | Converts the given Hamlet template into 'Content', which can be used in a
-- Yesod 'Response'.
hamletToContent :: Hamlet (Route master) -> GHandler sub master Content
hamletToContent h = do
render <- getUrlRenderParams
return $ toContent $ renderHamlet render h
-- | Wraps the 'Content' generated by 'hamletToContent' in a 'RepHtml'.
hamletToRepHtml :: Hamlet (Route master) -> GHandler sub master RepHtml
hamletToRepHtml = fmap RepHtml . hamletToContent

View File

@ -9,6 +9,7 @@ module Yesod.Widget
( -- * Datatype
GWidget (..)
, liftHandler
, PageContent (..)
-- * Creating
-- ** Head of page
, setTitle
@ -31,7 +32,11 @@ module Yesod.Widget
, addScriptEither
-- * Utilities
, extractBody
, newIdent
, newIdent -- FIXME this should be a function on Handler, not Widget
-- * Helpers for specific content
-- ** Hamlet
, hamletToContent
, hamletToRepHtml
) where
import Data.Monoid
@ -40,11 +45,15 @@ import Control.Monad.Trans.State
import Text.Hamlet
import Text.Cassius
import Text.Julius
import Yesod.Handler (Route, GHandler, YesodSubRoute(..), toMasterHandlerMaybe, getYesod)
import Yesod.Handler
( Route, GHandler, YesodSubRoute(..), toMasterHandlerMaybe, getYesod
, getUrlRenderParams
)
import Control.Applicative (Applicative)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Trans.Class (lift)
import Yesod.Internal
import Yesod.Content (RepHtml (RepHtml), Content, toContent)
import Control.Monad.IO.Peel (MonadPeelIO)
@ -187,3 +196,26 @@ extractBody (GWidget w) =
GWidget $ mapWriterT (fmap go) w
where
go ((), Body h) = (h, Body mempty)
-- | 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
data PageContent url = PageContent
{ pageTitle :: Html
, pageHead :: Hamlet url
, pageBody :: Hamlet url
}
-- FIXME these ideally belong somewhere else, I'm just not sure where
-- | Converts the given Hamlet template into 'Content', which can be used in a
-- Yesod 'Response'.
hamletToContent :: Hamlet (Route master) -> GHandler sub master Content
hamletToContent h = do
render <- getUrlRenderParams
return $ toContent $ h render
-- | Wraps the 'Content' generated by 'hamletToContent' in a 'RepHtml'.
hamletToRepHtml :: Hamlet (Route master) -> GHandler sub master RepHtml
hamletToRepHtml = fmap RepHtml . hamletToContent

View File

@ -57,10 +57,10 @@ library
, cookie >= 0.0 && < 0.1
, json-enumerator >= 0.0 && < 0.1
, json-types >= 0.1 && < 0.2
, blaze-html >= 0.3.0.4 && < 0.4
exposed-modules: Yesod.Content
Yesod.Core
Yesod.Dispatch
Yesod.Hamlet
Yesod.Handler
Yesod.Request
Yesod.Widget