diff options
author | Johannes Gerer <oss@johannesgerer.com> | 2016-10-27 02:46:07 +0200 |
---|---|---|
committer | Johannes Gerer <oss@johannesgerer.com> | 2016-10-27 02:47:19 +0200 |
commit | cdfc5a078a334f8467fb52f30c3ef544b63be4d0 (patch) | |
tree | e15bc0ccf9a78b9b066fc7d19de6124828e1a2f8 /src/Text/BlazeT/Internal.hs | |
parent | 95eb4d6a041305a27dc8fcd42ff1831d9961b7a3 (diff) | |
download | blazeT-0.0.2.tar.gz blazeT-0.0.2.tar.zst blazeT-0.0.2.zip |
fixed compilation error for GHC 7.6.3, 7.8.4, 7.10.3v0.0.2
Diffstat (limited to 'src/Text/BlazeT/Internal.hs')
-rw-r--r-- | src/Text/BlazeT/Internal.hs | 46 |
1 files changed, 23 insertions, 23 deletions
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 #-} |