doing `IO` (like database access) are the first things that come to
mind.
-The initial reason of existence of this library is its use
+The reason of existence of this library is its use
in [Lykah](http://johannesgerer.com/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) and automatically check, insert and keep
-track of referenced pages and assets, which turns out to be very
-useful for the task of static website generation.
+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.
# How to use it?
## Unleash the monads
+[Text.BlazeT](https://hackage.haskell.org/package/blazeT/docs/Text-BlazeT.html)
+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](https://hackage.haskell.org/package/transformers-0.5.2.0/docs/Control-Monad-Trans-Class.html)
+into the Markup, as shown in the following example (from
+[here](src/Readme.hs)):
+```Haskell
+{-# 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:
+
+```HTML
+<p>created with blaze-html</p>
+<p>created with blazeT at 2016-10-26 01:09:16.969147361 UTC</p>
+```
+
+# Installation
+
+1. To make it available on your system (or sandbox) use `cabal install blazeT`.
+
+2. To play around with the source, obtain by cloning this repo or use
+ `cabal get blazet`, enter the directory and run:
+
+```bash
+cabal sandbox init #optional
+cabal install
+```
+
+# Documentation on [Hackage](https://hackage.haskell.org/package/blazeT)
# Implementation
-... is located
+... is contained
in
[Text.BlazeT.Internals](https://hackage.haskell.org/package/blazeT/docs/Text-BlazeT-Internals.html).
-Everything build around the simple `newtype` definition of the
-`MarkupT` transformer, which makes use of the fact that `Blaze.Markup`
-is
-a
-[Monoid](https://hackage.haskell.org/package/base-4.7.0.2/docs/Data-Monoid.html) and
-which is basically a `WriterT` transformer writing `Blaze.Markup`:
+Everything is build around the simple `newtype` definition of the
+`MarkupT` transformer, which makes use
+the
+[Monoid](https://hackage.haskell.org/package/base-4.7.0.2/docs/Data-Monoid.html) instance
+of `Blaze.Markup` and is basically a `WriterT` writing `Blaze.Markup`:
```Haskell
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:
+
+```Haskell
+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`:
+expressible using basic `WriterT` class methods. Wrapping
+`Blaze.Markup` is simply `WriterT.tell`:
```Haskell
wrapMarkupT :: Monad m => B.Markup -> MarkupT m ()
wrapMarkupT2 = censor
```
-
import Distribution.Simple.Haddock
main = do
defaultMainWithHooks simpleUserHooks{
- haddockHook = \p l h f -> haddockHook simpleUserHooks p l h f{
+ haddockHook = \p l h flags -> haddockHook simpleUserHooks p l h flags{
haddockHoogle = Flag True,
haddockHtml = Flag True,
+ haddockProgramArgs = [("-q",["aliased"])], -- does not seam to do anything
haddockExecutables = Flag True,
haddockHscolour = Flag True
}
--- /dev/null
+{-# 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
+
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
+
module Text.BlazeT
(
- -- * Important types.
+ -- * DO NOT READ THIS. READ "Text.BlazeT.Internal" INSTEAD
+ -- $descr
+
+ -- * DO NOT READ THIS
+-- -- * Important types.
Markup
, Tag
, Attribute
, AttributeValue
- -- * Creating attributes.
+-- -- * Creating attributes.
, dataAttribute
, customAttribute
- -- * Converting values to Markup.
+-- -- * Converting values to Markup.
, ToMarkup (..)
, text
, preEscapedText
, unsafeByteString
, unsafeLazyByteString
- -- * Comments
+-- -- * Comments
, textComment
, lazyTextComment
, stringComment
, unsafeByteStringComment
, unsafeLazyByteStringComment
- -- * Creating tags.
+-- -- * Creating tags.
, textTag
, stringTag
- -- * Converting values to attribute values.
- , B.ToValue (..)
+-- -- * Converting values to attribute values.
+ , Text.Blaze.ToValue (..)
, textValue
, preEscapedTextValue
, lazyTextValue
, unsafeByteStringValue
, unsafeLazyByteStringValue
- -- * Setting attributes
+-- -- * Setting attributes
, (!)
, (!?)
- -- * Modifiying Markup trees
+-- -- * Modifiying Markup trees
, contents
- -- * BlazeT new stuff
+ ,MarkupT(..)
+ ,MarkupI
+ ,mapMarkupT
,MarkupM
,Markup2
- ,mapMarkupT
- ,MarkupT
- ,runMarkup
,runMarkupT
- ,execMarkup
+ ,runMarkup
+ ,runWith
,execMarkupT
+ ,execMarkup
+ ,execWith
) where
-import qualified Text.Blaze as B
-import Text.BlazeT.Internal
+import qualified Text.Blaze
+import Text.BlazeT.Internal as Text.BlazeT.Internal
class ToMarkup a where
toMarkup :: a -> Markup
-- test :: (ToMarkup a, Monad m) => a -> MarkupT m ()
-- test = toMarkup
-instance B.ToMarkup a => ToMarkup a where
- toMarkup = wrapMarkup . B.toMarkup
+instance Text.Blaze.ToMarkup a => ToMarkup a where
+ toMarkup = wrapMarkup . Text.Blaze.toMarkup
{-# INLINE toMarkup #-}
- preEscapedToMarkup = wrapMarkup . B.preEscapedToMarkup
+ preEscapedToMarkup = wrapMarkup . Text.Blaze.preEscapedToMarkup
{-# INLINE preEscapedToMarkup #-}
+
+
+-- $descr
+--
+-- Due due a Haddock bug, this documentation is misleading. Please
+-- read "Text.BlazeT.Internal" instead.
+--
+-- (The bug shows both @Text.Blaze.Markup@ and @Text.BlazeT.Markup@ as
+-- "Markup".)
+--
+-- Use this documentation only to see which entities are exported by
+-- this module.
{-# LANGUAGE RankNTypes #-}
module Text.BlazeT.Html
- ( module Text.BlazeT
+ (
+ module Text.BlazeT
+ -- * Entities exported only by the @blazeT@ version of this module
+ ,HtmlM
+ ,HtmlT
+ -- * Entities exported also by "Text.Blaze.Html"
+ -- $descr1
, Html
, toHtml
, preEscapedToHtml
- -- * BlazeT new stuff
- ,HtmlM
- ,HtmlT
) where
import Text.BlazeT
type HtmlT = MarkupT
-type HtmlM = MarkupM
+type HtmlM a = MarkupM a
type Html = Markup
toHtml ::(ToMarkup a) => a -> Html
preEscapedToHtml ::(ToMarkup a) => a -> Html
preEscapedToHtml = preEscapedToMarkup
+
+-- $descr1 The following is an adaptation of all "Text.Blaze.Html"
+-- exports to @blazeT@ types. For their documentation consult the
+-- "Text.Blaze.Html" documentation.
#endif
module Text.BlazeT.Internal
(
- -- * Important types.
- B.ChoiceString (..)
- , B.StaticString (..)
- , MarkupM
- , Markup
- , B.Tag
- , B.Attribute
- , B.AttributeValue
-
- -- * Creating custom tags and attributes.
+ -- * Entities exported only by the @blazeT@ version of this module
+ MarkupT(..)
+ ,MarkupI
+ ,mapMarkupT
+ -- ** Specializations for @blaze-markup@ backwards compatibility
+ ,MarkupM
+ ,Markup
+ ,Markup2
+ -- ** Running
+ ,runMarkupT
+ ,runMarkup
+ ,runWith
+ -- ** Executing
+ ,execMarkupT
+ ,execMarkup
+ ,execWith
+ -- ** Wrappers
+ ,wrapMarkupT
+ ,wrapMarkupT2
+ ,wrapMarkup
+ ,wrapMarkup2
+ ,
+
+ -- * Entities exported also by "Text.Blaze.Internal"
+ -- $descr1
+
+ -- ** Important types.
+ Text.Blaze.ChoiceString (..)
+ , Text.Blaze.StaticString (..)
+ -- , MarkupM
+ -- , Markup
+ , Text.Blaze.Tag
+ , Text.Blaze.Attribute
+ , Text.Blaze.AttributeValue
+
+ -- ** Creating custom tags and attributes.
, customParent
, customLeaf
- , B.attribute
- , B.dataAttribute
- , B.customAttribute
+ , Text.Blaze.attribute
+ , Text.Blaze.dataAttribute
+ , Text.Blaze.customAttribute
- -- * Converting values to Markup.
+ -- ** Converting values to Markup.
, text
, preEscapedText
, lazyText
, unsafeByteString
, unsafeLazyByteString
- -- * Comments
- , B.textComment
- , B.lazyTextComment
- , B.stringComment
- , B.unsafeByteStringComment
- , B.unsafeLazyByteStringComment
-
- -- * Converting values to tags.
- , B.textTag
- , B.stringTag
-
- -- * Converting values to attribute values.
- , B.textValue
- , B.preEscapedTextValue
- , B.lazyTextValue
- , B.preEscapedLazyTextValue
- , B.textBuilderValue
- , B.preEscapedTextBuilderValue
- , B.stringValue
- , B.preEscapedStringValue
- , B.unsafeByteStringValue
- , B.unsafeLazyByteStringValue
-
- -- * Setting attributes
- , B.Attributable
- , (B.!)
- , (B.!?)
-
- -- * Modifying Markup elements
+ -- ** Comments
+ , Text.Blaze.textComment
+ , Text.Blaze.lazyTextComment
+ , Text.Blaze.stringComment
+ , Text.Blaze.unsafeByteStringComment
+ , Text.Blaze.unsafeLazyByteStringComment
+
+ -- ** Converting values to tags.
+ , Text.Blaze.textTag
+ , Text.Blaze.stringTag
+
+ -- ** Converting values to attribute values.
+ , Text.Blaze.textValue
+ , Text.Blaze.preEscapedTextValue
+ , Text.Blaze.lazyTextValue
+ , Text.Blaze.preEscapedLazyTextValue
+ , Text.Blaze.textBuilderValue
+ , Text.Blaze.preEscapedTextBuilderValue
+ , Text.Blaze.stringValue
+ , Text.Blaze.preEscapedStringValue
+ , Text.Blaze.unsafeByteStringValue
+ , Text.Blaze.unsafeLazyByteStringValue
+
+ -- ** Setting attributes
+ , Text.Blaze.Attributable
+ , (Text.Blaze.!)
+ , (Text.Blaze.!?)
+
+ -- ** Modifying Markup elements
, contents
, external
- -- * Querying Markup elements
+ -- ** Querying Markup elements
, null
- -- * BlazeT new stuff
- ,Markup2
- ,mapMarkupT
- ,MarkupT
- ,runMarkup
- ,runMarkupT
- ,execMarkup
- ,execMarkupT
- ,wrapMarkup
- ,wrapMarkupT
- ,wrapMarkup2
- ,wrapMarkupT2
) where
+import Control.Arrow
import Control.Monad.Identity
import Control.Monad.Trans.Class
import Control.Monad.Writer.Strict
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Builder as LTB
-import qualified Text.Blaze as B
-import qualified Text.Blaze.Internal as B
-
-newtype MarkupT m a= MarkupT { fromMarkupT :: WriterT B.Markup m a }
+import qualified Text.Blaze
+import qualified Text.Blaze.Internal as Text.Blaze
+
+{- | Everything is build around the simple @newtype@ definition of the
+'MarkupT' transformer, which makes use the 'Monoid' instance of Blaze
+'Text.Blaze.Markup' and is basically a 'WriterT' writing Blaze
+'Text.Blaze.Markup':
+-}
+newtype MarkupT m a= MarkupT { fromMarkupT :: WriterT Text.Blaze.Markup m a }
deriving (Functor
#if MIN_VERSION_base(4,8,0)
,Applicative
#endif
,Monad
- ,MonadWriter B.Markup
+ ,MonadWriter Text.Blaze.Markup
,MonadTrans
)
+type MarkupI a = MarkupT Identity a
+
-- | Map both the return value and markup of a computation using the
-- given function
-mapMarkupT :: (m (a,B.Markup) -> n (b,B.Markup)) -> MarkupT m a -> MarkupT n b
+mapMarkupT :: (m (a,Text.Blaze.Markup) -> n (b,Text.Blaze.Markup)) -> MarkupT m a -> MarkupT n b
mapMarkupT f = MarkupT . mapWriterT f . fromMarkupT
{-# INLINE mapMarkupT #-}
-type MarkupM = MarkupT Identity
-type Markup = forall m . Monad m => MarkupT m ()
+type MarkupM a = forall m . Monad m => MarkupT m a
+type Markup = MarkupM ()
type Markup2 = forall m . Monad m => MarkupT m () -> MarkupT m ()
-runMarkupT :: MarkupT m a -> m (a,B.Markup)
+runMarkupT :: MarkupT m a -> m (a,Text.Blaze.Markup)
runMarkupT = runWriterT . fromMarkupT
{-# INLINE runMarkupT #-}
-execMarkupT :: Monad m => MarkupT m a -> m B.Markup
+-- | run the MarkupT and return a pair consisting of the result of the
+-- computation and the blaze markup rendered with a blaze renderer
+-- like 'Text.BlazeT.Renderer.Text.renderHtml'
+runWith :: Monad m => (Markup -> c) -> MarkupT m a -> m (a, c)
+runWith renderer = liftM (second $ \x -> renderer $ wrapMarkup x) . runMarkupT
+{-# INLINE runWith #-}
+
+execMarkupT :: Monad m => MarkupT m a -> m Text.Blaze.Markup
execMarkupT = liftM snd . runMarkupT
{-# INLINE execMarkupT #-}
-runMarkup :: MarkupM a -> (a,B.Markup)
+execWith :: Monad m => (Markup -> c) -> MarkupT m a -> m c
+execWith renderer = liftM snd . runWith renderer
+{-# INLINE execWith #-}
+
+runMarkup :: MarkupI a -> (a, Text.Blaze.Markup)
runMarkup = runIdentity . runMarkupT
{-# INLINE runMarkup #-}
-execMarkup :: MarkupM a -> B.Markup
+execMarkup :: MarkupI a -> Text.Blaze.Markup
execMarkup = snd . runMarkup
{-# INLINE execMarkup #-}
--- instance MonadTrans MarkupT where
-
instance (Monad m,Monoid a) => Monoid (MarkupT m a) where
mempty = return mempty
{-# INLINE mappend #-}
-instance Monad m => B.Attributable (MarkupT m a) where
- h ! a = wrapMarkupT2 (B.! a) h
+instance Monad m => Text.Blaze.Attributable (MarkupT m a) where
+ h ! a = wrapMarkupT2 (Text.Blaze.! a) h
{-# INLINE (!) #-}
-instance Monad m => B.Attributable (a -> MarkupT m b) where
- h ! a = \x -> wrapMarkupT2 (B.! a) $ h x
+instance Monad m => Text.Blaze.Attributable (a -> MarkupT m b) where
+ h ! a = \x -> wrapMarkupT2 (Text.Blaze.! a) $ h x
{-# INLINE (!) #-}
instance Monad m => IsString (MarkupT m ()) where
fromString = wrapMarkup . fromString
{-# INLINE fromString #-}
-wrapMarkupT :: Monad m => B.Markup -> MarkupT m ()
+-- | Wrapper for 'Text.Blaze.Markup' is simply
+-- 'tell'
+wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m ()
wrapMarkupT = tell
{-# INLINE wrapMarkupT #-}
-wrapMarkup :: B.Markup -> Markup
+wrapMarkup :: Text.Blaze.Markup -> Markup
wrapMarkup = wrapMarkupT
{-# INLINE wrapMarkup #-}
-wrapMarkupT2 :: Monad m => (B.Markup -> B.Markup)
+
+-- | Wrapper for functions that modify 'Text.Blaze.Markup' is simply
+-- 'censor'
+wrapMarkupT2 :: Monad m => (Text.Blaze.Markup -> Text.Blaze.Markup)
-> MarkupT m a -> MarkupT m a
wrapMarkupT2 = censor
{-# INLINE wrapMarkupT2 #-}
-wrapMarkup2 :: (B.Markup -> B.Markup) -> Markup2
+wrapMarkup2 :: (Text.Blaze.Markup -> Text.Blaze.Markup) -> Markup2
wrapMarkup2 = wrapMarkupT2
{-# INLINE wrapMarkup2 #-}
unsafeByteString :: BS.ByteString -> Markup
-unsafeByteString = wrapMarkup . B.unsafeByteString
+unsafeByteString = wrapMarkup . Text.Blaze.unsafeByteString
{-# INLINE unsafeByteString #-}
-- | Insert a lazy 'BL.ByteString'. See 'unsafeByteString' for reasons why this
--
unsafeLazyByteString :: BL.ByteString -- ^ Value to insert
-> Markup -- ^ Resulting HTML fragment
-unsafeLazyByteString = wrapMarkup . B.unsafeLazyByteString
+unsafeLazyByteString = wrapMarkup . Text.Blaze.unsafeLazyByteString
{-# INLINE unsafeLazyByteString #-}
external :: Monad m => MarkupT m a -> MarkupT m a
-external = wrapMarkupT2 B.external
+external = wrapMarkupT2 Text.Blaze.external
{-# INLINE external #-}
contents :: Monad m => MarkupT m a -> MarkupT m a
-contents = wrapMarkupT2 B.contents
+contents = wrapMarkupT2 Text.Blaze.contents
{-# INLINE contents #-}
-customParent ::B.Tag -> Markup2
-customParent = wrapMarkup2 . B.customParent
+customParent ::Text.Blaze.Tag -> Markup2
+customParent = wrapMarkup2 . Text.Blaze.customParent
{-# INLINE customParent #-}
-customLeaf :: B.Tag -> Bool -> Markup
-customLeaf = fmap wrapMarkup . B.customLeaf
+customLeaf :: Text.Blaze.Tag -> Bool -> Markup
+customLeaf = fmap wrapMarkup . Text.Blaze.customLeaf
{-# INLINE customLeaf #-}
preEscapedText :: T.Text -> Markup
-preEscapedText = wrapMarkup . B.preEscapedText
+preEscapedText = wrapMarkup . Text.Blaze.preEscapedText
{-# INLINE preEscapedText #-}
preEscapedLazyText :: LT.Text -> Markup
-preEscapedLazyText = wrapMarkup . B.preEscapedLazyText
+preEscapedLazyText = wrapMarkup . Text.Blaze.preEscapedLazyText
{-# INLINE preEscapedLazyText #-}
preEscapedTextBuilder :: LTB.Builder -> Markup
textBuilder :: LTB.Builder -> Markup
#ifdef PRE_BUILDER
-preEscapedTextBuilder = wrapMarkup . B.preEscapedTextBuilder
-textBuilder = wrapMarkup . B.textBuilder
+preEscapedTextBuilder = wrapMarkup . Text.Blaze.preEscapedTextBuilder
+textBuilder = wrapMarkup . Text.Blaze.textBuilder
{-# INLINE preEscapedTextBuilder #-}
{-# INLINE textBuilder #-}
#else
#endif
preEscapedString :: String -> Markup
-preEscapedString = wrapMarkup . B.preEscapedString
+preEscapedString = wrapMarkup . Text.Blaze.preEscapedString
{-# INLINE preEscapedString #-}
string :: String -> Markup
-string = wrapMarkup . B.string
+string = wrapMarkup . Text.Blaze.string
{-# INLINE string #-}
text :: T.Text -> Markup
-text = wrapMarkup . B.text
+text = wrapMarkup . Text.Blaze.text
{-# INLINE text #-}
lazyText :: LT.Text -> Markup
-lazyText = wrapMarkup . B.lazyText
+lazyText = wrapMarkup . Text.Blaze.lazyText
{-# INLINE lazyText #-}
+
+-- $descr1
+-- The following is an adaptation of all "Text.Blaze.Internal" exports to
+-- @blazeT@ types.
+--
+-- Entities that are reexported from "Text.Blaze.Internal" have the original
+-- documentation attached to them.
+--
+-- Entities that had to be adapted are tagged with \"(Adapted)\". For
+-- their documentation consult the "Text.Blaze.Internal" documentation.
+{-# LANGUAGE RankNTypes #-}
module Text.BlazeT.Renderer.Pretty
( renderMarkup
, renderHtml
- , renderMarkupT
- , renderHtmlT
) where
-import Control.Monad
-import Control.Monad.Identity
import qualified Text.Blaze.Renderer.Pretty as BU
import Text.BlazeT
renderMarkup :: MarkupM a -> String
-renderMarkup = runIdentity . renderMarkupT
-renderMarkupT :: Monad m => MarkupT m a -> m String
-renderMarkupT = liftM BU.renderMarkup . execMarkupT
+renderMarkup = BU.renderMarkup . execMarkup
renderHtml :: MarkupM a -> String
renderHtml = renderMarkup
-renderHtmlT :: Monad m => MarkupT m a -> m String
-renderHtmlT = renderMarkupT
+{-# LANGUAGE RankNTypes #-}
module Text.BlazeT.Renderer.String
( fromChoiceString
, renderMarkup
, renderHtml
- , renderMarkupT
- , renderHtmlT
) where
-import Control.Monad
-import Control.Monad.Identity
import Text.Blaze.Internal (ChoiceString)
import qualified Text.Blaze.Renderer.String as BU
import Text.BlazeT
fromChoiceString = BU.fromChoiceString
renderMarkup :: MarkupM a -> String
-renderMarkup = runIdentity . renderMarkupT
-renderMarkupT :: Monad m => MarkupT m a -> m String
-renderMarkupT = liftM BU.renderMarkup . execMarkupT
+renderMarkup = BU.renderMarkup . execMarkup
renderHtml :: MarkupM a -> String
renderHtml = renderMarkup
-renderHtmlT :: Monad m => MarkupT m a -> m String
-renderHtmlT = renderMarkupT
+{-# LANGUAGE RankNTypes #-}
module Text.BlazeT.Renderer.Text
- ( renderMarkupBuilderT
- , renderMarkupBuilder
- , renderMarkupBuilderWithT
- , renderMarkupT
- , renderMarkupWithT
- , renderHtmlBuilderT
- , renderHtmlBuilderWithT
- , renderHtmlT
- , renderHtmlWithT
+ ( renderMarkupBuilder
, renderMarkupBuilderWith
, renderMarkup
, renderMarkupWith
, renderHtmlWith
) where
-import Control.Monad
import Data.ByteString (ByteString)
-import Control.Monad.Identity
import Data.Text (Text)
import qualified Data.Text.Lazy as L
import qualified Data.Text.Lazy.Builder as B
import Text.BlazeT
renderMarkupBuilder :: MarkupM a -> B.Builder
-renderMarkupBuilder = runIdentity . renderMarkupBuilderT
-
-renderMarkupBuilderT :: Monad m => MarkupT m a -> m B.Builder
-renderMarkupBuilderT = liftM BU.renderMarkupBuilder . execMarkupT
+renderMarkupBuilder = BU.renderMarkupBuilder . execMarkup
renderHtmlBuilder :: MarkupM a -> B.Builder
renderHtmlBuilder = renderMarkupBuilder
-renderHtmlBuilderT :: Monad m => MarkupT m a -> m B.Builder
-renderHtmlBuilderT = renderMarkupBuilderT
-
renderMarkup :: MarkupM a -> L.Text
-renderMarkup = runIdentity . renderMarkupT
-renderMarkupT :: Monad m => MarkupT m a -> m L.Text
-renderMarkupT = liftM BU.renderMarkup . execMarkupT
+renderMarkup = BU.renderMarkup . execMarkup
renderHtml :: MarkupM a -> L.Text
renderHtml = renderMarkup
-renderHtmlT :: Monad m => MarkupT m a -> m L.Text
-renderHtmlT = renderMarkupT
-
-renderMarkupWithT :: Monad m => (ByteString -> Text) -> MarkupT m a -> m L.Text
-renderMarkupWithT g = liftM (BU.renderMarkupWith g) . execMarkupT
renderMarkupWith :: (ByteString -> Text) -> MarkupM a -> L.Text
-renderMarkupWith g = runIdentity . renderMarkupWithT g
-
-renderHtmlWithT :: Monad m => (ByteString -> Text) -> MarkupT m a -> m L.Text
-renderHtmlWithT g = liftM (BH.renderHtmlWith g) . execMarkupT
+renderMarkupWith g = (BH.renderHtmlWith g) . execMarkup
renderHtmlWith :: (ByteString -> Text) -> MarkupM a -> L.Text
-renderHtmlWith g = runIdentity . renderHtmlWithT g
-
-renderHtmlBuilderWithT :: Monad m => (ByteString -> Text) -> MarkupT m a -> m B.Builder
-renderHtmlBuilderWithT g = liftM (BH.renderHtmlBuilderWith g) . execMarkupT
-
-renderHtmlBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder
-renderHtmlBuilderWith g = runIdentity . renderHtmlBuilderWithT g
+renderHtmlWith = renderMarkupWith
+renderMarkupBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder
+renderMarkupBuilderWith g = (BU.renderMarkupBuilderWith g) . execMarkup
-renderMarkupBuilderWithT :: Monad m => (ByteString -> Text) -> MarkupT m a -> m B.Builder
-renderMarkupBuilderWithT g = liftM (BU.renderMarkupBuilderWith g) . execMarkupT
+renderHtmlBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder
+renderHtmlBuilderWith = renderHtmlBuilderWith
-renderMarkupBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder
-renderMarkupBuilderWith g = runIdentity . renderMarkupBuilderWithT g
+{-# LANGUAGE RankNTypes #-}
{-# OPTIONS_GHC -fsimpl-tick-factor=230 #-}
-- the above option was not needed with
, renderHtmlBuilder
, renderHtml
, renderHtmlToByteStringIO
-
- -- * new BlazeT stuff
- , renderMarkupBuilderT
- , renderMarkupT
- , renderMarkupToByteStringIOT
- , renderHtmlToByteStringIOT
- , renderHtmlBuilderT
- , renderHtmlT
) where
import qualified Blaze.ByteString.Builder as B
-import Control.Monad
-import Control.Monad.Identity
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
import qualified Text.Blaze.Renderer.Utf8 as BU
import Text.BlazeT
renderMarkupBuilder :: MarkupM a -> B.Builder
-renderMarkupBuilder = runIdentity . renderMarkupBuilderT
-
-renderMarkupBuilderT :: Monad m => MarkupT m a -> m B.Builder
-renderMarkupBuilderT = liftM BU.renderMarkupBuilder . execMarkupT
+renderMarkupBuilder = BU.renderMarkupBuilder . execMarkup
renderHtmlBuilder :: MarkupM a -> B.Builder
renderHtmlBuilder = renderMarkupBuilder
-renderHtmlBuilderT :: Monad m => MarkupT m a -> m B.Builder
-renderHtmlBuilderT = renderMarkupBuilderT
-
renderMarkup :: MarkupM a -> BL.ByteString
-renderMarkup = runIdentity . renderMarkupT
-renderMarkupT :: Monad m => MarkupT m a -> m BL.ByteString
-renderMarkupT = liftM BU.renderMarkup . execMarkupT
+renderMarkup = BU.renderMarkup . execMarkup
renderHtml :: MarkupM a -> BL.ByteString
renderHtml = renderMarkup
-renderHtmlT :: Monad m => MarkupT m a -> m BL.ByteString
-renderHtmlT = renderMarkupT
renderMarkupToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupM a -> IO ()
-renderMarkupToByteStringIO g = runIdentity . renderMarkupToByteStringIOT g
-renderMarkupToByteStringIOT :: Monad m => (BS.ByteString -> IO ()) ->
- MarkupT m a -> m (IO ())
-renderMarkupToByteStringIOT g = liftM (BU.renderMarkupToByteStringIO g) . execMarkupT
+renderMarkupToByteStringIO g = BU.renderMarkupToByteStringIO g . execMarkup
renderHtmlToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupM a -> IO ()
-renderHtmlToByteStringIO g = runIdentity . renderMarkupToByteStringIOT g
-renderHtmlToByteStringIOT :: Monad m => (BS.ByteString -> IO ()) ->
- MarkupT m a -> m (IO ())
-renderHtmlToByteStringIOT g = liftM (BU.renderMarkupToByteStringIO g) . execMarkupT
+renderHtmlToByteStringIO = renderMarkupToByteStringIO