]> git.immae.eu Git - github/fretlink/blazeT.git/blobdiff - src/Text/BlazeT/Internal.hs
Docs
[github/fretlink/blazeT.git] / src / Text / BlazeT / Internal.hs
index 24ef1fe342429a12a53df68717c2c07bc2694237..aa5634729f67c9e8c27cca2e6cfb5a3f4526c437 100644 (file)
@@ -8,23 +8,49 @@
 #endif
 module Text.BlazeT.Internal
     (
-      -- * Important types.
-      B.ChoiceString (..)
-    , B.StaticString (..)
-    , MarkupM
-    , Markup
-    , B.Tag
-    , B.Attribute
-    , B.AttributeValue
-
-      -- * Creating custom tags and attributes.
+    -- * Entities exported only by the @blazeT@ version of this module
+    MarkupT(..)
+    ,MarkupI
+    ,mapMarkupT
+    -- ** Specializations for @blaze-markup@ backwards compatibility
+    ,MarkupM
+    ,Markup
+    ,Markup2
+    -- ** Running
+    ,runMarkupT
+    ,runMarkup
+    ,runWith
+    -- ** Executing
+    ,execMarkupT
+    ,execMarkup
+    ,execWith
+    -- ** Wrappers
+    ,wrapMarkupT
+    ,wrapMarkupT2
+    ,wrapMarkup
+    ,wrapMarkup2
+    ,
+    
+    -- * Entities exported also by "Text.Blaze.Internal"
+    -- $descr1
+    
+      -- ** Important types.
+      Text.Blaze.ChoiceString (..)
+    , Text.Blaze.StaticString (..)
+    -- , MarkupM
+    -- , Markup
+    , Text.Blaze.Tag
+    , Text.Blaze.Attribute
+    , Text.Blaze.AttributeValue
+
+      -- ** Creating custom tags and attributes.
     , customParent
     , customLeaf
-    , B.attribute
-    , B.dataAttribute
-    , B.customAttribute
+    , Text.Blaze.attribute
+    , Text.Blaze.dataAttribute
+    , Text.Blaze.customAttribute
 
-      -- * Converting values to Markup.
+      -- ** Converting values to Markup.
     , text
     , preEscapedText
     , lazyText
@@ -36,55 +62,44 @@ module Text.BlazeT.Internal
     , unsafeByteString
     , unsafeLazyByteString
 
-      -- * Comments
-    , B.textComment
-    , B.lazyTextComment
-    , B.stringComment
-    , B.unsafeByteStringComment
-    , B.unsafeLazyByteStringComment
-
-      -- * Converting values to tags.
-    , B.textTag
-    , B.stringTag
-
-      -- * Converting values to attribute values.
-    , B.textValue
-    , B.preEscapedTextValue
-    , B.lazyTextValue
-    , B.preEscapedLazyTextValue
-    , B.textBuilderValue
-    , B.preEscapedTextBuilderValue
-    , B.stringValue
-    , B.preEscapedStringValue
-    , B.unsafeByteStringValue
-    , B.unsafeLazyByteStringValue
-
-      -- * Setting attributes
-    , B.Attributable
-    , (B.!)
-    , (B.!?)
-
-      -- * Modifying Markup elements
+      -- ** Comments
+    , Text.Blaze.textComment
+    , Text.Blaze.lazyTextComment
+    , Text.Blaze.stringComment
+    , Text.Blaze.unsafeByteStringComment
+    , Text.Blaze.unsafeLazyByteStringComment
+
+      -- ** Converting values to tags.
+    , Text.Blaze.textTag
+    , Text.Blaze.stringTag
+
+      -- ** Converting values to attribute values.
+    , Text.Blaze.textValue
+    , Text.Blaze.preEscapedTextValue
+    , Text.Blaze.lazyTextValue
+    , Text.Blaze.preEscapedLazyTextValue
+    , Text.Blaze.textBuilderValue
+    , Text.Blaze.preEscapedTextBuilderValue
+    , Text.Blaze.stringValue
+    , Text.Blaze.preEscapedStringValue
+    , Text.Blaze.unsafeByteStringValue
+    , Text.Blaze.unsafeLazyByteStringValue
+
+      -- ** Setting attributes
+    , Text.Blaze.Attributable
+    , (Text.Blaze.!)
+    , (Text.Blaze.!?)
+
+      -- ** Modifying Markup elements
     , contents
     , external
 
-      -- * Querying Markup elements
+      -- ** Querying Markup elements
     , null
 
-    -- * BlazeT new stuff
-    ,Markup2
-    ,mapMarkupT
-    ,MarkupT
-    ,runMarkup
-    ,runMarkupT
-    ,execMarkup
-    ,execMarkupT
-    ,wrapMarkup
-    ,wrapMarkupT
-    ,wrapMarkup2
-    ,wrapMarkupT2
   ) where
 
