pipes-bytestring-2.1.7: ByteString support for pipes
Safe HaskellTrustworthy
LanguageHaskell2010

Pipes.ByteString

Description

This module provides pipes utilities for "byte streams", which are streams of strict ByteStrings chunks. Use byte streams to interact with both Handles and lazy ByteStrings.

To stream to or from Handles, use fromHandle or toHandle. For example, the following program copies data from one file to another:

import Pipes
import qualified Pipes.ByteString as P
import System.IO

main =
    withFile "inFile.txt"  ReadMode  $ \hIn  ->
    withFile "outFile.txt" WriteMode $ \hOut ->
    runEffect $ P.fromHandle hIn >-> P.toHandle hOut

You can stream to and from stdin and stdout using the predefined stdin and stdout pipes, like in the following "echo" program:

main = runEffect $ P.stdin >-> P.stdout

You can also translate pure lazy ByteStrings to and from pipes:

import qualified Data.ByteString.Lazy.Char8 as BL

main = runEffect $ P.fromLazy (BL.pack "Hello, world!\n") >-> P.stdout

In addition, this module provides many functions equivalent to lazy ByteString functions so that you can transform or fold byte streams. For example, to stream only the first three lines of stdin to stdout you would write:

import Lens.Family (over)
import Pipes
import qualified Pipes.ByteString as PB
import Pipes.Group (takes)

main = runEffect $ over PB.lines (takes 3) PB.stdin >-> PB.stdout

The above program will never bring more than one chunk (~ 32 KB) into memory, no matter how long the lines are.

Note that functions in this library are designed to operate on streams that are insensitive to chunk boundaries. This means that they may freely split chunks into smaller chunks and discard empty chunks. However, they will never concatenate chunks in order to provide strict upper bounds on memory usage.

Synopsis

Producers

fromLazy :: Monad m => ByteString -> Producer' ByteString m () Source #

Convert a lazy ByteString into a Producer of strict ByteStrings

stdin :: MonadIO m => Producer' ByteString m () Source #

Stream bytes from stdin

fromHandle :: MonadIO m => Handle -> Producer' ByteString m () Source #

Convert a Handle into a byte stream using a default chunk size

hGetSome :: MonadIO m => Int -> Handle -> Producer' ByteString m () Source #

Convert a handle into a byte stream using a maximum chunk size

hGetSome forwards input immediately as it becomes available, splitting the input into multiple chunks if it exceeds the maximum chunk size.

hGetNonBlocking :: MonadIO m => Int -> Handle -> Producer' ByteString m () Source #

Convert a handle into a byte stream using a fixed chunk size

Similar to hGet except that it will never block waiting for data to become available.

hGet :: MonadIO m => Int -> Handle -> Producer' ByteString m () Source #

Convert a handle into a byte stream using a fixed chunk size

hGet waits until exactly the requested number of bytes are available for each chunk.

hGetRange Source #

Arguments

:: MonadIO m 
=> Int

Offset

-> Int

Size

-> Handle 
-> Producer' ByteString m () 

Like hGet but with an extra parameter specifying an initial handle offset

Servers

hGetSomeN :: MonadIO m => Handle -> Int -> Server' Int ByteString m () Source #

Like hGetSome, except you can vary the maximum chunk size for each request

hGetN :: MonadIO m => Handle -> Int -> Server' Int ByteString m () Source #

Like hGet, except you can vary the chunk size for each request

Consumers

stdout :: MonadIO m => Consumer' ByteString m () Source #

Stream bytes to stdout

Unlike toHandle, stdout gracefully terminates on a broken output pipe.

toHandle :: MonadIO m => Handle -> Consumer' ByteString m r Source #

Convert a byte stream into a Handle

p >-> toHandle handle = for p (liftIO . hPutStr handle)

Pipes

map :: Monad m => (Word8 -> Word8) -> Pipe ByteString ByteString m r Source #

Apply a transformation to each Word8 in the stream

concatMap :: Monad m => (Word8 -> ByteString) -> Pipe ByteString ByteString m r Source #

Map a function over the byte stream and concatenate the results

take :: (Monad m, Integral n) => n -> Pipe ByteString ByteString m () Source #

(take n) only allows n bytes to pass

takeWhile :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m () Source #

Take bytes until they fail the predicate

filter :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m r Source #

Only allows Word8s to pass if they satisfy the predicate

elemIndices :: (Monad m, Num n) => Word8 -> Pipe ByteString n m r Source #

Stream all indices whose elements match the given Word8

