]> git.immae.eu Git - github/fretlink/text-pipes.git/commitdiff
updated examples
authormichaelt <what_is_it_to_do_anything@yahoo.com>
Tue, 11 Nov 2014 21:09:48 +0000 (16:09 -0500)
committermichaelt <what_is_it_to_do_anything@yahoo.com>
Tue, 11 Nov 2014 21:09:48 +0000 (16:09 -0500)
examples/attoparser.hs
examples/decode.hs
examples/zoom.hs

index ddf770d0776f618c4c6aa8f1280d1c1ab34b0d7a..6328991a815bbe1eb5d946614b267eca5d5ae237 100644 (file)
@@ -2,7 +2,8 @@ import Pipes
 import Pipes.Text.IO (fromHandle)
 import Pipes.Attoparsec (parsed)
 import qualified System.IO as IO
-
+import Data.Attoparsec.Text
+import Control.Applicative
 data Test = Test {
   a :: Int,
   b :: Int
@@ -17,5 +18,32 @@ testParser = do
   return $ Test a b
   
 main = IO.withFile "./testfile" IO.ReadMode $ \handle -> runEffect $
-    for test_parser (lift . print)
-  where (parsed (testParser <* endOfLine) (fromHandle handle))
\ No newline at end of file
+    for  (parsed testParser (fromHandle handle)) 
+         (lift . print)
+
+
+-- >>> :! cat testfile
+-- 1 1
+-- 2 2
+-- 3 3
+-- 4 4
+-- 5 5
+-- 6 6
+-- 7 7
+-- 8 8
+-- 9 9
+-- 10 10
+
+-- >>> main
+-- Test {a = 1, b = 1}
+-- Test {a = 2, b = 2}
+-- Test {a = 3, b = 3}
+-- Test {a = 4, b = 4}
+-- Test {a = 5, b = 5}
+-- Test {a = 6, b = 6}
+-- Test {a = 7, b = 7}
+-- Test {a = 8, b = 8}
+-- Test {a = 9, b = 9}
+-- Test {a = 10, b = 10}
+
+
index 8cb44f8443ebb4459ed3f617f5df4f700c8ac022..177325d39f2b2d5d1c14ac21791868ec94744bc9 100644 (file)
@@ -3,14 +3,16 @@
 import Data.ByteString (ByteString)
 import Data.Text       (Text)
 import Lens.Family.State.Strict (zoom)
+
 import Pipes
 import Pipes.Parse
 import qualified Pipes.ByteString as ByteString
-import qualified Pipes.Text       as Text
+import qualified Pipes.Text as Text
+import qualified Pipes.Text.Encoding as Text
 
 -- Retrieve all `Text` chunks up to 10 characters
 parser :: Monad m => Parser ByteString m [Text]
-parser = zoom (Text.decodeUtf8 . Text.splitAt 10) drawAll
+parser = zoom (Text.utf8 . Text.splitAt 10) drawAll
 
 main = do
     (textChunks, leftovers) <- runStateT parser ByteString.stdin
index 3442dc8abde2aa600a3ff581d900f33d00488ad4..c3afc8365a618cd7a0b12fecce26aecb6d83579f 100644 (file)
@@ -26,15 +26,14 @@ import qualified Pipes.ByteString as Bytes
 import qualified Pipes.Text as Txt
 import Pipes.Text.Encoding (utf8)
 
-import Control.Lens
-import Control.Lens.Internal.Zoom
+import Control.Lens -- we use 'zoom' with MonadState, not just StateT
 import Control.Monad
 import qualified System.IO as IO
 import Control.Monad.Trans.Maybe
 import Control.Monad.State.Class
 
 main :: IO ()
-main = do -- S.writeFile fp $ contents 10000 -- 10000 cannot be handled fileParser0 and 1
+main = do S.writeFile fp $ contents 10000 -- 10000 cannot be handled fileParser0 and 1
           -- parse_file fileParser0  -- pathological
           -- parse_file fileParser1  -- programs
           parse_file fileParser2  -- good program 
@@ -76,22 +75,16 @@ fileParser1  = do nameLength    <- zoom utf8 parseNumber
                   contents      <- zoom (Bytes.splitAt contentLength) (lift drawAll)
                   return (File (T.concat names) (S.concat contents))
 
--- this is the good program; be reflecting on the fact that file names
+-- This is the good program; by reflecting on the fact that file names
 -- should not be a 1000 bytes long, and binary files longer than e.g. 10 ^ 10
 -- we can restrict the length of the byte stream to which we apply `zoom utf8`
-fileParser2  = do nameLength  <- Bytes.splitAt 3 ~~> utf8 ~~> parseNumber
-                  names       <- Bytes.splitAt nameLength ~~> utf8 ~~> lift drawAll
-                  len         <- Bytes.splitAt 10 ~~>  utf8 ~~> parseNumber
-                  contents    <- Bytes.splitAt len ~~> lift drawAll
+fileParser2  = do nameLength  <- zoom (Bytes.splitAt 3 . utf8) parseNumber
+                  names       <- zoom (Bytes.splitAt nameLength . utf8) (lift drawAll)
+                  len         <- zoom (Bytes.splitAt 10 . utf8) parseNumber
+                  contents    <- zoom (Bytes.splitAt len) (lift drawAll)
                   return (File (T.concat names) (S.concat contents))
 
--- infix lens nonsense
-infixr 1 ~~>
-(~~>) :: Zoom m n s t 
-      => ((s -> Zoomed n c s) -> t -> Zoomed n c t)
-      -> m c -> n c
-(~~>) = zoom
-{-# INLINE (~~>) #-}
+
 
 parseNumber :: Monad m =>  MaybeT (StateT (Producer Text m x) m) Int
 parseNumber  = loop  0 where
@@ -132,21 +125,3 @@ input =
     ]
 
 
----
-
--- This desperate scheme actually has some efficacy, if used before `utf8` in a zoom
--- but not much 
-
-chunk :: Monad m => Int -> Lens' (Producer ByteString m r) (Producer ByteString m r)
-chunk n = lens (chunkyN n) (\_ b -> b) where
-
-    chunkyN  :: Monad m => Int -> Producer ByteString m r -> Producer ByteString m r
-    chunkyN n  = prod_loop where
-
-      prod_loop p = do mbs <- lift $ next p
-                       case mbs of Left r -> return r
-                                   Right (bs, p') -> do bs_loop bs
-                                                        prod_loop p'
-      bs_loop bs = unless (S.null bs) $ do yield fore
-                                           unless (S.null aft)  (bs_loop aft)
-            where (fore, aft) = S.splitAt n bs