diff options
-rw-r--r-- | blazeT.cabal | 2 | ||||
-rw-r--r-- | src/Text/BlazeT/Internal.hs | 46 | ||||
-rw-r--r-- | src/Text/BlazeT/Renderer/Pretty.hs | 4 | ||||
-rw-r--r-- | src/Text/BlazeT/Renderer/String.hs | 4 | ||||
-rw-r--r-- | src/Text/BlazeT/Renderer/Text.hs | 16 | ||||
-rw-r--r-- | src/Text/BlazeT/Renderer/Utf8.hs | 12 |
6 files changed, 42 insertions, 42 deletions
diff --git a/blazeT.cabal b/blazeT.cabal index eb3907e..42e44ba 100644 --- a/blazeT.cabal +++ b/blazeT.cabal | |||
@@ -1,5 +1,5 @@ | |||
1 | Name: blazeT | 1 | Name: blazeT |
2 | Version: 0.0.1 | 2 | Version: 0.0.2 |
3 | Homepage: | 3 | Homepage: |
4 | Bug-Reports: http://github.com/johannesgerer/blazeT/issues | 4 | Bug-Reports: http://github.com/johannesgerer/blazeT/issues |
5 | License: MIT | 5 | License: MIT |
diff --git a/src/Text/BlazeT/Internal.hs b/src/Text/BlazeT/Internal.hs index aa56347..1a2fe8c 100644 --- a/src/Text/BlazeT/Internal.hs +++ b/src/Text/BlazeT/Internal.hs | |||
@@ -146,15 +146,15 @@ runMarkupT = runWriterT . fromMarkupT | |||
146 | -- | 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 |
147 | -- computation and the blaze markup rendered with a blaze renderer | 147 | -- computation and the blaze markup rendered with a blaze renderer |
148 | -- like 'Text.BlazeT.Renderer.Text.renderHtml' | 148 | -- like 'Text.BlazeT.Renderer.Text.renderHtml' |
149 | runWith :: Monad m => (Markup -> c) -> MarkupT m a -> m (a, c) | 149 | runWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m (a, c) |
150 | runWith renderer = liftM (second $ \x -> renderer $ wrapMarkup x) . runMarkupT | 150 | runWith renderer = liftM (second $ renderer . wrapMarkup) . runMarkupT |
151 | {-# INLINE runWith #-} | 151 | {-# INLINE runWith #-} |
152 | 152 | ||
153 | execMarkupT :: Monad m => MarkupT m a -> m Text.Blaze.Markup | 153 | execMarkupT :: Monad m => MarkupT m a -> m Text.Blaze.Markup |
154 | execMarkupT = liftM snd . runMarkupT | 154 | execMarkupT = liftM snd . runMarkupT |
155 | {-# INLINE execMarkupT #-} | 155 | {-# INLINE execMarkupT #-} |
156 | 156 | ||
157 | execWith :: Monad m => (Markup -> c) -> MarkupT m a -> m c | 157 | execWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m c |
158 | execWith renderer = liftM snd . runWith renderer | 158 | execWith renderer = liftM snd . runWith renderer |
159 | {-# INLINE execWith #-} | 159 | {-# INLINE execWith #-} |
160 | 160 | ||
@@ -166,26 +166,6 @@ execMarkup :: MarkupI a -> Text.Blaze.Markup | |||
166 | execMarkup = snd . runMarkup | 166 | execMarkup = snd . runMarkup |
167 | {-# INLINE execMarkup #-} | 167 | {-# INLINE execMarkup #-} |
168 | 168 | ||
169 | |||
170 | instance (Monad m,Monoid a) => Monoid (MarkupT m a) where | ||
171 | mempty = return mempty | ||
172 | {-# INLINE mempty #-} | ||
173 | a `mappend` b = do {a' <- a; b >>= return . (mappend a')} | ||
174 | {-# INLINE mappend #-} | ||
175 | |||
176 | |||
177 | instance Monad m => Text.Blaze.Attributable (MarkupT m a) where | ||
178 | h ! a = wrapMarkupT2 (Text.Blaze.! a) h | ||
179 | {-# INLINE (!) #-} | ||
180 | |||
181 | instance Monad m => Text.Blaze.Attributable (a -> MarkupT m b) where | ||
182 | h ! a = \x -> wrapMarkupT2 (Text.Blaze.! a) $ h x | ||
183 | {-# INLINE (!) #-} | ||
184 | |||
185 | instance Monad m => IsString (MarkupT m ()) where | ||
186 | fromString = wrapMarkup . fromString | ||
187 | {-# INLINE fromString #-} | ||
188 | |||
189 | -- | Wrapper for 'Text.Blaze.Markup' is simply | 169 | -- | Wrapper for 'Text.Blaze.Markup' is simply |
190 | -- 'tell' | 170 | -- 'tell' |
191 | wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m () | 171 | wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m () |
@@ -208,6 +188,26 @@ wrapMarkup2 :: (Text.Blaze.Markup -> Text.Blaze.Markup) -> Markup2 | |||
208 | wrapMarkup2 = wrapMarkupT2 | 188 | wrapMarkup2 = wrapMarkupT2 |
209 | {-# INLINE wrapMarkup2 #-} | 189 | {-# INLINE wrapMarkup2 #-} |
210 | 190 | ||
191 | |||
192 | instance (Monad m,Monoid a) => Monoid (MarkupT m a) where | ||
193 | mempty = return mempty | ||
194 | {-# INLINE mempty #-} | ||
195 | a `mappend` b = do {a' <- a; b >>= return . (mappend a')} | ||
196 | {-# INLINE mappend #-} | ||
197 | |||
198 | |||
199 | instance Monad m => Text.Blaze.Attributable (MarkupT m a) where | ||
200 | h ! a = wrapMarkupT2 (Text.Blaze.! a) h | ||
201 | {-# INLINE (!) #-} | ||
202 | |||
203 | instance Monad m => Text.Blaze.Attributable (a -> MarkupT m b) where | ||
204 | h ! a = \x -> wrapMarkupT2 (Text.Blaze.! a) $ h x | ||
205 | {-# INLINE (!) #-} | ||
206 | |||
207 | instance Monad m => IsString (MarkupT m ()) where | ||
208 | fromString = wrapMarkup . fromString | ||
209 | {-# INLINE fromString #-} | ||
210 | |||
211 | unsafeByteString :: BS.ByteString -> Markup | 211 | unsafeByteString :: BS.ByteString -> Markup |
212 | unsafeByteString = wrapMarkup . Text.Blaze.unsafeByteString | 212 | unsafeByteString = wrapMarkup . Text.Blaze.unsafeByteString |
213 | {-# INLINE unsafeByteString #-} | 213 | {-# INLINE unsafeByteString #-} |
diff --git a/src/Text/BlazeT/Renderer/Pretty.hs b/src/Text/BlazeT/Renderer/Pretty.hs index 5e033ac..4fc77b7 100644 --- a/src/Text/BlazeT/Renderer/Pretty.hs +++ b/src/Text/BlazeT/Renderer/Pretty.hs | |||
@@ -7,9 +7,9 @@ module Text.BlazeT.Renderer.Pretty | |||
7 | import qualified Text.Blaze.Renderer.Pretty as BU | 7 | import qualified Text.Blaze.Renderer.Pretty as BU |
8 | import Text.BlazeT | 8 | import Text.BlazeT |
9 | 9 | ||
10 | renderMarkup :: MarkupM a -> String | 10 | renderMarkup :: MarkupI a -> String |
11 | renderMarkup = BU.renderMarkup . execMarkup | 11 | renderMarkup = BU.renderMarkup . execMarkup |
12 | 12 | ||
13 | renderHtml :: MarkupM a -> String | 13 | renderHtml :: MarkupI a -> String |
14 | renderHtml = renderMarkup | 14 | renderHtml = renderMarkup |
15 | 15 | ||
diff --git a/src/Text/BlazeT/Renderer/String.hs b/src/Text/BlazeT/Renderer/String.hs index 45c4786..615abbc 100644 --- a/src/Text/BlazeT/Renderer/String.hs +++ b/src/Text/BlazeT/Renderer/String.hs | |||
@@ -12,9 +12,9 @@ import Text.BlazeT | |||
12 | fromChoiceString :: ChoiceString -> String -> String | 12 | fromChoiceString :: ChoiceString -> String -> String |
13 | fromChoiceString = BU.fromChoiceString | 13 | fromChoiceString = BU.fromChoiceString |
14 | 14 | ||
15 | renderMarkup :: MarkupM a -> String | 15 | renderMarkup :: MarkupI a -> String |
16 | renderMarkup = BU.renderMarkup . execMarkup | 16 | renderMarkup = BU.renderMarkup . execMarkup |
17 | 17 | ||
18 | renderHtml :: MarkupM a -> String | 18 | renderHtml :: MarkupI a -> String |
19 | renderHtml = renderMarkup | 19 | renderHtml = renderMarkup |
20 | 20 | ||
diff --git a/src/Text/BlazeT/Renderer/Text.hs b/src/Text/BlazeT/Renderer/Text.hs index a595bd1..5e5583c 100644 --- a/src/Text/BlazeT/Renderer/Text.hs +++ b/src/Text/BlazeT/Renderer/Text.hs | |||
@@ -18,27 +18,27 @@ import qualified Text.Blaze.Html.Renderer.Text as BH | |||
18 | import qualified Text.Blaze.Renderer.Text as BU | 18 | import qualified Text.Blaze.Renderer.Text as BU |
19 | import Text.BlazeT | 19 | import Text.BlazeT |
20 | 20 | ||
21 | renderMarkupBuilder :: MarkupM a -> B.Builder | 21 | renderMarkupBuilder :: MarkupI a -> B.Builder |
22 | renderMarkupBuilder = BU.renderMarkupBuilder . execMarkup | 22 | renderMarkupBuilder = BU.renderMarkupBuilder . execMarkup |
23 | 23 | ||
24 | renderHtmlBuilder :: MarkupM a -> B.Builder | 24 | renderHtmlBuilder :: MarkupI a -> B.Builder |
25 | renderHtmlBuilder = renderMarkupBuilder | 25 | renderHtmlBuilder = renderMarkupBuilder |
26 | 26 | ||
27 | renderMarkup :: MarkupM a -> L.Text | 27 | renderMarkup :: MarkupI a -> L.Text |
28 | renderMarkup = BU.renderMarkup . execMarkup | 28 | renderMarkup = BU.renderMarkup . execMarkup |
29 | 29 | ||
30 | renderHtml :: MarkupM a -> L.Text | 30 | renderHtml :: MarkupI a -> L.Text |
31 | renderHtml = renderMarkup | 31 | renderHtml = renderMarkup |
32 | 32 | ||
33 | renderMarkupWith :: (ByteString -> Text) -> MarkupM a -> L.Text | 33 | renderMarkupWith :: (ByteString -> Text) -> MarkupI a -> L.Text |
34 | renderMarkupWith g = (BH.renderHtmlWith g) . execMarkup | 34 | renderMarkupWith g = (BH.renderHtmlWith g) . execMarkup |
35 | 35 | ||
36 | renderHtmlWith :: (ByteString -> Text) -> MarkupM a -> L.Text | 36 | renderHtmlWith :: (ByteString -> Text) -> MarkupI a -> L.Text |
37 | renderHtmlWith = renderMarkupWith | 37 | renderHtmlWith = renderMarkupWith |
38 | 38 | ||
39 | renderMarkupBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder | 39 | renderMarkupBuilderWith :: (ByteString -> Text) -> MarkupI a -> B.Builder |
40 | renderMarkupBuilderWith g = (BU.renderMarkupBuilderWith g) . execMarkup | 40 | renderMarkupBuilderWith g = (BU.renderMarkupBuilderWith g) . execMarkup |
41 | 41 | ||
42 | renderHtmlBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder | 42 | renderHtmlBuilderWith :: (ByteString -> Text) -> MarkupI a -> B.Builder |
43 | renderHtmlBuilderWith = renderHtmlBuilderWith | 43 | renderHtmlBuilderWith = renderHtmlBuilderWith |
44 | 44 | ||
diff --git a/src/Text/BlazeT/Renderer/Utf8.hs b/src/Text/BlazeT/Renderer/Utf8.hs index 2874b68..3862a2b 100644 --- a/src/Text/BlazeT/Renderer/Utf8.hs +++ b/src/Text/BlazeT/Renderer/Utf8.hs | |||
@@ -22,20 +22,20 @@ import qualified Data.ByteString.Lazy as BL | |||
22 | import qualified Text.Blaze.Renderer.Utf8 as BU | 22 | import qualified Text.Blaze.Renderer.Utf8 as BU |
23 | import Text.BlazeT | 23 | import Text.BlazeT |
24 | 24 | ||
25 | renderMarkupBuilder :: MarkupM a -> B.Builder | 25 | renderMarkupBuilder :: MarkupI a -> B.Builder |
26 | renderMarkupBuilder = BU.renderMarkupBuilder . execMarkup | 26 | renderMarkupBuilder = BU.renderMarkupBuilder . execMarkup |
27 | 27 | ||
28 | renderHtmlBuilder :: MarkupM a -> B.Builder | 28 | renderHtmlBuilder :: MarkupI a -> B.Builder |
29 | renderHtmlBuilder = renderMarkupBuilder | 29 | renderHtmlBuilder = renderMarkupBuilder |
30 | 30 | ||
31 | renderMarkup :: MarkupM a -> BL.ByteString | 31 | renderMarkup :: MarkupI a -> BL.ByteString |
32 | renderMarkup = BU.renderMarkup . execMarkup | 32 | renderMarkup = BU.renderMarkup . execMarkup |
33 | 33 | ||
34 | renderHtml :: MarkupM a -> BL.ByteString | 34 | renderHtml :: MarkupI a -> BL.ByteString |
35 | renderHtml = renderMarkup | 35 | renderHtml = renderMarkup |
36 | 36 | ||
37 | renderMarkupToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupM a -> IO () | 37 | renderMarkupToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupI a -> IO () |
38 | renderMarkupToByteStringIO g = BU.renderMarkupToByteStringIO g . execMarkup | 38 | renderMarkupToByteStringIO g = BU.renderMarkupToByteStringIO g . execMarkup |
39 | 39 | ||
40 | renderHtmlToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupM a -> IO () | 40 | renderHtmlToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupI a -> IO () |
41 | renderHtmlToByteStringIO = renderMarkupToByteStringIO | 41 | renderHtmlToByteStringIO = renderMarkupToByteStringIO |