aboutsummaryrefslogtreecommitdiffhomepage
path: root/src/Text/BlazeT/Internal.hs
diff options
context:
space:
mode:
authorJohannes Gerer <oss@johannesgerer.com>2016-10-27 02:38:57 +0200
committerJohannes Gerer <oss@johannesgerer.com>2016-10-27 02:38:57 +0200
commit73c84adf70ad57420416d0df9c8a328c6f690c18 (patch)
tree27c5a98ae9df9f5a5b2a58c612ca0b01e9223edc /src/Text/BlazeT/Internal.hs
parentfd25f72d8615ed8fd91317a6391e207a7aaba8d5 (diff)
downloadblazeT-73c84adf70ad57420416d0df9c8a328c6f690c18.tar.gz
blazeT-73c84adf70ad57420416d0df9c8a328c6f690c18.tar.zst
blazeT-73c84adf70ad57420416d0df9c8a328c6f690c18.zip
Diffstat (limited to 'src/Text/BlazeT/Internal.hs')
-rw-r--r--src/Text/BlazeT/Internal.hs44
1 files changed, 22 insertions, 22 deletions
diff --git a/src/Text/BlazeT/Internal.hs b/src/Text/BlazeT/Internal.hs
index aa56347..6e57b7c 100644
--- a/src/Text/BlazeT/Internal.hs
+++ b/src/Text/BlazeT/Internal.hs
@@ -146,7 +146,7 @@ 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'
149runWith :: Monad m => (Markup -> c) -> MarkupT m a -> m (a, c) 149runWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m (a, c)
150runWith renderer = liftM (second $ \x -> renderer $ wrapMarkup x) . runMarkupT 150runWith renderer = liftM (second $ \x -> renderer $ wrapMarkup x) . runMarkupT
151{-# INLINE runWith #-} 151{-# INLINE runWith #-}
152 152
@@ -154,7 +154,7 @@ execMarkupT :: Monad m => MarkupT m a -> m Text.Blaze.Markup
154execMarkupT = liftM snd . runMarkupT 154execMarkupT = liftM snd . runMarkupT
155{-# INLINE execMarkupT #-} 155{-# INLINE execMarkupT #-}
156 156
157execWith :: Monad m => (Markup -> c) -> MarkupT m a -> m c 157execWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m c
158execWith renderer = liftM snd . runWith renderer 158execWith renderer = liftM snd . runWith renderer
159{-# INLINE execWith #-} 159{-# INLINE execWith #-}
160 160
@@ -166,26 +166,6 @@ execMarkup :: MarkupI a -> Text.Blaze.Markup
166execMarkup = snd . runMarkup 166execMarkup = snd . runMarkup
167{-# INLINE execMarkup #-} 167{-# INLINE execMarkup #-}
168 168
169
170instance (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
177instance Monad m => Text.Blaze.Attributable (MarkupT m a) where
178 h ! a = wrapMarkupT2 (Text.Blaze.! a) h
179 {-# INLINE (!) #-}
180
181instance Monad m => Text.Blaze.Attributable (a -> MarkupT m b) where
182 h ! a = \x -> wrapMarkupT2 (Text.Blaze.! a) $ h x
183 {-# INLINE (!) #-}
184
185instance 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'
191wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m () 171wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m ()
@@ -208,6 +188,26 @@ wrapMarkup2 :: (Text.Blaze.Markup -> Text.Blaze.Markup) -> Markup2
208wrapMarkup2 = wrapMarkupT2 188wrapMarkup2 = wrapMarkupT2
209{-# INLINE wrapMarkup2 #-} 189{-# INLINE wrapMarkup2 #-}
210 190
191
192instance (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
199instance Monad m => Text.Blaze.Attributable (MarkupT m a) where
200 h ! a = wrapMarkupT2 (Text.Blaze.! a) h
201 {-# INLINE (!) #-}
202
203instance Monad m => Text.Blaze.Attributable (a -> MarkupT m b) where
204 h ! a = \x -> wrapMarkupT2 (Text.Blaze.! a) $ h x
205 {-# INLINE (!) #-}
206
207instance Monad m => IsString (MarkupT m ()) where
208 fromString = wrapMarkup . fromString
209 {-# INLINE fromString #-}
210
211unsafeByteString :: BS.ByteString -> Markup 211unsafeByteString :: BS.ByteString -> Markup
212unsafeByteString = wrapMarkup . Text.Blaze.unsafeByteString 212unsafeByteString = wrapMarkup . Text.Blaze.unsafeByteString
213{-# INLINE unsafeByteString #-} 213{-# INLINE unsafeByteString #-}