+import           Control.Arrow
 import           Control.Monad.Identity
 import           Control.Monad.Trans.Class
 import           Control.Monad.Writer.Strict
@@ -94,47 +109,63 @@ import           Data.String
 import qualified Data.Text as T
 import qualified Data.Text.Lazy as LT
 import qualified Data.Text.Lazy.Builder as LTB
-import qualified Text.Blaze as B
-import qualified Text.Blaze.Internal as B
-
-newtype MarkupT m a= MarkupT { fromMarkupT :: WriterT B.Markup m a }
+import qualified Text.Blaze
+import qualified Text.Blaze.Internal as Text.Blaze
+
+{- | Everything is build around the simple @newtype@ definition of the
+'MarkupT' transformer, which makes use the 'Monoid' instance of Blaze
+'Text.Blaze.Markup' and is basically a 'WriterT' writing Blaze
+'Text.Blaze.Markup':
+-}
+newtype MarkupT m a= MarkupT { fromMarkupT :: WriterT Text.Blaze.Markup m a }
                      deriving (Functor
 #if MIN_VERSION_base(4,8,0)
                               ,Applicative
 #endif
                               ,Monad
-                              ,MonadWriter B.Markup
+                              ,MonadWriter Text.Blaze.Markup
                               ,MonadTrans
                               )
 
+type MarkupI a = MarkupT Identity a
+
 -- | Map both the return value and markup of a computation using the
 -- given function
