aboutsummaryrefslogtreecommitdiffhomepage
path: root/src/Text/BlazeT
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/BlazeT')
-rw-r--r--src/Text/BlazeT/Html.hs17
-rw-r--r--src/Text/BlazeT/Internal.hs234
-rw-r--r--src/Text/BlazeT/Renderer/Pretty.hs11
-rw-r--r--src/Text/BlazeT/Renderer/String.hs11
-rw-r--r--src/Text/BlazeT/Renderer/Text.hs51
-rw-r--r--src/Text/BlazeT/Renderer/Utf8.hs35
6 files changed, 171 insertions, 188 deletions
diff --git a/src/Text/BlazeT/Html.hs b/src/Text/BlazeT/Html.hs
index 4a21c03..d71e90a 100644
--- a/src/Text/BlazeT/Html.hs
+++ b/src/Text/BlazeT/Html.hs
@@ -1,18 +1,21 @@
1{-# LANGUAGE RankNTypes #-} 1{-# LANGUAGE RankNTypes #-}
2module Text.BlazeT.Html 2module Text.BlazeT.Html
3 ( module Text.BlazeT 3 (
4 module Text.BlazeT
5 -- * Entities exported only by the @blazeT@ version of this module
6 ,HtmlM
7 ,HtmlT
8 -- * Entities exported also by "Text.Blaze.Html"
9 -- $descr1
4 , Html 10 , Html
5 , toHtml 11 , toHtml
6 , preEscapedToHtml 12 , preEscapedToHtml
7 -- * BlazeT new stuff
8 ,HtmlM
9 ,HtmlT
10 ) where 13 ) where
11 14
12import Text.BlazeT 15import Text.BlazeT
13 16
14type HtmlT = MarkupT 17type HtmlT = MarkupT
15type HtmlM = MarkupM 18type HtmlM a = MarkupM a
16type Html = Markup 19type Html = Markup
17 20
18toHtml ::(ToMarkup a) => a -> Html 21toHtml ::(ToMarkup a) => a -> Html
@@ -20,3 +23,7 @@ toHtml = toMarkup
20 23
21preEscapedToHtml ::(ToMarkup a) => a -> Html 24preEscapedToHtml ::(ToMarkup a) => a -> Html
22preEscapedToHtml = preEscapedToMarkup 25preEscapedToHtml = preEscapedToMarkup
26
27-- $descr1 The following is an adaptation of all "Text.Blaze.Html"
28-- exports to @blazeT@ types. For their documentation consult the
29-- "Text.Blaze.Html" documentation.
diff --git a/src/Text/BlazeT/Internal.hs b/src/Text/BlazeT/Internal.hs
index 24ef1fe..aa56347 100644
--- a/src/Text/BlazeT/Internal.hs
+++ b/src/Text/BlazeT/Internal.hs
@@ -8,23 +8,49 @@
8#endif 8#endif
9module Text.BlazeT.Internal 9module Text.BlazeT.Internal
10 ( 10 (
11 -- * Important types. 11 -- * Entities exported only by the @blazeT@ version of this module
12 B.ChoiceString (..) 12 MarkupT(..)
13 , B.StaticString (..) 13 ,MarkupI
14 , MarkupM 14 ,mapMarkupT
15 , Markup 15 -- ** Specializations for @blaze-markup@ backwards compatibility
16 , B.Tag 16 ,MarkupM
17 , B.Attribute 17 ,Markup
18 , B.AttributeValue 18 ,Markup2
19 19 -- ** Running
20 -- * Creating custom tags and attributes. 20 ,runMarkupT
21 ,runMarkup
22 ,runWith
23 -- ** Executing
24 ,execMarkupT
25 ,execMarkup
26 ,execWith
27 -- ** Wrappers
28 ,wrapMarkupT
29 ,wrapMarkupT2
30 ,wrapMarkup
31 ,wrapMarkup2
32 ,
33
34 -- * Entities exported also by "Text.Blaze.Internal"
35 -- $descr1
36
37 -- ** Important types.
38 Text.Blaze.ChoiceString (..)
39 , Text.Blaze.StaticString (..)
40 -- , MarkupM
41 -- , Markup
42 , Text.Blaze.Tag
43 , Text.Blaze.Attribute
44 , Text.Blaze.AttributeValue
45
46 -- ** Creating custom tags and attributes.
21 , customParent 47 , customParent
22 , customLeaf 48 , customLeaf
23 , B.attribute 49 , Text.Blaze.attribute
24 , B.dataAttribute 50 , Text.Blaze.dataAttribute
25 , B.customAttribute 51 , Text.Blaze.customAttribute
26 52
27 -- * Converting values to Markup. 53 -- ** Converting values to Markup.
28 , text 54 , text
29 , preEscapedText 55 , preEscapedText
30 , lazyText 56 , lazyText
@@ -36,55 +62,44 @@ module Text.BlazeT.Internal
36 , unsafeByteString 62 , unsafeByteString
37 , unsafeLazyByteString 63 , unsafeLazyByteString
38 64
39 -- * Comments 65 -- ** Comments
40 , B.textComment 66 , Text.Blaze.textComment
41 , B.lazyTextComment 67 , Text.Blaze.lazyTextComment
42 , B.stringComment 68 , Text.Blaze.stringComment
43 , B.unsafeByteStringComment 69 , Text.Blaze.unsafeByteStringComment
44 , B.unsafeLazyByteStringComment 70 , Text.Blaze.unsafeLazyByteStringComment
45 71
46 -- * Converting values to tags. 72 -- ** Converting values to tags.
47 , B.textTag 73 , Text.Blaze.textTag
48 , B.stringTag 74 , Text.Blaze.stringTag
49 75
50 -- * Converting values to attribute values. 76 -- ** Converting values to attribute values.
51 , B.textValue 77 , Text.Blaze.textValue
52 , B.preEscapedTextValue 78 , Text.Blaze.preEscapedTextValue
53 , B.lazyTextValue 79 , Text.Blaze.lazyTextValue
54 , B.preEscapedLazyTextValue 80 , Text.Blaze.preEscapedLazyTextValue
55 , B.textBuilderValue 81 , Text.Blaze.textBuilderValue
56 , B.preEscapedTextBuilderValue 82 , Text.Blaze.preEscapedTextBuilderValue
57 , B.stringValue 83 , Text.Blaze.stringValue
58 , B.preEscapedStringValue 84 , Text.Blaze.preEscapedStringValue
59 , B.unsafeByteStringValue 85 , Text.Blaze.unsafeByteStringValue
60 , B.unsafeLazyByteStringValue 86 , Text.Blaze.unsafeLazyByteStringValue
61 87
62 -- * Setting attributes 88 -- ** Setting attributes
63 , B.Attributable 89 , Text.Blaze.Attributable
64 , (B.!) 90 , (Text.Blaze.!)
65 , (B.!?) 91 , (Text.Blaze.!?)
66 92
67 -- * Modifying Markup elements 93 -- ** Modifying Markup elements
68 , contents 94 , contents
69 , external 95 , external
70 96
71 -- * Querying Markup elements 97 -- ** Querying Markup elements
72 , null 98 , null
73 99
74 -- * BlazeT new stuff
75 ,Markup2
76 ,mapMarkupT
77 ,MarkupT
78 ,runMarkup
79 ,runMarkupT
80 ,execMarkup
81 ,execMarkupT
82 ,wrapMarkup
83 ,wrapMarkupT
84 ,wrapMarkup2
85 ,wrapMarkupT2
86 ) where 100 ) where
87 101
102import Control.Arrow
88import Control.Monad.Identity 103import Control.Monad.Identity
89import Control.Monad.Trans.Class 104import Control.Monad.Trans.Class
90import Control.Monad.Writer.Strict 105import Control.Monad.Writer.Strict
@@ -94,47 +109,63 @@ import Data.String
94import qualified Data.Text as T 109import qualified Data.Text as T
95import qualified Data.Text.Lazy as LT 110import qualified Data.Text.Lazy as LT
96import qualified Data.Text.Lazy.Builder as LTB 111import qualified Data.Text.Lazy.Builder as LTB
97import qualified Text.Blaze as B 112import qualified Text.Blaze
98import qualified Text.Blaze.Internal as B 113import qualified Text.Blaze.Internal as Text.Blaze
99 114
100newtype MarkupT m a= MarkupT { fromMarkupT :: WriterT B.Markup m a } 115{- | Everything is build around the simple @newtype@ definition of the
116'MarkupT' transformer, which makes use the 'Monoid' instance of Blaze
117'Text.Blaze.Markup' and is basically a 'WriterT' writing Blaze
118'Text.Blaze.Markup':
119-}
120newtype MarkupT m a= MarkupT { fromMarkupT :: WriterT Text.Blaze.Markup m a }
101 deriving (Functor 121 deriving (Functor
102#if MIN_VERSION_base(4,8,0) 122#if MIN_VERSION_base(4,8,0)
103 ,Applicative 123 ,Applicative
104#endif 124#endif
105 ,Monad 125 ,Monad
106 ,MonadWriter B.Markup 126 ,MonadWriter Text.Blaze.Markup
107 ,MonadTrans 127 ,MonadTrans
108 ) 128 )
109 129
130type MarkupI a = MarkupT Identity a
131
110-- | Map both the return value and markup of a computation using the 132-- | Map both the return value and markup of a computation using the
111-- given function 133-- given function
112mapMarkupT :: (m (a,B.Markup) -> n (b,B.Markup)) -> MarkupT m a -> MarkupT n b 134mapMarkupT :: (m (a,Text.Blaze.Markup) -> n (b,Text.Blaze.Markup)) -> MarkupT m a -> MarkupT n b
113mapMarkupT f = MarkupT . mapWriterT f . fromMarkupT 135mapMarkupT f = MarkupT . mapWriterT f . fromMarkupT
114{-# INLINE mapMarkupT #-} 136{-# INLINE mapMarkupT #-}
115 137
116type MarkupM = MarkupT Identity 138type MarkupM a = forall m . Monad m => MarkupT m a
117type Markup = forall m . Monad m => MarkupT m () 139type Markup = MarkupM ()
118type Markup2 = forall m . Monad m => MarkupT m () -> MarkupT m () 140type Markup2 = forall m . Monad m => MarkupT m () -> MarkupT m ()
119 141
120runMarkupT :: MarkupT m a -> m (a,B.Markup) 142runMarkupT :: MarkupT m a -> m (a,Text.Blaze.Markup)
121runMarkupT = runWriterT . fromMarkupT 143runMarkupT = runWriterT . fromMarkupT
122{-# INLINE runMarkupT #-} 144{-# INLINE runMarkupT #-}
123 145
124execMarkupT :: Monad m => MarkupT m a -> m B.Markup 146-- | run the MarkupT and return a pair consisting of the result of the
147-- computation and the blaze markup rendered with a blaze renderer
148-- like 'Text.BlazeT.Renderer.Text.renderHtml'
149runWith :: Monad m => (Markup -> c) -> MarkupT m a -> m (a, c)
150runWith renderer = liftM (second $ \x -> renderer $ wrapMarkup x) . runMarkupT
151{-# INLINE runWith #-}
152
153execMarkupT :: Monad m => MarkupT m a -> m Text.Blaze.Markup
125execMarkupT = liftM snd . runMarkupT 154execMarkupT = liftM snd . runMarkupT
126{-# INLINE execMarkupT #-} 155{-# INLINE execMarkupT #-}
127 156
128runMarkup :: MarkupM a -> (a,B.Markup) 157execWith :: Monad m => (Markup -> c) -> MarkupT m a -> m c
158execWith renderer = liftM snd . runWith renderer
159{-# INLINE execWith #-}
160
161runMarkup :: MarkupI a -> (a, Text.Blaze.Markup)
129runMarkup = runIdentity . runMarkupT 162runMarkup = runIdentity . runMarkupT
130{-# INLINE runMarkup #-} 163{-# INLINE runMarkup #-}
131 164
132execMarkup :: MarkupM a -> B.Markup 165execMarkup :: MarkupI a -> Text.Blaze.Markup
133execMarkup = snd . runMarkup 166execMarkup = snd . runMarkup
134{-# INLINE execMarkup #-} 167{-# INLINE execMarkup #-}
135 168
136-- instance MonadTrans MarkupT where
137
138 169
139instance (Monad m,Monoid a) => Monoid (MarkupT m a) where 170instance (Monad m,Monoid a) => Monoid (MarkupT m a) where
140 mempty = return mempty 171 mempty = return mempty
@@ -143,37 +174,42 @@ instance (Monad m,Monoid a) => Monoid (MarkupT m a) where
143 {-# INLINE mappend #-} 174 {-# INLINE mappend #-}
144 175
145 176
146instance Monad m => B.Attributable (MarkupT m a) where 177instance Monad m => Text.Blaze.Attributable (MarkupT m a) where
147 h ! a = wrapMarkupT2 (B.! a) h 178 h ! a = wrapMarkupT2 (Text.Blaze.! a) h
148 {-# INLINE (!) #-} 179 {-# INLINE (!) #-}
149 180
150instance Monad m => B.Attributable (a -> MarkupT m b) where 181instance Monad m => Text.Blaze.Attributable (a -> MarkupT m b) where
151 h ! a = \x -> wrapMarkupT2 (B.! a) $ h x 182 h ! a = \x -> wrapMarkupT2 (Text.Blaze.! a) $ h x
152 {-# INLINE (!) #-} 183 {-# INLINE (!) #-}
153 184
154instance Monad m => IsString (MarkupT m ()) where 185instance Monad m => IsString (MarkupT m ()) where
155 fromString = wrapMarkup . fromString 186 fromString = wrapMarkup . fromString
156 {-# INLINE fromString #-} 187 {-# INLINE fromString #-}
157 188
158wrapMarkupT :: Monad m => B.Markup -> MarkupT m () 189-- | Wrapper for 'Text.Blaze.Markup' is simply
190-- 'tell'
191wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m ()
159wrapMarkupT = tell 192wrapMarkupT = tell
160{-# INLINE wrapMarkupT #-} 193{-# INLINE wrapMarkupT #-}
161 194
162wrapMarkup :: B.Markup -> Markup 195wrapMarkup :: Text.Blaze.Markup -> Markup
163wrapMarkup = wrapMarkupT 196wrapMarkup = wrapMarkupT
164{-# INLINE wrapMarkup #-} 197{-# INLINE wrapMarkup #-}
165 198
166wrapMarkupT2 :: Monad m => (B.Markup -> B.Markup) 199
200-- | Wrapper for functions that modify 'Text.Blaze.Markup' is simply
201-- 'censor'
202wrapMarkupT2 :: Monad m => (Text.Blaze.Markup -> Text.Blaze.Markup)
167 -> MarkupT m a -> MarkupT m a 203 -> MarkupT m a -> MarkupT m a
168wrapMarkupT2 = censor 204wrapMarkupT2 = censor
169{-# INLINE wrapMarkupT2 #-} 205{-# INLINE wrapMarkupT2 #-}
170 206
171wrapMarkup2 :: (B.Markup -> B.Markup) -> Markup2 207wrapMarkup2 :: (Text.Blaze.Markup -> Text.Blaze.Markup) -> Markup2
172wrapMarkup2 = wrapMarkupT2 208wrapMarkup2 = wrapMarkupT2
173{-# INLINE wrapMarkup2 #-} 209{-# INLINE wrapMarkup2 #-}
174 210
175unsafeByteString :: BS.ByteString -> Markup 211unsafeByteString :: BS.ByteString -> Markup
176unsafeByteString = wrapMarkup . B.unsafeByteString 212unsafeByteString = wrapMarkup . Text.Blaze.unsafeByteString
177{-# INLINE unsafeByteString #-} 213{-# INLINE unsafeByteString #-}
178 214
179-- | Insert a lazy 'BL.ByteString'. See 'unsafeByteString' for reasons why this 215-- | Insert a lazy 'BL.ByteString'. See 'unsafeByteString' for reasons why this
@@ -181,39 +217,39 @@ unsafeByteString = wrapMarkup . B.unsafeByteString
181-- 217--
182unsafeLazyByteString :: BL.ByteString -- ^ Value to insert 218unsafeLazyByteString :: BL.ByteString -- ^ Value to insert
183 -> Markup -- ^ Resulting HTML fragment 219 -> Markup -- ^ Resulting HTML fragment
184unsafeLazyByteString = wrapMarkup . B.unsafeLazyByteString 220unsafeLazyByteString = wrapMarkup . Text.Blaze.unsafeLazyByteString
185{-# INLINE unsafeLazyByteString #-} 221{-# INLINE unsafeLazyByteString #-}
186 222
187external :: Monad m => MarkupT m a -> MarkupT m a 223external :: Monad m => MarkupT m a -> MarkupT m a
188external = wrapMarkupT2 B.external 224external = wrapMarkupT2 Text.Blaze.external
189{-# INLINE external #-} 225{-# INLINE external #-}
190 226
191contents :: Monad m => MarkupT m a -> MarkupT m a 227contents :: Monad m => MarkupT m a -> MarkupT m a
192contents = wrapMarkupT2 B.contents 228contents = wrapMarkupT2 Text.Blaze.contents
193{-# INLINE contents #-} 229{-# INLINE contents #-}
194 230
195customParent ::B.Tag -> Markup2 231customParent ::Text.Blaze.Tag -> Markup2
196customParent = wrapMarkup2 . B.customParent 232customParent = wrapMarkup2 . Text.Blaze.customParent
197{-# INLINE customParent #-} 233{-# INLINE customParent #-}
198 234
199customLeaf :: B.Tag -> Bool -> Markup 235customLeaf :: Text.Blaze.Tag -> Bool -> Markup
200customLeaf = fmap wrapMarkup . B.customLeaf 236customLeaf = fmap wrapMarkup . Text.Blaze.customLeaf
201{-# INLINE customLeaf #-} 237{-# INLINE customLeaf #-}
202 238
203preEscapedText :: T.Text -> Markup 239preEscapedText :: T.Text -> Markup
204preEscapedText = wrapMarkup . B.preEscapedText 240preEscapedText = wrapMarkup . Text.Blaze.preEscapedText
205{-# INLINE preEscapedText #-} 241{-# INLINE preEscapedText #-}
206 242
207preEscapedLazyText :: LT.Text -> Markup 243preEscapedLazyText :: LT.Text -> Markup
208preEscapedLazyText = wrapMarkup . B.preEscapedLazyText 244preEscapedLazyText = wrapMarkup . Text.Blaze.preEscapedLazyText
209{-# INLINE preEscapedLazyText #-} 245{-# INLINE preEscapedLazyText #-}
210 246
211preEscapedTextBuilder :: LTB.Builder -> Markup 247preEscapedTextBuilder :: LTB.Builder -> Markup
212textBuilder :: LTB.Builder -> Markup 248textBuilder :: LTB.Builder -> Markup
213 249
214#ifdef PRE_BUILDER 250#ifdef PRE_BUILDER
215preEscapedTextBuilder = wrapMarkup . B.preEscapedTextBuilder 251preEscapedTextBuilder = wrapMarkup . Text.Blaze.preEscapedTextBuilder
216textBuilder = wrapMarkup . B.textBuilder 252textBuilder = wrapMarkup . Text.Blaze.textBuilder
217{-# INLINE preEscapedTextBuilder #-} 253{-# INLINE preEscapedTextBuilder #-}
218{-# INLINE textBuilder #-} 254{-# INLINE textBuilder #-}
219#else 255#else
@@ -222,17 +258,27 @@ textBuilder = error "This function needs blaze-markup 0.7.1.0"
222#endif 258#endif
223 259
224preEscapedString :: String -> Markup 260preEscapedString :: String -> Markup
225preEscapedString = wrapMarkup . B.preEscapedString 261preEscapedString = wrapMarkup . Text.Blaze.preEscapedString
226{-# INLINE preEscapedString #-} 262{-# INLINE preEscapedString #-}
227 263
228string :: String -> Markup 264string :: String -> Markup
229string = wrapMarkup . B.string 265string = wrapMarkup . Text.Blaze.string
230{-# INLINE string #-} 266{-# INLINE string #-}
231 267
232text :: T.Text -> Markup 268text :: T.Text -> Markup
233text = wrapMarkup . B.text 269text = wrapMarkup . Text.Blaze.text
234{-# INLINE text #-} 270{-# INLINE text #-}
235 271
236lazyText :: LT.Text -> Markup 272lazyText :: LT.Text -> Markup
237lazyText = wrapMarkup . B.lazyText 273lazyText = wrapMarkup . Text.Blaze.lazyText
238{-# INLINE lazyText #-} 274{-# INLINE lazyText #-}
275
276-- $descr1
277-- The following is an adaptation of all "Text.Blaze.Internal" exports to
278-- @blazeT@ types.
279--
280-- Entities that are reexported from "Text.Blaze.Internal" have the original
281-- documentation attached to them.
282--
283-- Entities that had to be adapted are tagged with \"(Adapted)\". For
284-- their documentation consult the "Text.Blaze.Internal" documentation.
diff --git a/src/Text/BlazeT/Renderer/Pretty.hs b/src/Text/BlazeT/Renderer/Pretty.hs
index 8977c94..5e033ac 100644
--- a/src/Text/BlazeT/Renderer/Pretty.hs
+++ b/src/Text/BlazeT/Renderer/Pretty.hs
@@ -1,22 +1,15 @@
1{-# LANGUAGE RankNTypes #-}
1module Text.BlazeT.Renderer.Pretty 2module Text.BlazeT.Renderer.Pretty
2 ( renderMarkup 3 ( renderMarkup
3 , renderHtml 4 , renderHtml
4 , renderMarkupT
5 , renderHtmlT
6 ) where 5 ) where
7 6
8import Control.Monad
9import Control.Monad.Identity
10import qualified Text.Blaze.Renderer.Pretty as BU 7import qualified Text.Blaze.Renderer.Pretty as BU
11import Text.BlazeT 8import Text.BlazeT
12 9
13renderMarkup :: MarkupM a -> String 10renderMarkup :: MarkupM a -> String
14renderMarkup = runIdentity . renderMarkupT 11renderMarkup = BU.renderMarkup . execMarkup
15renderMarkupT :: Monad m => MarkupT m a -> m String
16renderMarkupT = liftM BU.renderMarkup . execMarkupT
17 12
18renderHtml :: MarkupM a -> String 13renderHtml :: MarkupM a -> String
19renderHtml = renderMarkup 14renderHtml = renderMarkup
20renderHtmlT :: Monad m => MarkupT m a -> m String
21renderHtmlT = renderMarkupT
22 15
diff --git a/src/Text/BlazeT/Renderer/String.hs b/src/Text/BlazeT/Renderer/String.hs
index 0a2de8a..45c4786 100644
--- a/src/Text/BlazeT/Renderer/String.hs
+++ b/src/Text/BlazeT/Renderer/String.hs
@@ -1,13 +1,10 @@
1{-# LANGUAGE RankNTypes #-}
1module Text.BlazeT.Renderer.String 2module Text.BlazeT.Renderer.String
2 ( fromChoiceString 3 ( fromChoiceString
3 , renderMarkup 4 , renderMarkup
4 , renderHtml 5 , renderHtml
5 , renderMarkupT
6 , renderHtmlT
7 ) where 6 ) where
8 7
9import Control.Monad
10import Control.Monad.Identity
11import Text.Blaze.Internal (ChoiceString) 8import Text.Blaze.Internal (ChoiceString)
12import qualified Text.Blaze.Renderer.String as BU 9import qualified Text.Blaze.Renderer.String as BU
13import Text.BlazeT 10import Text.BlazeT
@@ -16,12 +13,8 @@ fromChoiceString :: ChoiceString -> String -> String
16fromChoiceString = BU.fromChoiceString 13fromChoiceString = BU.fromChoiceString
17 14
18renderMarkup :: MarkupM a -> String 15renderMarkup :: MarkupM a -> String
19renderMarkup = runIdentity . renderMarkupT 16renderMarkup = BU.renderMarkup . execMarkup
20renderMarkupT :: Monad m => MarkupT m a -> m String
21renderMarkupT = liftM BU.renderMarkup . execMarkupT
22 17
23renderHtml :: MarkupM a -> String 18renderHtml :: MarkupM a -> String
24renderHtml = renderMarkup 19renderHtml = renderMarkup
25renderHtmlT :: Monad m => MarkupT m a -> m String
26renderHtmlT = renderMarkupT
27 20
diff --git a/src/Text/BlazeT/Renderer/Text.hs b/src/Text/BlazeT/Renderer/Text.hs
index 31181eb..a595bd1 100644
--- a/src/Text/BlazeT/Renderer/Text.hs
+++ b/src/Text/BlazeT/Renderer/Text.hs
@@ -1,13 +1,6 @@
1{-# LANGUAGE RankNTypes #-}
1module Text.BlazeT.Renderer.Text 2module Text.BlazeT.Renderer.Text
2 ( renderMarkupBuilderT 3 ( renderMarkupBuilder
3 , renderMarkupBuilder
4 , renderMarkupBuilderWithT
5 , renderMarkupT
6 , renderMarkupWithT
7 , renderHtmlBuilderT
8 , renderHtmlBuilderWithT
9 , renderHtmlT
10 , renderHtmlWithT
11 , renderMarkupBuilderWith 4 , renderMarkupBuilderWith
12 , renderMarkup 5 , renderMarkup
13 , renderMarkupWith 6 , renderMarkupWith
@@ -17,9 +10,7 @@ module Text.BlazeT.Renderer.Text
17 , renderHtmlWith 10 , renderHtmlWith
18 ) where 11 ) where
19 12
20import Control.Monad
21import Data.ByteString (ByteString) 13import Data.ByteString (ByteString)
22import Control.Monad.Identity
23import Data.Text (Text) 14import Data.Text (Text)
24import qualified Data.Text.Lazy as L 15import qualified Data.Text.Lazy as L
25import qualified Data.Text.Lazy.Builder as B 16import qualified Data.Text.Lazy.Builder as B
@@ -28,48 +19,26 @@ import qualified Text.Blaze.Renderer.Text as BU
28import Text.BlazeT 19import Text.BlazeT
29 20
30renderMarkupBuilder :: MarkupM a -> B.Builder 21renderMarkupBuilder :: MarkupM a -> B.Builder
31renderMarkupBuilder = runIdentity . renderMarkupBuilderT 22renderMarkupBuilder = BU.renderMarkupBuilder . execMarkup
32
33renderMarkupBuilderT :: Monad m => MarkupT m a -> m B.Builder
34renderMarkupBuilderT = liftM BU.renderMarkupBuilder . execMarkupT
35 23
36renderHtmlBuilder :: MarkupM a -> B.Builder 24renderHtmlBuilder :: MarkupM a -> B.Builder
37renderHtmlBuilder = renderMarkupBuilder 25renderHtmlBuilder = renderMarkupBuilder
38 26
39renderHtmlBuilderT :: Monad m => MarkupT m a -> m B.Builder
40renderHtmlBuilderT = renderMarkupBuilderT
41
42renderMarkup :: MarkupM a -> L.Text 27renderMarkup :: MarkupM a -> L.Text
43renderMarkup = runIdentity . renderMarkupT 28renderMarkup = BU.renderMarkup . execMarkup
44renderMarkupT :: Monad m => MarkupT m a -> m L.Text
45renderMarkupT = liftM BU.renderMarkup . execMarkupT
46 29
47renderHtml :: MarkupM a -> L.Text 30renderHtml :: MarkupM a -> L.Text
48renderHtml = renderMarkup 31renderHtml = renderMarkup
49renderHtmlT :: Monad m => MarkupT m a -> m L.Text
50renderHtmlT = renderMarkupT
51
52renderMarkupWithT :: Monad m => (ByteString -> Text) -> MarkupT m a -> m L.Text
53renderMarkupWithT g = liftM (BU.renderMarkupWith g) . execMarkupT
54 32
55renderMarkupWith :: (ByteString -> Text) -> MarkupM a -> L.Text 33renderMarkupWith :: (ByteString -> Text) -> MarkupM a -> L.Text
56renderMarkupWith g = runIdentity . renderMarkupWithT g 34renderMarkupWith g = (BH.renderHtmlWith g) . execMarkup
57
58renderHtmlWithT :: Monad m => (ByteString -> Text) -> MarkupT m a -> m L.Text
59renderHtmlWithT g = liftM (BH.renderHtmlWith g) . execMarkupT
60 35
61renderHtmlWith :: (ByteString -> Text) -> MarkupM a -> L.Text 36renderHtmlWith :: (ByteString -> Text) -> MarkupM a -> L.Text
62renderHtmlWith g = runIdentity . renderHtmlWithT g 37renderHtmlWith = renderMarkupWith
63
64renderHtmlBuilderWithT :: Monad m => (ByteString -> Text) -> MarkupT m a -> m B.Builder
65renderHtmlBuilderWithT g = liftM (BH.renderHtmlBuilderWith g) . execMarkupT
66
67renderHtmlBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder
68renderHtmlBuilderWith g = runIdentity . renderHtmlBuilderWithT g
69 38
39renderMarkupBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder
40renderMarkupBuilderWith g = (BU.renderMarkupBuilderWith g) . execMarkup
70 41
71renderMarkupBuilderWithT :: Monad m => (ByteString -> Text) -> MarkupT m a -> m B.Builder 42renderHtmlBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder
72renderMarkupBuilderWithT g = liftM (BU.renderMarkupBuilderWith g) . execMarkupT 43renderHtmlBuilderWith = renderHtmlBuilderWith
73 44
74renderMarkupBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder
75renderMarkupBuilderWith g = runIdentity . renderMarkupBuilderWithT g
diff --git a/src/Text/BlazeT/Renderer/Utf8.hs b/src/Text/BlazeT/Renderer/Utf8.hs
index 292f81f..2874b68 100644
--- a/src/Text/BlazeT/Renderer/Utf8.hs
+++ b/src/Text/BlazeT/Renderer/Utf8.hs
@@ -1,3 +1,4 @@
1{-# LANGUAGE RankNTypes #-}
1{-# OPTIONS_GHC -fsimpl-tick-factor=230 #-} 2{-# OPTIONS_GHC -fsimpl-tick-factor=230 #-}
2 3
3-- the above option was not needed with 4-- the above option was not needed with
@@ -13,54 +14,28 @@ module Text.BlazeT.Renderer.Utf8
13 , renderHtmlBuilder 14 , renderHtmlBuilder
14 , renderHtml 15 , renderHtml
15 , renderHtmlToByteStringIO 16 , renderHtmlToByteStringIO
16
17 -- * new BlazeT stuff
18 , renderMarkupBuilderT
19 , renderMarkupT
20 , renderMarkupToByteStringIOT
21 , renderHtmlToByteStringIOT
22 , renderHtmlBuilderT
23 , renderHtmlT
24 ) where 17 ) where
25 18
26import qualified Blaze.ByteString.Builder as B 19import qualified Blaze.ByteString.Builder as B
27import Control.Monad
28import Control.Monad.Identity
29import qualified Data.ByteString as BS 20import qualified Data.ByteString as BS
30import qualified Data.ByteString.Lazy as BL 21import qualified Data.ByteString.Lazy as BL
31import qualified Text.Blaze.Renderer.Utf8 as BU 22import qualified Text.Blaze.Renderer.Utf8 as BU
32import Text.BlazeT 23import Text.BlazeT
33 24
34renderMarkupBuilder :: MarkupM a -> B.Builder 25renderMarkupBuilder :: MarkupM a -> B.Builder
35renderMarkupBuilder = runIdentity . renderMarkupBuilderT 26renderMarkupBuilder = BU.renderMarkupBuilder . execMarkup
36
37renderMarkupBuilderT :: Monad m => MarkupT m a -> m B.Builder
38renderMarkupBuilderT = liftM BU.renderMarkupBuilder . execMarkupT
39 27
40renderHtmlBuilder :: MarkupM a -> B.Builder 28renderHtmlBuilder :: MarkupM a -> B.Builder
41renderHtmlBuilder = renderMarkupBuilder 29renderHtmlBuilder = renderMarkupBuilder
42 30
43renderHtmlBuilderT :: Monad m => MarkupT m a -> m B.Builder
44renderHtmlBuilderT = renderMarkupBuilderT
45
46renderMarkup :: MarkupM a -> BL.ByteString 31renderMarkup :: MarkupM a -> BL.ByteString
47renderMarkup = runIdentity . renderMarkupT 32renderMarkup = BU.renderMarkup . execMarkup
48renderMarkupT :: Monad m => MarkupT m a -> m BL.ByteString
49renderMarkupT = liftM BU.renderMarkup . execMarkupT
50 33
51renderHtml :: MarkupM a -> BL.ByteString 34renderHtml :: MarkupM a -> BL.ByteString
52renderHtml = renderMarkup 35renderHtml = renderMarkup
53renderHtmlT :: Monad m => MarkupT m a -> m BL.ByteString
54renderHtmlT = renderMarkupT
55 36
56renderMarkupToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupM a -> IO () 37renderMarkupToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupM a -> IO ()
57renderMarkupToByteStringIO g = runIdentity . renderMarkupToByteStringIOT g 38renderMarkupToByteStringIO g = BU.renderMarkupToByteStringIO g . execMarkup
58renderMarkupToByteStringIOT :: Monad m => (BS.ByteString -> IO ()) ->
59 MarkupT m a -> m (IO ())
60renderMarkupToByteStringIOT g = liftM (BU.renderMarkupToByteStringIO g) . execMarkupT
61 39
62renderHtmlToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupM a -> IO () 40renderHtmlToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupM a -> IO ()
63renderHtmlToByteStringIO g = runIdentity . renderMarkupToByteStringIOT g 41renderHtmlToByteStringIO = renderMarkupToByteStringIO
64renderHtmlToByteStringIOT :: Monad m => (BS.ByteString -> IO ()) ->
65 MarkupT m a -> m (IO ())
66renderHtmlToByteStringIOT g = liftM (BU.renderMarkupToByteStringIO g) . execMarkupT