findIndices :: (Monad m, Num n) => (Word8 -> Bool) -> Pipe ByteString n m r Source #

Stream all indices whose elements satisfy the given predicate

scan :: Monad m => (Word8 -> Word8 -> Word8) -> Word8 -> Pipe ByteString ByteString m r Source #

Strict left scan over the bytes

Folds

toLazy :: Producer ByteString Identity () -> ByteString Source #

Fold a pure Producer of strict ByteStrings into a lazy ByteString

toLazyM :: Monad m => Producer ByteString m () -> m ByteString Source #

Fold an effectful Producer of strict ByteStrings into a lazy ByteString

Note: toLazyM is not an idiomatic use of pipes, but I provide it for simple testing purposes. Idiomatic pipes style consumes the chunks immediately as they are generated instead of loading them all into memory.

toLazyM' :: Monad m => Producer ByteString m a -> m (ByteString, a) Source #

Fold an effectful Producer of strict ByteStrings into a lazy ByteString alongside the return value

Note: toLazyM' is not an idiomatic use of pipes, but I provide it for simple testing purposes. Idiomatic pipes style consumes the chunks immediately as they are generated instead of loading them all into memory.

foldBytes :: Monad m => (x -> Word8 -> x) -> x -> (x -> r) -> Producer ByteString m () -> m r Source #

Reduce the stream of bytes using a strict left fold

Note: It's more efficient to use folds from Control.Foldl.ByteString in conjunction with Pipes.Prelude.fold when possible

head :: Monad m => Producer ByteString m () -> m (Maybe Word8) Source #

Retrieve the first Word8

last :: Monad m => Producer ByteString m () -> m (Maybe Word8) Source #

Retrieve the last Word8

null :: Monad m => Producer ByteString m () -> m Bool Source #

Determine if the stream is empty

length :: (Monad m, Num n) => Producer ByteString m () -> m n Source #

Count the number of bytes

any :: Monad m => (Word8 -> Bool) -> Producer ByteString m () -> m Bool Source #

Fold that returns whether Any received Word8s satisfy the predicate

all :: Monad m => (Word8 -> Bool) -> Producer ByteString m () -> m Bool Source #

Fold that returns whether All received Word8s satisfy the predicate

maximum :: Monad m => Producer ByteString m () -> m (Maybe Word8) Source #

Return the maximum Word8 within a byte stream

minimum :: Monad m => Producer ByteString m () -> m (Maybe Word8) Source #

Return the minimum Word8 within a byte stream

elem :: Monad m => Word8 -> Producer ByteString m () -> m Bool Source #

Determine whether any element in the byte stream matches the given Word8

notElem :: Monad m => Word8 -> Producer ByteString m () -> m Bool Source #

Determine whether all elements in the byte stream do not match the given Word8

find :: Monad m => (Word8 -> Bool) -> Producer ByteString m () -> m (Maybe Word8) Source #

Find the first element in the stream that matches the predicate

index :: (Monad m, Integral n) => n -> Producer ByteString m () -> m (Maybe Word8) Source #

Index into a byte stream

elemIndex :: (Monad m, Num n) => Word8 -> Producer ByteString m () -> m (Maybe n) Source #

Find the index of an element that matches the given Word8

findIndex :: (Monad m, Num n) => (Word8 -> Bool) -> Producer ByteString m () -> m (Maybe n) Source #

Store the first index of an element that satisfies the predicate

count :: (Monad m, Num n) => Word8 -> Producer ByteString m () -> m n Source #

Store a tally of how many elements match the given Word8

Parsing

The following parsing utilities are single-byte analogs of the ones found in pipes-parse.

nextByte :: Monad m => Producer ByteString m r -> m (Either r (Word8, Producer ByteString m r)) Source #

Consume the first byte from a byte stream

next either fails with a Left if the Producer has no more bytes or succeeds with a Right providing the next byte and the remainder of the Producer.

drawByte :: Monad m => Parser ByteString m (Maybe Word8) Source #

Draw one Word8 from the underlying Producer, returning Nothing if the Producer is empty

unDrawByte :: Monad m => Word8 -> Parser ByteString m () Source #

Push back a Word8 onto the underlying Producer

peekByte :: Monad m => Parser ByteString m (Maybe Word8) Source #

peekByte checks the first Word8 in the stream, but uses unDrawByte to push the Word8 back

peekByte = do
    x <- drawByte
    case x of
        Nothing -> return ()
        Just w8 -> unDrawByte w8
    return x

