From cdfc5a078a334f8467fb52f30c3ef544b63be4d0 Mon Sep 17 00:00:00 2001 From: Johannes Gerer Date: Thu, 27 Oct 2016 02:46:07 +0200 Subject: fixed compilation error for GHC 7.6.3, 7.8.4, 7.10.3 --- blazeT.cabal | 2 +- src/Text/BlazeT/Internal.hs | 46 +++++++++++++++++++------------------- src/Text/BlazeT/Renderer/Pretty.hs | 4 ++-- src/Text/BlazeT/Renderer/String.hs | 4 ++-- src/Text/BlazeT/Renderer/Text.hs | 16 ++++++------- 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 @@ Name: blazeT -Version: 0.0.1 +Version: 0.0.2 Homepage: Bug-Reports: http://github.com/johannesgerer/blazeT/issues 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 -- | run the MarkupT and return a pair consisting of the result of the -- computation and the blaze markup rendered with a blaze renderer -- like 'Text.BlazeT.Renderer.Text.renderHtml' -runWith :: Monad m => (Markup -> c) -> MarkupT m a -> m (a, c) -runWith renderer = liftM (second $ \x -> renderer $ wrapMarkup x) . runMarkupT +runWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m (a, c) +runWith renderer = liftM (second $ renderer . wrapMarkup) . runMarkupT {-# INLINE runWith #-} execMarkupT :: Monad m => MarkupT m a -> m Text.Blaze.Markup execMarkupT = liftM snd . runMarkupT {-# INLINE execMarkupT #-} -execWith :: Monad m => (Markup -> c) -> MarkupT m a -> m c +execWith :: Monad m => (MarkupI () -> c) -> MarkupT m a -> m c execWith renderer = liftM snd . runWith renderer {-# INLINE execWith #-} @@ -166,26 +166,6 @@ execMarkup :: MarkupI a -> Text.Blaze.Markup execMarkup = snd . runMarkup {-# INLINE execMarkup #-} - -instance (Monad m,Monoid a) => Monoid (MarkupT m a) where - mempty = return mempty - {-# INLINE mempty #-} - a `mappend` b = do {a' <- a; b >>= return . (mappend a')} - {-# INLINE mappend #-} - - -instance Monad m => Text.Blaze.Attributable (MarkupT m a) where - h ! a = wrapMarkupT2 (Text.Blaze.! a) h - {-# INLINE (!) #-} - -instance Monad m => Text.Blaze.Attributable (a -> MarkupT m b) where - h ! a = \x -> wrapMarkupT2 (Text.Blaze.! a) $ h x - {-# INLINE (!) #-} - -instance Monad m => IsString (MarkupT m ()) where - fromString = wrapMarkup . fromString - {-# INLINE fromString #-} - -- | Wrapper for 'Text.Blaze.Markup' is simply -- 'tell' wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m () @@ -208,6 +188,26 @@ wrapMarkup2 :: (Text.Blaze.Markup -> Text.Blaze.Markup) -> Markup2 wrapMarkup2 = wrapMarkupT2 {-# INLINE wrapMarkup2 #-} + +instance (Monad m,Monoid a) => Monoid (MarkupT m a) where + mempty = return mempty + {-# INLINE mempty #-} + a `mappend` b = do {a' <- a; b >>= return . (mappend a')} + {-# INLINE mappend #-} + + +instance Monad m => Text.Blaze.Attributable (MarkupT m a) where + h ! a = wrapMarkupT2 (Text.Blaze.! a) h + {-# INLINE (!) #-} + +instance Monad m => Text.Blaze.Attributable (a -> MarkupT m b) where + h ! a = \x -> wrapMarkupT2 (Text.Blaze.! a) $ h x + {-# INLINE (!) #-} + +instance Monad m => IsString (MarkupT m ()) where + fromString = wrapMarkup . fromString + {-# INLINE fromString #-} + unsafeByteString :: BS.ByteString -> Markup unsafeByteString = wrapMarkup . Text.Blaze.unsafeByteString {-# 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 import qualified Text.Blaze.Renderer.Pretty as BU import Text.BlazeT -renderMarkup :: MarkupM a -> String +renderMarkup :: MarkupI a -> String renderMarkup = BU.renderMarkup . execMarkup -renderHtml :: MarkupM a -> String +renderHtml :: MarkupI a -> String renderHtml = renderMarkup 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 fromChoiceString :: ChoiceString -> String -> String fromChoiceString = BU.fromChoiceString -renderMarkup :: MarkupM a -> String +renderMarkup :: MarkupI a -> String renderMarkup = BU.renderMarkup . execMarkup -renderHtml :: MarkupM a -> String +renderHtml :: MarkupI a -> String renderHtml = renderMarkup 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 import qualified Text.Blaze.Renderer.Text as BU import Text.BlazeT -renderMarkupBuilder :: MarkupM a -> B.Builder +renderMarkupBuilder :: MarkupI a -> B.Builder renderMarkupBuilder = BU.renderMarkupBuilder . execMarkup -renderHtmlBuilder :: MarkupM a -> B.Builder +renderHtmlBuilder :: MarkupI a -> B.Builder renderHtmlBuilder = renderMarkupBuilder -renderMarkup :: MarkupM a -> L.Text +renderMarkup :: MarkupI a -> L.Text renderMarkup = BU.renderMarkup . execMarkup -renderHtml :: MarkupM a -> L.Text +renderHtml :: MarkupI a -> L.Text renderHtml = renderMarkup -renderMarkupWith :: (ByteString -> Text) -> MarkupM a -> L.Text +renderMarkupWith :: (ByteString -> Text) -> MarkupI a -> L.Text renderMarkupWith g = (BH.renderHtmlWith g) . execMarkup -renderHtmlWith :: (ByteString -> Text) -> MarkupM a -> L.Text +renderHtmlWith :: (ByteString -> Text) -> MarkupI a -> L.Text renderHtmlWith = renderMarkupWith -renderMarkupBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder +renderMarkupBuilderWith :: (ByteString -> Text) -> MarkupI a -> B.Builder renderMarkupBuilderWith g = (BU.renderMarkupBuilderWith g) . execMarkup -renderHtmlBuilderWith :: (ByteString -> Text) -> MarkupM a -> B.Builder +renderHtmlBuilderWith :: (ByteString -> Text) -> MarkupI a -> B.Builder renderHtmlBuilderWith = renderHtmlBuilderWith 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 import qualified Text.Blaze.Renderer.Utf8 as BU import Text.BlazeT -renderMarkupBuilder :: MarkupM a -> B.Builder +renderMarkupBuilder :: MarkupI a -> B.Builder renderMarkupBuilder = BU.renderMarkupBuilder . execMarkup -renderHtmlBuilder :: MarkupM a -> B.Builder +renderHtmlBuilder :: MarkupI a -> B.Builder renderHtmlBuilder = renderMarkupBuilder -renderMarkup :: MarkupM a -> BL.ByteString +renderMarkup :: MarkupI a -> BL.ByteString renderMarkup = BU.renderMarkup . execMarkup -renderHtml :: MarkupM a -> BL.ByteString +renderHtml :: MarkupI a -> BL.ByteString renderHtml = renderMarkup -renderMarkupToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupM a -> IO () +renderMarkupToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupI a -> IO () renderMarkupToByteStringIO g = BU.renderMarkupToByteStringIO g . execMarkup -renderHtmlToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupM a -> IO () +renderHtmlToByteStringIO :: (BS.ByteString -> IO ()) -> MarkupI a -> IO () renderHtmlToByteStringIO = renderMarkupToByteStringIO -- cgit v1.2.3