Port to senza

This commit is contained in:
Chris Done 2014-05-27 17:33:22 +02:00
parent 4a8bdcaa63
commit d587a067ae
22 changed files with 55 additions and 144 deletions

View file

@ -15,7 +15,8 @@ executable hl
hs-source-dirs: src/ hs-source-dirs: src/
ghc-options: -Wall -O2 ghc-options: -Wall -O2
main-is: Main.hs main-is: Main.hs
build-depends: monad-extras, build-depends: blaze-html,
monad-extras,
filepath, filepath,
markdown, markdown,
xml-conduit, xml-conduit,
@ -30,8 +31,7 @@ executable hl
yesod-static, yesod-static,
base >= 4 && < 5, base >= 4 && < 5,
foreign-store, foreign-store,
blaze, senza,
css,
directory, directory,
pandoc, pandoc,
pandoc-types, pandoc-types,

View file

@ -1,14 +0,0 @@
-- | A prelude for when using blaze-html.
module Blaze.Prelude
(module Blaze.Attributes
,module Blaze.Senza
,module Prelude
,AttributeValue
,docTypeHtml)
where
import Blaze.Attributes hiding (style,span)
import Blaze.Senza
import Blaze
import Prelude hiding (head,div,max,span,id,min)

View file

@ -1,73 +0,0 @@
-- | Blaze without attribute operators.
module Blaze.Senza where
import Blaze (with,Html)
import qualified Blaze.Elements as E
import Prelude ()
meta :: [E.Attribute] -> Html
meta = with E.meta
headtitle :: Html -> Html
headtitle = E.title
style :: [E.Attribute] -> Html
style = with E.link
script :: [E.Attribute] -> Html -> Html
script = with E.script
div :: [E.Attribute] -> Html -> Html
div = with E.div
span :: [E.Attribute] -> Html -> Html
span = with E.span
link :: [E.Attribute] -> Html
link = with E.link
a :: [E.Attribute] -> Html -> Html
a = with E.a
h1 :: [E.Attribute] -> Html -> Html
h1 = with E.h1
h2 :: [E.Attribute] -> Html -> Html
h2 = with E.h2
h3 :: [E.Attribute] -> Html -> Html
h3 = with E.h3
h4 :: [E.Attribute] -> Html -> Html
h4 = with E.h4
h5 :: [E.Attribute] -> Html -> Html
h5 = with E.h5
head :: [E.Attribute] -> Html -> Html
head = with E.head
body :: [E.Attribute] -> Html -> Html
body = with E.body
nav :: [E.Attribute] -> Html -> Html
nav = with E.nav
ul :: [E.Attribute] -> Html -> Html
ul = with E.ul
ol :: [E.Attribute] -> Html -> Html
ol = with E.ol
li :: [E.Attribute] -> Html -> Html
li = with E.li
p :: [E.Attribute] -> Html -> Html
p = with E.p
pre :: [E.Attribute] -> Html -> Html
pre = with E.pre
code :: [E.Attribute] -> Html -> Html
code = with E.code

View file

@ -13,7 +13,7 @@ import HL.Foundation as C (Route(..),App(..))
import Control.Monad.Extra import Control.Monad.Extra
import Data.Text as C (Text) import Data.Text as C (Text)
import Yesod as C import Yesod as C
import Yesod.Blaze as C import Yesod.Senza as C
-- | Controller type. -- | Controller type.
type C = Handler type C = Handler

View file

@ -9,4 +9,4 @@ import HL.V.Community
-- | Community controller. -- | Community controller.
getCommunityR :: C Html getCommunityR :: C Html
getCommunityR = blaze communityV getCommunityR = senza communityV

View file

@ -10,4 +10,4 @@ import HL.V.Documentation
-- | Documentation controller. -- | Documentation controller.
getDocumentationR :: C Html getDocumentationR :: C Html
getDocumentationR = getDocumentationR =
blaze documentationV senza documentationV

View file

@ -10,4 +10,4 @@ import HL.C
-- | Home controller. -- | Home controller.
getHomeR :: C Html getHomeR :: C Html
getHomeR = getHomeR =
markdownPage [HomeR] "Home" "home.md" markdownPage [] "Home" "home.md"

View file

@ -12,4 +12,4 @@ import HL.V.Markdown
markdownPage :: [Route App] -> Text -> FilePath -> C Html markdownPage :: [Route App] -> Text -> FilePath -> C Html
markdownPage crumbs t name = markdownPage crumbs t name =
do content <- io (getMarkdown name) do content <- io (getMarkdown name)
blaze (markdownV crumbs t content) senza (markdownV crumbs t content)

View file

@ -12,4 +12,4 @@ import HL.V.News
getNewsR :: C Html getNewsR :: C Html
getNewsR = getNewsR =
do html <- io getHaskellNews do html <- io getHaskellNews
blaze (newsV html) senza (newsV html)

View file

@ -10,7 +10,7 @@ import HL.M.Report
getReportR :: Int -> FilePath -> C Html getReportR :: Int -> FilePath -> C Html
getReportR year page = getReportR year page =
do content <- io (getReportPage year page) do content <- io (getReportPage year page)
blaze (reportV year page content) senza (reportV year page content)
-- | Default page to go to for the given year. -- | Default page to go to for the given year.
getReportHomeR :: Int -> C Html getReportHomeR :: Int -> C Html

View file

@ -22,4 +22,4 @@ getWikiR :: Text -> C Html
getWikiR name = getWikiR name =
do url <- getUrlRender do url <- getUrlRender
result <- io (getWikiPage name) result <- io (getWikiPage name)
blaze (wikiV url result) senza (wikiV url result)

View file