isEndOfBytes :: Monad m => Parser ByteString m Bool Source #

Check if the underlying Producer has no more bytes

Note that this will skip over empty ByteString chunks, unlike isEndOfInput from pipes-parse.

isEndOfBytes = liftM isNothing peekByte

Parsing Lenses

splitAt :: (Monad m, Integral n) => n -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #

Improper lens that splits a Producer after the given number of bytes

span :: Monad m => (Word8 -> Bool) -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #

Improper lens that splits after the longest consecutive group of bytes that satisfy the given predicate

break :: Monad m => (Word8 -> Bool) -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #

Improper lens that splits after the longest consecutive group of bytes that fail the given predicate

breakOn :: Monad m => ByteString -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #

Improper lens that splits at the first occurrence of the pattern.

groupBy :: Monad m => (Word8 -> Word8 -> Bool) -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #

Improper lens that splits after the first group of matching bytes, as defined by the given equality predicate

group :: Monad m => Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #

Like groupBy, where the equality predicate is (==)

word :: Monad m => Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #

Improper lens that splits a Producer after the first word

Unlike words, this does not drop leading whitespace

Note: This function is purely for demonstration purposes since it assumes a particular encoding. You should prefer the Text equivalent of this function from the pipes-text library.

line :: Monad m => Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #

Improper lens that splits a Producer after the first line

Unlike lines, this does not consume the newline marker, which is stored within the inner Producer

Note: This function is purely for demonstration purposes since it assumes a particular encoding. You should prefer the Text equivalent of this function from the pipes-text library.

Transforming Byte Streams

drop :: (Monad m, Integral n) => n -> Producer ByteString m r -> Producer ByteString m r Source #

(drop n) drops the first n bytes

dropWhile :: Monad m => (Word8 -> Bool) -> Producer ByteString m r -> Producer ByteString m r Source #

Drop bytes until they fail the predicate

intersperse :: Monad m => Word8 -> Producer ByteString m r -> Producer ByteString m r Source #

Intersperse a Word8 in between the bytes of the byte stream

pack :: Monad m => Lens' (Producer Word8 m x) (Producer ByteString m x) Source #

Improper lens from unpacked Word8s to packaged ByteStrings

unpack :: Monad m => Lens' (Producer ByteString m x) (Producer Word8 m x) Source #

Improper lens from packed ByteStrings to unpacked Word8s

chunksOf' :: (Monad m, Integral n) => n -> Producer ByteString m r -> Producer ByteString m r Source #

Group byte stream chunks into chunks of fixed length

Note: This is the only function in this API that concatenates ByteString chunks, which requires allocating new ByteStrings

FreeT Transformations

chunksOf :: (Monad m, Integral n) => n -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #

Split a byte stream into FreeT-delimited byte streams of fixed size

splitsWith :: Monad m => (Word8 -> Bool) -> Producer ByteString m x -> FreeT (Producer ByteString m) m x Source #

Split a byte stream into groups separated by bytes that satisfy the predicate

splits :: Monad m => Word8 -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #

Split a byte stream into groups separated by the given byte

splitOn :: Monad m => ByteString -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #

Split a byte stream into groups separated by the given ByteString

groupsBy :: Monad m => (Word8 -> Word8 -> Bool) -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #

Isomorphism between a byte stream and groups of identical bytes using the supplied equality predicate

groups :: Monad m => Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #

Like groupsBy, where the equality predicate is (==)

lines :: Monad m => Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x) Source #

Improper lens between a bytestream and its lines

Note: This function is purely for demonstration purposes since it assumes a particular encoding. You should prefer the Text equivalent of this function from the pipes-text library.

unlines :: Monad m => Lens' (FreeT (Producer ByteString m) m x) (Producer ByteString m x) Source #

Improper lens between lines and a bytestream

Note: This function is purely for demonstration purposes since it assumes a particular encoding. You should prefer the Text equivalent of this function from the pipes-text library.

words :: Monad m => Producer ByteString m x -> FreeT (Producer ByteString m) m x Source #

Convert a bytestream to delimited words

Note: This function is purely for demonstration purposes since it assumes a particular encoding. You should prefer the Text equivalent of this function from the pipes-text library.

unwords :: Monad m => FreeT (Producer ByteString m) m x -> Producer ByteString m x Source #

Convert delimited words back to a byte stream

Note: This function is purely for demonstration purposes since it assumes a particular encoding. You should prefer the Text equivalent of this function from the pipes-text library.

