blazeT
A true monad (transformer) version of the
blaze-markup and
blaze-html
libraries:
BlazeHtml is a blazingly fast HTML combinator library for the
Haskell programming language. It embeds HTML templates in Haskell
code for optimal efficiency and composability.
— from https://jaspervdj.be/blaze/.
What’s wrong with blaze?
Blaze’s Markup
and Html
cannot be used as Monads, let alone Monad transformers.
While blaze's Markup
and Html
types have Monad
instances and can
leverage the concise do
notation, they do not satisfy the
Monad Laws.
How do Monads help? - Use Cases
The MarkupT
Monad Transformer enables us to write Markup (e.g. HTML)
templates that have access to all those Monads you cannot live without
anymore.
The first things that come to mind:
- Accessing an environment
(MonadReader)
- Logging and other diagnostic output
(MonadWriter),
IO
(e.g. for database access)
The reason for the existence of this library is its use
in Lykah, which powers my personal
website
[http://johannesgerer.com](http://johannesgerer.com/johannesgerer.com). In
Lykah, the HTML templates have access to the whole site structure (to
build things like menus or blog post lists) and automatically check,
insert and keep track of referenced pages and assets, which turns out
to be very useful functionality of a static website generator.
Usage
Integrating with your existing code
The library is intended to serve as a drop-in replacement for the
blaze-markup
and blaze-html
libraries and should be backwards
compatible:
Simply replace your module Text.Blaze.*
imports with module Text.BlazeT.*
and it should give the same results.
For usage of blaze check out
their documentation.
Unleash the monads
Text.BlazeT
exports runWith
and execWith
, which work on any
Text.BlazeT.Renderer.*
. The rendered markup will be returned within
the base monad, whose actions can be
lift
ed
into the Markup, as shown in the following example (from
here):
{-# LANGUAGE OverloadedStrings #-}
import Data.Time (getCurrentTime)
import Text.BlazeT.Html5 hiding (main)
import Text.BlazeT.Renderer.String
import Control.Monad.Trans.Class (lift)
-- Backwords compatible Blaze HTML
old :: Markup
old = do
p $ "created with blaze-html"
-- BlazeT HTML with lifted IO actions
new :: MarkupT IO ()
new = do
time <- lift getCurrentTime
p $ string $ "created with blazeT at " ++ show time
main :: IO ()
main = do
putStrLn $ renderMarkup old
putStrLn =<< execWith renderMarkup new
prints:
<p>created with blaze-html</p>
<p>created with blazeT at 2016-10-26 01:09:16.969147361 UTC</p>
Installation
-
To make it available on your system (or sandbox) use cabal install blazeT
.
-
To play around with the source, obtain by cloning this repo or use
cabal get blazet
, enter the directory and run:
cabal sandbox init #optional
cabal install
Documentation on Hackage
Implementation
... is contained
in
Text.BlazeT.Internals.
Everything is build around the simple newtype
definition of the
MarkupT
transformer, which makes use
the
Monoid instance
of Blaze.Markup
and is simply a WriterT
writing Blaze.Markup
:
newtype MarkupT m a = MarkupT { fromMarkupT :: WriterT B.Markup m a }
The old Text.Blaze.Markup
type is replaced by a rank-2 version of
the transformer:
type Markup = forall m . Monad m => MarkupT m ()
Wrappers used to lift all Blaze
entities into BlazeT
are trivially
expressible using basic WriterT
class methods. Wrapping
Blaze.Markup
is simply WriterT.tell
:
wrapMarkupT :: Monad m => B.Markup -> MarkupT m ()
wrapMarkupT = tell
Wrapping functions that modify Blaze.Markup
is simply WriterT.censor
:
wrapMarkupT2 :: Monad m => (B.Markup -> B.Markup) -> MarkupT m a -> MarkupT m a
wrapMarkupT2 = censor