@ -7,8 +7,9 @@ module HL.V
import HL.Foundation as V (Route(..),App) import HL.Foundation as V (Route(..),App)
import HL.Static as V import HL.Static as V
import Blaze.Bootstrap as V
import Blaze.Prelude as V
import Data.Text as V (Text)
import Yesod.Blaze as V
import Control.Monad as V import Control.Monad as V
import Data.Text as V (Text)
import Prelude as V hiding (span,head,min,max,id,div)
import Senza as V
import Senza.Bootstrap as V
import Yesod.Senza as V

View file

@ -9,7 +9,7 @@ import HL.V hiding (list)
import HL.V.Template import HL.V.Template
-- | Community view. -- | Community view.
communityV :: Blaze App communityV :: FromSenza App
communityV = communityV =
template template
[CommunityR] [CommunityR]

View file

@ -10,7 +10,7 @@ import HL.V
import HL.V.Template import HL.V.Template
-- | Documentation view. -- | Documentation view.
documentationV :: Blaze App documentationV :: FromSenza App
documentationV = documentationV =
template template
[DocumentationR] [DocumentationR]

View file

@ -8,7 +8,7 @@ import HL.V
import HL.V.Template import HL.V.Template
-- | Render a simple page. -- | Render a simple page.
markdownV :: [Route App] -> Text -> Html -> Blaze App markdownV :: [Route App] -> Text -> Html -> FromSenza App
markdownV routes t inner = markdownV routes t inner =
template template
routes routes

View file

@ -9,7 +9,7 @@ import HL.V
import HL.V.Template import HL.V.Template
-- | News view. -- | News view.
newsV :: Html -> Blaze App newsV :: Html -> FromSenza App
newsV inner = newsV inner =
template template
[NewsR] [NewsR]

View file

@ -9,7 +9,7 @@ import HL.V
import HL.V.Template import HL.V.Template
-- | Report view. -- | Report view.
reportV :: Int -> FilePath -> Html -> Blaze App reportV :: Int -> FilePath -> Html -> FromSenza App
reportV year _ inner = reportV year _ inner =
template template
[DocumentationR [DocumentationR

View file

@ -6,19 +6,18 @@
module HL.V.Template where module HL.V.Template where
import HL.V hiding (item) import HL.V hiding (item)
import qualified Blaze.Elements as E import Data.Maybe
import Data.Maybe import Data.Monoid
import Data.Monoid import Data.Text (pack)
import Data.Text (pack)
-- | Render a template. -- | Render a template.
template template
:: [Route App] :: [Route App]
-> Text -> Text
-> ((Route App -> AttributeValue) -> Html) -> ((Route App -> AttributeValue) -> Html)
-> Blaze App -> FromSenza App
template crumbs ptitle inner url = template crumbs ptitle inner url =
docTypeHtml docTypeHtml
(do head [] (do head []
@ -57,7 +56,7 @@ template crumbs ptitle inner url =
,href (url route)]) ,href (url route)])
-- | Main navigation. -- | Main navigation.
navigation :: Maybe (Route App) -> Blaze App navigation :: Maybe (Route App) -> FromSenza App
navigation cur url = navigation cur url =
nav [class_ "navbar navbar-default"] nav [class_ "navbar navbar-default"]
(div [class_ "container"] (div [class_ "container"]
@ -88,7 +87,7 @@ navigation cur url =
"Haskell")) "Haskell"))
-- | Breadcrumb. -- | Breadcrumb.
bread :: (Route App -> E.AttributeValue) -> [Route App] -> Html bread :: (Route App -> AttributeValue) -> [Route App] -> Html
bread url crumbs = bread url crumbs =
ol [class_ "breadcrumb"] ol [class_ "breadcrumb"]
(forM_ crumbs (forM_ crumbs

View file

@ -19,7 +19,7 @@ import Text.Pandoc.Walk
import Text.Pandoc.Writers.HTML import Text.Pandoc.Writers.HTML
-- | Wiki view. -- | Wiki view.
wikiV :: (Route App -> Text) -> Either Text (Text,Pandoc) -> Blaze App wikiV :: (Route App -> Text) -> Either Text (Text,Pandoc) -> FromSenza App
wikiV urlr result = wikiV urlr result =
template template
([WikiHomeR] ++ ([WikiHomeR] ++

View file

@ -2,14 +2,12 @@
module Main where module Main where
import HL.Foundation import HL.Dispatch ()
import HL.Dispatch () import HL.Foundation
import Control.Concurrent.Chan import Control.Concurrent.Chan
import qualified Data.Text.Lazy.IO as L import Yesod
import System.Directory import Yesod.Static
import Yesod
import Yesod.Static
-- | Main entry point. -- | Main entry point.
main :: IO () main :: IO ()

View file

@ -1,21 +0,0 @@
-- | Useful utilities for using blaze-html with Yesod.
module Yesod.Blaze
(module Yesod.Blaze
,module Yesod)
where
import Yesod hiding (object)
import Blaze
-- | A blaze generator.
type Blaze a =
(Route a -> AttributeValue) ->
Html
-- | Output some blaze, passes a URL renderer to the continuation.
blaze :: MonadHandler m => Blaze (HandlerSite m) -> m Html
blaze cont =
do render <- getUrlRender
return
(cont (toValue . render))

21
src/Yesod/Senza.hs Normal file
View file

@ -0,0 +1,21 @@
-- | Useful utilities for using Senza with Yesod.
module Yesod.Senza
(module Yesod.Senza
,module Yesod)
where
import Senza
import Yesod
-- | A senza generator.
type FromSenza a =
(Route a -> AttributeValue) ->
Senza
-- | Output some senza, passes a URL renderer to the continuation.
senza :: MonadHandler m => FromSenza (HandlerSite m) -> m Html
senza cont =
do render <- getUrlRender
return
(cont (toValue . render))