| Safe Haskell | None |
|---|
Pipes.Parse
Description
Element-agnostic parsing utilities for pipes
pipes-parse provides two ways to parse and transform streams in constant
space:
- The "list-like" approach, using the split / transform / join paradigm
- The monadic approach, using parser combinators
The top half of this module provides the list-like approach. The key idea is that:
-- '~' means "is analogous to" Producer a m () ~ [a] FreeT (Producer a m) m () ~ [[a]]
FreeT nests each subsequent Producer within the return value of the
previous Producer so that you cannot access the next Producer until you
completely drain the current Producer. However, you rarely need to work
with FreeT directly. Instead, you structure everything using
"splitters", "transformations" and "joiners":
-- A "splitter" Producer a m () -> FreeT (Producer a m) m () ~ [a] -> [[a]] -- A "transformation" FreeT (Producer a m) m () -> FreeT (Producer a m) m () ~ [[a]] -> [[a]] -- A "joiner" FreeT (Producer a m) m () -> Producer a m () ~ [[a]] -> [a]
For example, if you wanted to group standard input by equal lines and take the first three groups, you would write:
import Pipes import qualified Pipes.Parse as Parse import qualified Pipes.Prelude as Prelude threeGroups :: (Monad m, Eq a) => Producer a m () -> Producer a m () threeGroups = Parse.concat . Parse.takeFree 3 . Parse.groupBy (==) -- ^ Joiner ^ Transformation ^ Splitter
This then limits standard input to the first three consecutive groups of equal lines:
>>>runEffect $ threeGroups Prelude.stdinLn >-> Prelude.stdoutLnGroup1<Enter> Group1 Group1<Enter> Group1 Group2<Enter> Group2 Group3<Enter> Group3 Group3<Enter> Group3 Group4<Enter>>>>-- Done, because we began entering our fourth group
The advantage of this style or programming is that you never bring more than
a single element into memory. This works because FreeT sub-divides the
Producer without concatenating elements together, preserving the laziness
of the underlying Producer.
The bottom half of this module contains the lower-level monadic parsing
primitives. These are more useful for pipes implementers, particularly
for building splitters. I recommend that application developers use the
list-like style whenever possible.
- groupBy :: Monad m => (a -> a -> Bool) -> Producer a m r -> FreeT (Producer a m) m r
- chunksOf :: Monad m => Int -> Producer a m r -> FreeT (Producer a m) m r
- splitOn :: Monad m => (a -> Bool) -> Producer a m r -> FreeT (Producer a m) m r
- takeFree :: (Functor f, Monad m) => Int -> FreeT f m () -> FreeT f m ()
- concat :: Monad m => FreeT (Producer a m) m r -> Producer a m r
- intercalate :: Monad m => Producer a m () -> FreeT (Producer a m) m r -> Producer a m r
- draw :: Monad m => StateT (Producer a m r) m (Either r a)
- unDraw :: Monad m => a -> StateT (Producer a m r) m ()
- peek :: Monad m => StateT (Producer a m r) m (Either r a)
- isEndOfInput :: Monad m => StateT (Producer a m r) m Bool
- input :: Monad m => Producer' a (StateT (Producer a m r) m) r
- takeWhile :: Monad m => (a -> Bool) -> Pipe a a (StateT (Producer a m r) m) ()
- module Control.Monad.Trans.Free
- module Control.Monad.Trans.State.Strict
Splitters
Transformations
takeFree :: (Functor f, Monad m) => Int -> FreeT f m () -> FreeT f m ()Source
(take n) only keeps the first n functor layers of a FreeT
Joiners
Low-level Parsers
unDraw :: Monad m => a -> StateT (Producer a m r) m ()Source
Push back an element onto the underlying Producer
isEndOfInput :: Monad m => StateT (Producer a m r) m BoolSource
Check if the underlying Producer is empty
isEndOfInput = liftM isLeft peek
High-level Parsers
input provides a Producer that streams from the underlying Producer.
Streaming from input differs from streaming directly from the underlying
Producer because any unused input is saved for later, as the following
example illustrates:
import Control.Monad.Trans.State.Strict
import Pipes
import Pipes.Parse
import qualified Pipes.Prelude as P
parser :: (Show a) => StateT (Producer a IO ()) IO ()
parser = do
runEffect $ input >-> P.take 2 >-> P.show >-> P.stdoutLn
liftIO $ putStrLn "Intermission"
runEffect $ input >-> P.take 2 >-> P.show >-> P.stdoutLn
The second pipeline resumes where the first pipeline left off:
>>>evalStateT parser (each [1..])1 2 Intermission 3 4
You can see more examples of how to use these parsing utilities by studying the source code for the above splitters.
Utilities
Re-exports
Control.Monad.Trans.Free re-exports FreeF, FreeT, and runFreeT.
Control.Monad.Trans.State.Strict re-exports StateT, runStateT,
evalStateT, and execStateT.
module Control.Monad.Trans.Free