Re-exports

Data.ByteString re-exports the ByteString type.

Data.Word re-exports the Word8 type.

Pipes.Parse re-exports Parser.

Pipes.Group re-exports concats, intercalates, and FreeT (the type).

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances

Instances details
Eq ByteString 
Instance details

Defined in Data.ByteString.Internal

Data ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString #

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal

Read ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

IsString ByteString 
Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

data Word8 #

8-bit unsigned integer type

Instances

Instances details
Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

(>=) :: Word8 -> Word8 -> Bool #

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Bits Word8

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

liftTyped :: Word8 -> Q (TExp Word8) #

data FreeT (f :: Type -> Type) (m :: Type -> Type) a #

The "free monad transformer" for a functor f

Instances

Instances details
(Functor f, Monad m) => MonadFree f (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

wrap :: f (FreeT f m a) -> FreeT f m a #

(Functor f, MonadWriter w m) => MonadWriter w (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

writer :: (a, w) -> FreeT f m a #

tell :: w -> FreeT f m () #

listen :: FreeT f m a -> FreeT f m (a, w) #

pass :: FreeT f m (a, w -> w) -> FreeT f m a #

(Functor f, MonadState s m) => MonadState s (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

get :: FreeT f m s #

put :: s -> FreeT f m () #

state :: (s -> (a, s)) -> FreeT f m a #

(Functor f, MonadReader r m) => MonadReader r (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

ask :: FreeT f m r #

local :: (r -> r) -> FreeT f m a -> FreeT f m a #

reader :: (r -> a) -> FreeT f m a #

(Functor f, MonadError e m) => MonadError e (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

throwError :: e -> FreeT f m a #

catchError :: FreeT f m a -> (e -> FreeT f m a) -> FreeT f m a #

(Functor f, MonadBase b m) => MonadBase b (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

liftBase :: b α -> FreeT f m α #

MonadTrans (FreeT f) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

lift :: Monad m => m a -> FreeT f m a #

(Functor f, Monad m) => Monad (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

(>>=) :: FreeT f m a -> (a -> FreeT f m b) -> FreeT f m b #

(>>) :: FreeT f m a -> FreeT f m b -> FreeT f m b #

return :: a -> FreeT f m a #

(Functor f, Monad m) => Functor (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

fmap :: (a -> b) -> FreeT f m a -> FreeT f m b #

(<$) :: a -> FreeT f m b -> FreeT f m a #

(Functor f, MonadFail m) => MonadFail (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

fail :: String -> FreeT f m a #

(Functor f, Monad m) => Applicative (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

pure :: a -> FreeT f m a #

(<*>) :: FreeT f m (a -> b) -> FreeT f m a -> FreeT f m b #

liftA2 :: (a -> b -> c) -> FreeT f m a -> FreeT f m b -> FreeT f m c #

(*>) :: FreeT f m a -> FreeT f m b -> FreeT f m b #

(<*) :: FreeT f m a -> FreeT f m b -> FreeT f m a #

(Foldable m, Foldable f) => Foldable (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

fold :: Monoid m0 => FreeT f m m0 -> m0 #

foldMap :: Monoid m0 => (a -> m0) -> FreeT f m a -> m0 #

foldMap' :: Monoid m0 => (a -> m0) -> FreeT f m a -> m0 #

foldr :: (a -> b -> b) -> b -> FreeT f m a -> b #

foldr' :: (a -> b -> b) -> b -> FreeT f m a -> b #

foldl :: (b -> a -> b) -> b -> FreeT f m a -> b #

foldl' :: (b -> a -> b) -> b -> FreeT f m a -> b #

foldr1 :: (a -> a -> a) -> FreeT f m a -> a #

foldl1 :: (a -> a -> a) -> FreeT f m a -> a #

toList :: FreeT f m a -> [a] #

null :: FreeT f m a -> Bool #

length :: FreeT f m a -> Int #

elem :: Eq a => a -> FreeT f m a -> Bool #

maximum :: Ord a => FreeT f m a -> a #

minimum :: Ord a => FreeT f m a -> a #

sum :: Num a => FreeT f m a -> a #

product :: Num a => FreeT f m a -> a #

(Monad m, Traversable m, Traversable f) => Traversable (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

traverse :: Applicative f0 => (a -> f0 b) -> FreeT f m a -> f0 (FreeT f m b) #

sequenceA :: Applicative f0 => FreeT f m (f0 a) -> f0 (FreeT f m a) #

mapM :: Monad m0 => (a -> m0 b) -> FreeT f m a -> m0 (FreeT f m b) #

sequence :: Monad m0 => FreeT f m (m0 a) -> m0 (FreeT f m a) #

(Eq1 f, Eq1 m) => Eq1 (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

liftEq :: (a -> b -> Bool) -> FreeT f m a -> FreeT f m b -> Bool #

(Ord1 f, Ord1 m) => Ord1 (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

liftCompare :: (a -> b -> Ordering) -> FreeT f m a -> FreeT f m b -> Ordering #

(Read1 f, Read1 m) => Read1 (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (FreeT f m a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [FreeT f m a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (FreeT f m a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [FreeT f m a] #

(Show1 f, Show1 m) => Show1 (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FreeT f m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FreeT f m a] -> ShowS #

(Functor f, MonadIO m) => MonadIO (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

liftIO :: IO a -> FreeT f m a #

(Functor f, MonadPlus m) => Alternative (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

empty :: FreeT f m a #

(<|>) :: FreeT f m a -> FreeT f m a -> FreeT f m a #

some :: FreeT f m a -> FreeT f m [a] #

many :: FreeT f m a -> FreeT f m [a] #

(Functor f, MonadPlus m) => MonadPlus (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

mzero :: FreeT f m a #

mplus :: FreeT f m a -> FreeT f m a -> FreeT f m a #

(Functor f, MonadThrow m) => MonadThrow (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

throwM :: Exception e => e -> FreeT f m a #

(Functor f, MonadCatch m) => MonadCatch (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

catch :: Exception e => FreeT f m a -> (e -> FreeT f m a) -> FreeT f m a #

(Functor f, MonadCont m) => MonadCont (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

callCC :: ((a -> FreeT f m b) -> FreeT f m a) -> FreeT f m a #

(Functor f, Monad m) => Apply (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

(<.>) :: FreeT f m (a -> b) -> FreeT f m a -> FreeT f m b #

(.>) :: FreeT f m a -> FreeT f m b -> FreeT f m b #

(<.) :: FreeT f m a -> FreeT f m b -> FreeT f m a #

liftF2 :: (a -> b -> c) -> FreeT f m a -> FreeT f m b -> FreeT f m c #

(Functor f, Monad m) => Bind (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

(>>-) :: FreeT f m a -> (a -> FreeT f m b) -> FreeT f m b #

join :: FreeT f m (FreeT f m a) -> FreeT f m a #

(Eq1 f, Eq1 m, Eq a) => Eq (FreeT f m a) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

(==) :: FreeT f m a -> FreeT f m a -> Bool #

(/=) :: FreeT f m a -> FreeT f m a -> Bool #

(Ord1 f, Ord1 m, Ord a) => Ord (FreeT f m a) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

compare :: FreeT f m a -> FreeT f m a -> Ordering #

(<) :: FreeT f m a -> FreeT f m a -> Bool #

(<=) :: FreeT f m a -> FreeT f m a -> Bool #

(>) :: FreeT f m a -> FreeT f m a -> Bool #

(>=) :: FreeT f m a -> FreeT f m a -> Bool #

max :: FreeT f m a -> FreeT f m a -> FreeT f m a #

min :: FreeT f m a -> FreeT f m a -> FreeT f m a #

(Read1 f, Read1 m, Read a) => Read (FreeT f m a) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

readsPrec :: Int -> ReadS (FreeT f m a) #

readList :: ReadS [FreeT f m a] #

readPrec :: ReadPrec (FreeT f m a) #

readListPrec :: ReadPrec [FreeT f m a] #

(Show1 f, Show1 m, Show a) => Show (FreeT f m a) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

showsPrec :: Int -> FreeT f m a -> ShowS #

show :: FreeT f m a -> String #

showList :: [FreeT f m a] -> ShowS #

intercalates :: forall (m :: Type -> Type) a x. Monad m => Producer a m () -> FreeT (Producer a m) m x -> Producer a m x #

Join a FreeT-delimited stream of Producers into a single Producer by intercalating a Producer in between them

intercalates :: Monad m => Producer a m () -> Joiner a m x

concats :: forall (m :: Type -> Type) a x. Monad m => FreeT (Producer a m) m x -> Producer a m x #

Join a FreeT-delimited stream of Producers into a single Producer

concats :: Monad m => Joiner a m x

type Parser a (m :: Type -> Type) r = forall x. StateT (Producer a m x) m r #

A Parser is an action that reads from and writes to a stored Producer