]> git.immae.eu Git - github/fretlink/text-pipes.git/blobdiff - Pipes/Text.hs
travis new
[github/fretlink/text-pipes.git] / Pipes / Text.hs
index 7722f7fcec949892b5a7b0ec58e6864f24e374a2..f71f17f77528b2acbaa7b1785d5cf54e2c0b96d7 100644 (file)
@@ -128,8 +128,16 @@ import Prelude hiding (
     words,
     writeFile )
 
-
--- | Convert a lazy 'TL.Text' into a 'Producer' of strict 'Text's
+-- $setup
+-- >>> :set -XOverloadedStrings
+-- >>> import Data.Text (Text)
+-- >>> import qualified Data.Text as T
+-- >>> import qualified Data.Text.Lazy.IO as TL
+-- >>> import Data.Char
+
+-- | Convert a lazy 'TL.Text' into a 'Producer' of strict 'Text's. Producers in 
+-- IO can be found in 'Pipes.Text.IO' or in pipes-bytestring, employed with the
+-- decoding lenses in 'Pipes.Text.Encoding'
 fromLazy :: (Monad m) => TL.Text -> Producer' Text m ()
 fromLazy  = TL.foldrChunks (\e a -> yield e >> a) (return ())
 {-# INLINE fromLazy #-}
@@ -138,11 +146,17 @@ fromLazy  = TL.foldrChunks (\e a -> yield e >> a) (return ())
 a ^. lens = getConstant (lens Constant a)
 
 -- | Apply a transformation to each 'Char' in the stream
+
+-- >>> let margaret =  ["Margaret, are you grieving\nOver Golde","ngrove unleaving?":: Text]
+-- >>> TL.putStrLn . toLazy $ each margaret >-> map Data.Char.toUpper
+-- MARGARET, ARE YOU GRIEVING
+-- OVER GOLDENGROVE UNLEAVING?
 map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r
 map f = P.map (T.map f)
 {-# INLINABLE map #-}
 
 -- | Map a function over the characters of a text stream and concatenate the results
+
 concatMap
     :: (Monad m) => (Char -> Text) -> Pipe Text Text m r
 concatMap f = P.map (T.concatMap f)
@@ -154,7 +168,7 @@ take :: (Monad m, Integral a) => a -> Pipe Text Text m ()
 take n0 = go n0 where
     go n
         | n <= 0    = return ()
-        | otherwise = do
+        | otherwise = do 
             txt <- await
             let len = fromIntegral (T.length txt)
             if (len > n)
@@ -184,6 +198,11 @@ filter predicate = P.map (T.filter predicate)
 {-# INLINABLE filter #-}
 
 -- | Strict left scan over the characters
+-- >>> let margaret = ["Margaret, are you grieving\nOver Golde","ngrove unleaving?":: Text]
+-- >>> let title_caser a x = case a of ' ' -> Data.Char.toUpper x; _ -> x
+-- >>> toLazy $ each margaret >-> scan title_caser ' ' 
+-- " Margaret, Are You Grieving\nOver Goldengrove Unleaving?"
+
 scan
     :: (Monad m)
     => (Char -> Char -> Char) -> Char -> Pipe Text Text m r