-mapMarkupT :: (m (a,B.Markup) -> n (b,B.Markup)) -> MarkupT m a -> MarkupT n b
+mapMarkupT :: (m (a,Text.Blaze.Markup) -> n (b,Text.Blaze.Markup)) -> MarkupT m a -> MarkupT n b
 mapMarkupT f = MarkupT . mapWriterT f . fromMarkupT
 {-# INLINE mapMarkupT #-}
 
-type MarkupM = MarkupT Identity
-type Markup = forall m . Monad m => MarkupT m ()
+type MarkupM a = forall m . Monad m => MarkupT m a
+type Markup = MarkupM ()
 type Markup2 = forall m . Monad m => MarkupT m () -> MarkupT m ()
 
-runMarkupT :: MarkupT m a -> m (a,B.Markup)
+runMarkupT :: MarkupT m a -> m (a,Text.Blaze.Markup)
 runMarkupT = runWriterT . fromMarkupT
 {-# INLINE runMarkupT #-}
 
-execMarkupT :: Monad m => MarkupT m a -> m B.Markup
+-- | 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  
+{-# INLINE runWith #-}
+  
+execMarkupT :: Monad m => MarkupT m a -> m Text.Blaze.Markup
 execMarkupT = liftM snd . runMarkupT
 {-# INLINE execMarkupT #-}
 
-runMarkup :: MarkupM a -> (a,B.Markup)
+execWith :: Monad m => (Markup -> c) -> MarkupT m a -> m c
+execWith renderer = liftM snd . runWith renderer
+{-# INLINE execWith #-}
+
+runMarkup :: MarkupI a -> (a, Text.Blaze.Markup)
 runMarkup = runIdentity . runMarkupT
 {-# INLINE runMarkup #-}
 
-execMarkup :: MarkupM a -> B.Markup
+execMarkup :: MarkupI a -> Text.Blaze.Markup
 execMarkup = snd . runMarkup
 {-# INLINE execMarkup #-}
 
--- instance MonadTrans MarkupT where
-
 
 instance (Monad m,Monoid a) => Monoid (MarkupT m a) where
   mempty = return mempty
@@ -143,37 +174,42 @@ instance (Monad m,Monoid a) => Monoid (MarkupT m a) where
   {-# INLINE mappend #-}
 
 
-instance Monad m => B.Attributable (MarkupT m a) where
-  h ! a = wrapMarkupT2 (B.! a) h
+instance Monad m => Text.Blaze.Attributable (MarkupT m a) where
+  h ! a = wrapMarkupT2 (Text.Blaze.! a) h
   {-# INLINE (!) #-}
 
-instance Monad m => B.Attributable (a -> MarkupT m b) where
-  h ! a = \x -> wrapMarkupT2 (B.! a) $ h x
+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 #-}
 
-wrapMarkupT :: Monad m => B.Markup -> MarkupT m ()
+-- | Wrapper for 'Text.Blaze.Markup' is simply
+-- 'tell'
+wrapMarkupT :: Monad m => Text.Blaze.Markup -> MarkupT m ()
 wrapMarkupT = tell
 {-# INLINE wrapMarkupT #-}
 
-wrapMarkup :: B.Markup -> Markup
+wrapMarkup :: Text.Blaze.Markup -> Markup
 wrapMarkup = wrapMarkupT
 {-# INLINE wrapMarkup #-}
 
-wrapMarkupT2 ::  Monad m => (B.Markup -> B.Markup)
+
+-- | Wrapper for functions that modify 'Text.Blaze.Markup' is simply
+-- 'censor'
+wrapMarkupT2 ::  Monad m => (Text.Blaze.Markup -> Text.Blaze.Markup)
                  -> MarkupT m a -> MarkupT m a
 wrapMarkupT2 = censor
 {-# INLINE wrapMarkupT2 #-}
 
-wrapMarkup2 :: (B.Markup -> B.Markup) -> Markup2
+wrapMarkup2 :: (Text.Blaze.Markup -> Text.Blaze.Markup) -> Markup2
 wrapMarkup2 = wrapMarkupT2
 {-# INLINE wrapMarkup2 #-}
 
 unsafeByteString :: BS.ByteString -> Markup
-unsafeByteString = wrapMarkup . B.unsafeByteString
+unsafeByteString = wrapMarkup . Text.Blaze.unsafeByteString
 {-# INLINE unsafeByteString #-}
 
 -- | Insert a lazy 'BL.ByteString'. See 'unsafeByteString' for reasons why this
@@ -181,39 +217,39 @@ unsafeByteString = wrapMarkup . B.unsafeByteString
 --
 unsafeLazyByteString :: BL.ByteString  -- ^ Value to insert
                      -> Markup         -- ^ Resulting HTML fragment
-unsafeLazyByteString = wrapMarkup . B.unsafeLazyByteString
+unsafeLazyByteString = wrapMarkup . Text.Blaze.unsafeLazyByteString
 {-# INLINE unsafeLazyByteString #-}
 
 external :: Monad m => MarkupT m a -> MarkupT m a
-external = wrapMarkupT2  B.external
+external = wrapMarkupT2  Text.Blaze.external
 {-# INLINE external #-}
 
 contents :: Monad m => MarkupT m a -> MarkupT m a
-contents = wrapMarkupT2  B.contents
+contents = wrapMarkupT2  Text.Blaze.contents
 {-# INLINE contents #-}
 
-customParent ::B.Tag -> Markup2
-customParent = wrapMarkup2 . B.customParent
+customParent ::Text.Blaze.Tag -> Markup2
+customParent = wrapMarkup2 . Text.Blaze.customParent
 {-# INLINE customParent #-}
 
-customLeaf :: B.Tag -> Bool -> Markup
-customLeaf = fmap wrapMarkup . B.customLeaf
+customLeaf :: Text.Blaze.Tag -> Bool -> Markup
+customLeaf = fmap wrapMarkup . Text.Blaze.customLeaf
 {-# INLINE customLeaf #-}
 
 preEscapedText :: T.Text -> Markup
-preEscapedText = wrapMarkup . B.preEscapedText
+preEscapedText = wrapMarkup . Text.Blaze.preEscapedText
 {-# INLINE preEscapedText #-}
 
 preEscapedLazyText :: LT.Text -> Markup
-preEscapedLazyText = wrapMarkup . B.preEscapedLazyText
+preEscapedLazyText = wrapMarkup . Text.Blaze.preEscapedLazyText
 {-# INLINE preEscapedLazyText #-}
 
 preEscapedTextBuilder :: LTB.Builder -> Markup
 textBuilder :: LTB.Builder -> Markup
 
 #ifdef PRE_BUILDER
-preEscapedTextBuilder = wrapMarkup . B.preEscapedTextBuilder
-textBuilder = wrapMarkup . B.textBuilder
+preEscapedTextBuilder = wrapMarkup . Text.Blaze.preEscapedTextBuilder
+textBuilder = wrapMarkup . Text.Blaze.textBuilder
 {-# INLINE preEscapedTextBuilder #-}
 {-# INLINE textBuilder #-}
 #else
@@ -222,17 +258,27 @@ textBuilder = error "This function needs blaze-markup 0.7.1.0"
 #endif
 
 preEscapedString :: String -> Markup
-preEscapedString = wrapMarkup . B.preEscapedString
+preEscapedString = wrapMarkup . Text.Blaze.preEscapedString
 {-# INLINE preEscapedString #-}
 
 string :: String -> Markup
-string = wrapMarkup . B.string
+string = wrapMarkup . Text.Blaze.string
 {-# INLINE string #-}
 
 text :: T.Text -> Markup
-text = wrapMarkup . B.text
+text = wrapMarkup . Text.Blaze.text
 {-# INLINE text #-}
 
 lazyText :: LT.Text -> Markup
-lazyText = wrapMarkup . B.lazyText
+lazyText = wrapMarkup . Text.Blaze.lazyText
 {-# INLINE lazyText #-}
+
+-- $descr1
+-- The following is an adaptation of all "Text.Blaze.Internal" exports to
+-- @blazeT@ types.
+-- 
+-- Entities that are reexported from "Text.Blaze.Internal" have the original
+-- documentation attached to them.
+--
+-- Entities that had to be adapted are tagged with \"(Adapted)\". For
+-- their documentation consult the "Text.Blaze.Internal" documentation.