aboutsummaryrefslogtreecommitdiffhomepage
path: root/src
diff options
context:
space:
mode:
authorJohannes Gerer <oss@johannesgerer.com>2016-10-27 02:13:47 +0200
committerJohannes Gerer <oss@johannesgerer.com>2016-10-27 02:13:47 +0200
commit6b43720bb655cfade810b67fde62845776ce1ef2 (patch)
tree3433db574dc8d074354ae70232d29a9cb81ba136 /src
parent86d89e47d648770ae36dba01f7ae09d34f2ee171 (diff)
downloadblazeT-6b43720bb655cfade810b67fde62845776ce1ef2.tar.gz
blazeT-6b43720bb655cfade810b67fde62845776ce1ef2.tar.zst
blazeT-6b43720bb655cfade810b67fde62845776ce1ef2.zip
a
Diffstat (limited to 'src')
-rw-r--r--src/Text/BlazeT.hs57
-rw-r--r--src/Text/BlazeT/Html.hs17
-rw-r--r--src/Text/BlazeT/Internal.hs232
-rw-r--r--src/Text/BlazeT/Renderer/Pretty.hs1
-rw-r--r--src/Text/BlazeT/Renderer/String.hs3
-rw-r--r--src/Text/BlazeT/Renderer/Text.hs1
-rw-r--r--src/Text/BlazeT/Renderer/Utf8.hs1
7 files changed, 185 insertions, 127 deletions
diff --git a/src/Text/BlazeT.hs b/src/Text/BlazeT.hs
index b3e7c8d..ffdd89b 100644
--- a/src/Text/BlazeT.hs
+++ b/src/Text/BlazeT.hs
@@ -1,19 +1,24 @@
1{-# LANGUAGE UndecidableInstances #-} 1{-# LANGUAGE UndecidableInstances #-}
2{-# LANGUAGE FlexibleInstances #-} 2{-# LANGUAGE FlexibleInstances #-}
3{-# LANGUAGE RankNTypes #-} 3{-# LANGUAGE RankNTypes #-}
4
4module Text.BlazeT 5module Text.BlazeT
5 ( 6 (
6 -- * Important types. 7 -- * DO NOT READ THIS. READ "Text.BlazeT.Internal" INSTEAD
8 -- $descr
9
10 -- * DO NOT READ THIS
11-- -- * Important types.
7 Markup 12 Markup
8 , Tag 13 , Tag
9 , Attribute 14 , Attribute
10 , AttributeValue 15 , AttributeValue
11 16
12 -- * Creating attributes. 17-- -- * Creating attributes.
13 , dataAttribute 18 , dataAttribute
14 , customAttribute 19 , customAttribute
15 20
16 -- * Converting values to Markup. 21-- -- * Converting values to Markup.
17 , ToMarkup (..) 22 , ToMarkup (..)
18 , text 23 , text
19 , preEscapedText 24 , preEscapedText
@@ -24,19 +29,19 @@ module Text.BlazeT
24 , unsafeByteString 29 , unsafeByteString
25 , unsafeLazyByteString 30 , unsafeLazyByteString
26 31
27 -- * Comments 32-- -- * Comments
28 , textComment 33 , textComment
29 , lazyTextComment 34 , lazyTextComment
30 , stringComment 35 , stringComment
31 , unsafeByteStringComment 36 , unsafeByteStringComment
32 , unsafeLazyByteStringComment 37 , unsafeLazyByteStringComment
33 38
34 -- * Creating tags. 39-- -- * Creating tags.
35 , textTag 40 , textTag
36 , stringTag 41 , stringTag
37 42
38 -- * Converting values to attribute values. 43-- -- * Converting values to attribute values.
39 , B.ToValue (..) 44 , Text.Blaze.ToValue (..)
40 , textValue 45 , textValue
41 , preEscapedTextValue 46 , preEscapedTextValue
42 , lazyTextValue 47 , lazyTextValue
@@ -46,28 +51,28 @@ module Text.BlazeT
46 , unsafeByteStringValue 51 , unsafeByteStringValue
47 , unsafeLazyByteStringValue 52 , unsafeLazyByteStringValue
48 53
49 -- * Setting attributes 54-- -- * Setting attributes
50 , (!) 55 , (!)
51 , (!?) 56 , (!?)
52 57
53 -- * Modifiying Markup trees 58-- -- * Modifiying Markup trees
54 , contents 59 , contents
55 60
56 -- * BlazeT new stuff 61 ,MarkupT(..)
62 ,MarkupI
63 ,mapMarkupT
57 ,MarkupM 64 ,MarkupM
58 ,Markup2 65 ,Markup2
59 ,mapMarkupT
60 ,MarkupT
61 ,runMarkup
62 ,runMarkupT 66 ,runMarkupT
63 ,execMarkup 67 ,runMarkup
64 ,execMarkupT
65 ,runWith 68 ,runWith
69 ,execMarkupT
70 ,execMarkup
66 ,execWith 71 ,execWith
67 ) where 72 ) where
68 73
69import qualified Text.Blaze as B 74import qualified Text.Blaze
70import Text.BlazeT.Internal 75import Text.BlazeT.Internal as Text.BlazeT.Internal
71 76
72class ToMarkup a where 77class ToMarkup a where
73 toMarkup :: a -> Markup 78 toMarkup :: a -> Markup
@@ -76,8 +81,20 @@ class ToMarkup a where
76-- test :: (ToMarkup a, Monad m) => a -> MarkupT m () 81-- test :: (ToMarkup a, Monad m) => a -> MarkupT m ()
77-- test = toMarkup 82-- test = toMarkup
78 83
79instance B.ToMarkup a => ToMarkup a where 84instance Text.Blaze.ToMarkup a => ToMarkup a where
80 toMarkup = wrapMarkup . B.toMarkup 85 toMarkup = wrapMarkup . Text.Blaze.toMarkup
81 {-# INLINE toMarkup #-} 86 {-# INLINE toMarkup #-}
82 preEscapedToMarkup = wrapMarkup . B.preEscapedToMarkup 87 preEscapedToMarkup = wrapMarkup . Text.Blaze.preEscapedToMarkup
83 {-# INLINE preEscapedToMarkup #-} 88 {-# INLINE preEscapedToMarkup #-}
89
90
91-- $descr
92--
93-- Due due a Haddock bug, this documentation is misleading. Please
94-- read "Text.BlazeT.Internal" instead.
95--
96-- (The bug shows both @Text.Blaze.Markup@ and @Text.BlazeT.Markup@ as
97-- "Markup".)
98--
99-- Use this documentation only to see which entities are exported by
100-- this module.
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 f0c3edb..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,41 @@ 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 ,runWith
87 ,execWith
88 ) where 100 ) where
89 101
90import Control.Arrow 102import Control.Arrow
@@ -97,58 +109,63 @@ import Data.String
97import qualified Data.Text as T 109import qualified Data.Text as T
98import qualified Data.Text.Lazy as LT 110import qualified Data.Text.Lazy as LT
99import qualified Data.Text.Lazy.Builder as LTB 111import qualified Data.Text.Lazy.Builder as LTB
100import qualified Text.Blaze as B 112import qualified Text.Blaze
101import qualified Text.Blaze.Internal as B 113import qualified Text.Blaze.Internal as Text.Blaze
102 114
103newtype 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 }
104 deriving (Functor 121 deriving (Functor
105#if MIN_VERSION_base(4,8,0) 122#if MIN_VERSION_base(4,8,0)
106 ,Applicative 123 ,Applicative
107#endif 124#endif
108 ,Monad 125 ,Monad
109 ,MonadWriter B.Markup 126 ,MonadWriter Text.Blaze.Markup
110 ,MonadTrans 127 ,MonadTrans
111 ) 128 )
112 129
130type MarkupI a = MarkupT Identity a
131
113-- | 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
114-- given function 133-- given function
115mapMarkupT :: (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
116mapMarkupT f = MarkupT . mapWriterT f . fromMarkupT 135mapMarkupT f = MarkupT . mapWriterT f . fromMarkupT
117{-# INLINE mapMarkupT #-} 136{-# INLINE mapMarkupT #-}
118 137
119type MarkupM = MarkupT Identity 138type MarkupM a = forall m . Monad m => MarkupT m a
120type Markup = forall m . Monad m => MarkupT m () 139type Markup = MarkupM ()
121type Markup2 = forall m . Monad m => MarkupT m () -> MarkupT m () 140type Markup2 = forall m . Monad m => MarkupT m () -> MarkupT m ()
122 141
123runMarkupT :: MarkupT m a -> m (a,B.Markup) 142runMarkupT :: MarkupT m a -> m (a,Text.Blaze.Markup)
124runMarkupT = runWriterT . fromMarkupT 143runMarkupT = runWriterT . fromMarkupT
125{-# INLINE runMarkupT #-} 144{-# INLINE runMarkupT #-}
126 145
127-- | run the MarkupT and return a pair consisting of the result of the 146-- | run the MarkupT and return a pair consisting of the result of the
128-- computation and the blaze markup rendered with a blaze renderer 147-- computation and the blaze markup rendered with a blaze renderer
129-- like 'Text.Blaze.Renderer.Text.renderHtml' 148-- like 'Text.BlazeT.Renderer.Text.renderHtml'
130runWith :: Monad m => (MarkupM () -> c) -> MarkupT m a -> m (a, c) 149runWith :: Monad m => (Markup -> c) -> MarkupT m a -> m (a, c)
131runWith renderer = liftM (second $ renderer . wrapMarkup) . runMarkupT 150runWith renderer = liftM (second $ \x -> renderer $ wrapMarkup x) . runMarkupT
132{-# INLINE runWith #-} 151{-# INLINE runWith #-}
133 152
134execMarkupT :: Monad m => MarkupT m a -> m B.Markup 153execMarkupT :: Monad m => MarkupT m a -> m Text.Blaze.Markup
135execMarkupT = liftM snd . runMarkupT 154execMarkupT = liftM snd . runMarkupT
136{-# INLINE execMarkupT #-} 155{-# INLINE execMarkupT #-}
137 156
138execWith :: Monad m => (MarkupM () -> c) -> MarkupT m a -> m c 157execWith :: Monad m => (Markup -> c) -> MarkupT m a -> m c
139execWith renderer = liftM snd . runWith renderer 158execWith renderer = liftM snd . runWith renderer
140{-# INLINE execWith #-} 159{-# INLINE execWith #-}
141 160
142runMarkup :: MarkupM a -> (a,B.Markup) 161runMarkup :: MarkupI a -> (a, Text.Blaze.Markup)
143runMarkup = runIdentity . runMarkupT 162runMarkup = runIdentity . runMarkupT
144{-# INLINE runMarkup #-} 163{-# INLINE runMarkup #-}
145 164
146execMarkup :: MarkupM a -> B.Markup 165execMarkup :: MarkupI a -> Text.Blaze.Markup
147execMarkup = snd . runMarkup 166execMarkup = snd . runMarkup
148{-# INLINE execMarkup #-} 167{-# INLINE execMarkup #-}
149 168
150-- instance MonadTrans MarkupT where
151
152 169
153instance (Monad m,Monoid a) => Monoid (MarkupT m a) where 170instance (Monad m,Monoid a) => Monoid (MarkupT m a) where
154 mempty = return mempty 171 mempty = return mempty
@@ -157,37 +174,42 @@ instance (Monad m,Monoid a) => Monoid (MarkupT m a) where
157 {-# INLINE mappend #-} 174 {-# INLINE mappend #-}
158 175
159 176
160instance Monad m => B.Attributable (MarkupT m a) where 177instance Monad m => Text.Blaze.Attributable (MarkupT m a) where
161 h ! a = wrapMarkupT2 (B.! a) h 178 h ! a = wrapMarkupT2 (Text.Blaze.! a) h
162 {-# INLINE (!) #-} 179 {-# INLINE (!) #-}
163 180
164instance Monad m => B.Attributable (a -> MarkupT m b) where 181instance Monad m => Text.Blaze.Attributable (a -> MarkupT m b) where
165 h ! a = \x -> wrapMarkupT2 (B.! a) $ h x 182 h ! a = \x -> wrapMarkupT2 (Text.Blaze.! a) $ h x
166 {-# INLINE (!) #-} 183 {-# INLINE (!) #-}
167 184
168instance Monad m => IsString (MarkupT m ()) where 185instance Monad m => IsString (MarkupT m ()) where
169 fromString = wrapMarkup . fromString 186 fromString = wrapMarkup . fromString
170 {-# INLINE fromString #-} 187 {-# INLINE fromString #-}
171 188
172wrapMarkupT :: Monad m => B.Markup -> MarkupT m () 189-- | Wrapper for 'Text.Blaze.Markup' is simply
190-- 'tell'
191wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m ()
173wrapMarkupT = tell 192wrapMarkupT = tell
174{-# INLINE wrapMarkupT #-} 193{-# INLINE wrapMarkupT #-}
175 194
176wrapMarkup :: B.Markup -> Markup 195wrapMarkup :: Text.Blaze.Markup -> Markup
177wrapMarkup = wrapMarkupT 196wrapMarkup = wrapMarkupT
178{-# INLINE wrapMarkup #-} 197{-# INLINE wrapMarkup #-}
179 198
180wrapMarkupT2 :: 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)
181 -> MarkupT m a -> MarkupT m a 203 -> MarkupT m a -> MarkupT m a
182wrapMarkupT2 = censor 204wrapMarkupT2 = censor
183{-# INLINE wrapMarkupT2 #-} 205{-# INLINE wrapMarkupT2 #-}
184 206
185wrapMarkup2 :: (B.Markup -> B.Markup) -> Markup2 207wrapMarkup2 :: (Text.Blaze.Markup -> Text.Blaze.Markup) -> Markup2
186wrapMarkup2 = wrapMarkupT2 208wrapMarkup2 = wrapMarkupT2
187{-# INLINE wrapMarkup2 #-} 209{-# INLINE wrapMarkup2 #-}
188 210
189unsafeByteString :: BS.ByteString -> Markup 211unsafeByteString :: BS.ByteString -> Markup
190unsafeByteString = wrapMarkup . B.unsafeByteString 212unsafeByteString = wrapMarkup . Text.Blaze.unsafeByteString
191{-# INLINE unsafeByteString #-} 213{-# INLINE unsafeByteString #-}
192 214
193-- | Insert a lazy 'BL.ByteString'. See 'unsafeByteString' for reasons why this 215-- | Insert a lazy 'BL.ByteString'. See 'unsafeByteString' for reasons why this
@@ -195,39 +217,39 @@ unsafeByteString = wrapMarkup . B.unsafeByteString
195-- 217--
196unsafeLazyByteString :: BL.ByteString -- ^ Value to insert 218unsafeLazyByteString :: BL.ByteString -- ^ Value to insert
197 -> Markup -- ^ Resulting HTML fragment 219 -> Markup -- ^ Resulting HTML fragment
198unsafeLazyByteString = wrapMarkup . B.unsafeLazyByteString 220unsafeLazyByteString = wrapMarkup . Text.Blaze.unsafeLazyByteString
199{-# INLINE unsafeLazyByteString #-} 221{-# INLINE unsafeLazyByteString #-}
200 222
201external :: Monad m => MarkupT m a -> MarkupT m a 223external :: Monad m => MarkupT m a -> MarkupT m a
202external = wrapMarkupT2 B.external 224external = wrapMarkupT2 Text.Blaze.external
203{-# INLINE external #-} 225{-# INLINE external #-}
204 226
205contents :: Monad m => MarkupT m a -> MarkupT m a 227contents :: Monad m => MarkupT m a -> MarkupT m a
206contents = wrapMarkupT2 B.contents 228contents = wrapMarkupT2 Text.Blaze.contents
207{-# INLINE contents #-} 229{-# INLINE contents #-}
208 230
209customParent ::B.Tag -> Markup2 231customParent ::Text.Blaze.Tag -> Markup2
210customParent = wrapMarkup2 . B.customParent 232customParent = wrapMarkup2 . Text.Blaze.customParent
211{-# INLINE customParent #-} 233{-# INLINE customParent #-}
212 234
213customLeaf :: B.Tag -> Bool -> Markup 235customLeaf :: Text.Blaze.Tag -> Bool -> Markup
214customLeaf = fmap wrapMarkup . B.customLeaf 236customLeaf = fmap wrapMarkup . Text.Blaze.customLeaf
215{-# INLINE customLeaf #-} 237{-# INLINE customLeaf #-}
216 238
217preEscapedText :: T.Text -> Markup 239preEscapedText :: T.Text -> Markup
218preEscapedText = wrapMarkup . B.preEscapedText 240preEscapedText = wrapMarkup . Text.Blaze.preEscapedText
219{-# INLINE preEscapedText #-} 241{-# INLINE preEscapedText #-}
220 242
221preEscapedLazyText :: LT.Text -> Markup 243preEscapedLazyText :: LT.Text -> Markup
222preEscapedLazyText = wrapMarkup . B.preEscapedLazyText 244preEscapedLazyText = wrapMarkup . Text.Blaze.preEscapedLazyText
223{-# INLINE preEscapedLazyText #-} 245{-# INLINE preEscapedLazyText #-}
224 246
225preEscapedTextBuilder :: LTB.Builder -> Markup 247preEscapedTextBuilder :: LTB.Builder -> Markup
226textBuilder :: LTB.Builder -> Markup 248textBuilder :: LTB.Builder -> Markup
227 249
228#ifdef PRE_BUILDER 250#ifdef PRE_BUILDER
229preEscapedTextBuilder = wrapMarkup . B.preEscapedTextBuilder 251preEscapedTextBuilder = wrapMarkup . Text.Blaze.preEscapedTextBuilder
230textBuilder = wrapMarkup . B.textBuilder 252textBuilder = wrapMarkup . Text.Blaze.textBuilder
231{-# INLINE preEscapedTextBuilder #-} 253{-# INLINE preEscapedTextBuilder #-}
232{-# INLINE textBuilder #-} 254{-# INLINE textBuilder #-}
233#else 255#else
@@ -236,17 +258,27 @@ textBuilder = error "This function needs blaze-markup 0.7.1.0"
236#endif 258#endif
237 259
238preEscapedString :: String -> Markup 260preEscapedString :: String -> Markup
239preEscapedString = wrapMarkup . B.preEscapedString 261preEscapedString = wrapMarkup . Text.Blaze.preEscapedString
240{-# INLINE preEscapedString #-} 262{-# INLINE preEscapedString #-}
241 263
242string :: String -> Markup 264string :: String -> Markup
243string = wrapMarkup . B.string 265string = wrapMarkup . Text.Blaze.string
244{-# INLINE string #-} 266{-# INLINE string #-}
245 267
246text :: T.Text -> Markup 268text :: T.Text -> Markup
247text = wrapMarkup . B.text 269text = wrapMarkup . Text.Blaze.text
248{-# INLINE text #-} 270{-# INLINE text #-}
249 271
250lazyText :: LT.Text -> Markup 272lazyText :: LT.Text -> Markup
251lazyText = wrapMarkup . B.lazyText 273lazyText = wrapMarkup . Text.Blaze.lazyText
252{-# 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 fa8cdad..5e033ac 100644
--- a/src/Text/BlazeT/Renderer/Pretty.hs
+++ b/src/Text/BlazeT/Renderer/Pretty.hs
@@ -1,3 +1,4 @@
1{-# LANGUAGE RankNTypes #-}
1module Text.BlazeT.Renderer.Pretty 2module Text.BlazeT.Renderer.Pretty
2 ( renderMarkup 3 ( renderMarkup
3 , renderHtml 4 , renderHtml
diff --git a/src/Text/BlazeT/Renderer/String.hs b/src/Text/BlazeT/Renderer/String.hs
index 9f0e0a0..45c4786 100644
--- a/src/Text/BlazeT/Renderer/String.hs
+++ b/src/Text/BlazeT/Renderer/String.hs
@@ -1,11 +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 ) where 6 ) where
6 7
7import Control.Monad
8import Control.Monad.Identity
9import Text.Blaze.Internal (ChoiceString) 8import Text.Blaze.Internal (ChoiceString)
10import qualified Text.Blaze.Renderer.String as BU 9import qualified Text.Blaze.Renderer.String as BU
11import Text.BlazeT 10import Text.BlazeT
diff --git a/src/Text/BlazeT/Renderer/Text.hs b/src/Text/BlazeT/Renderer/Text.hs
index 991c81c..a595bd1 100644
--- a/src/Text/BlazeT/Renderer/Text.hs
+++ b/src/Text/BlazeT/Renderer/Text.hs
@@ -1,3 +1,4 @@
1{-# LANGUAGE RankNTypes #-}
1module Text.BlazeT.Renderer.Text 2module Text.BlazeT.Renderer.Text
2 ( renderMarkupBuilder 3 ( renderMarkupBuilder
3 , renderMarkupBuilderWith 4 , renderMarkupBuilderWith
diff --git a/src/Text/BlazeT/Renderer/Utf8.hs b/src/Text/BlazeT/Renderer/Utf8.hs
index b5fd656..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