Safe Haskell | None |
---|---|
Language | Haskell2010 |
Basically a reexport of Data.Iteratee less the names that clash with Prelude plus a handful of utilities.
- iGetString :: Int -> Iteratee ByteString m ByteString
- iterGet :: Get a -> Iteratee ByteString m a
- iterLoop :: (Nullable s, Monad m) => (a -> Iteratee s m a) -> a -> Iteratee s m a
- iLookAhead :: Monoid s => Iteratee s m a -> Iteratee s m a
- protectTerm :: (Nullable s, MonadIO m) => Iteratee s m a -> Iteratee s m a
- parMapChunksIO :: (MonadIO m, Nullable s) => Int -> (s -> IO t) -> Enumeratee s t m a
- parRunIO :: MonadIO m => Int -> Enumeratee [IO a] a m b
- progressGen :: (MonadIO m, NullPoint s, ListLike s a) => (Int -> a -> String) -> Int -> (String -> IO ()) -> Enumeratee s s m b
- progressNum :: (MonadIO m, NullPoint s, ListLike s a) => String -> Int -> (String -> IO ()) -> Enumeratee s s m b
- progressPos :: (MonadIO m, ListLike s a, NullPoint s) => (a -> (Refseq, Int)) -> String -> Refs -> Int -> (String -> IO ()) -> Enumeratee s s m b
- ($==) :: Monad m => Enumerator' hdr input m (Iteratee output m result) -> Enumeratee input output m result -> Enumerator' hdr output m result
- class (FoldableLL full item, Monoid full) => ListLike full item | full -> item
- class Monad m => MonadIO m where
- class MonadCatch m => MonadMask m
- lift :: MonadTrans t => forall m a. Monad m => m a -> t m a
- liftIO :: MonadIO m => forall a. IO a -> m a
- stdin :: Handle
- stdout :: Handle
- stderr :: Handle
- enumAuxFile :: (MonadIO m, MonadMask m) => FilePath -> Iteratee ByteString m a -> m a
- enumInputs :: (MonadIO m, MonadMask m) => [FilePath] -> Enumerator ByteString m a
- enumDefaultInputs :: (MonadIO m, MonadMask m) => Enumerator ByteString m a
- data Ordering' a
- mergeSortStreams :: (Monad m, ListLike s a, Nullable s) => (a -> a -> Ordering' a) -> Enumeratee s s (Iteratee s m) b
- type Enumerator' h eo m b = (h -> Iteratee eo m b) -> m (Iteratee eo m b)
- type Enumeratee' h ei eo m b = (h -> Iteratee eo m b) -> Iteratee ei m (Iteratee eo m b)
- mergeEnums' :: (Nullable s2, Nullable s1, Monad m) => Enumerator' hi s1 m a -> Enumerator' ho s2 (Iteratee s1 m) a -> (ho -> Enumeratee s2 s1 (Iteratee s1 m) a) -> Enumerator' hi s1 m a
- data QQ a = QQ !Int [a] [a]
- emptyQ :: QQ a
- lengthQ :: QQ a -> Int
- pushQ :: a -> QQ a -> QQ a
- popQ :: QQ a -> Maybe (a, QQ a)
- cancelAll :: MonadIO m => QQ (Async a) -> m ()
- data ParseError = ParseError {
- errorContexts :: [String]
- errorMessage :: String
- parserToIteratee :: Parser a -> Iteratee ByteString m a
- stream2vector :: (MonadIO m, ListLike s a, Nullable s, Vector v a) => Iteratee s m (v a)
- stream2vectorN :: (MonadIO m, ListLike s a, Nullable s, Vector v a) => Int -> Iteratee s m (v a)
- data Fd :: *
- withFileFd :: (MonadIO m, MonadMask m) => FilePath -> (Fd -> m a) -> m a
- module Bio.Iteratee.Binary
- module Bio.Iteratee.Char
- module Bio.Iteratee.IO
- module Bio.Iteratee.Iteratee
- module Bio.Iteratee.ListLike
Documentation
iGetString :: Int -> Iteratee ByteString m ByteString Source #
Collects a string of a given length. Don't use this for long
strings, use takeStream
instead.
iterLoop :: (Nullable s, Monad m) => (a -> Iteratee s m a) -> a -> Iteratee s m a Source #
Repeatedly apply an Iteratee
to a value until end of stream.
Returns the final value.
iLookAhead :: Monoid s => Iteratee s m a -> Iteratee s m a Source #
Run an Iteratee, collect the input. When it finishes, return the
result along with *all* input. Effectively allows lookahead. Be
careful, this will eat memory if the Iteratee
doesn't return
speedily.
parMapChunksIO :: (MonadIO m, Nullable s) => Int -> (s -> IO t) -> Enumeratee s t m a Source #
Parallel map of an IO action over the elements of a stream
This Enumeratee
applies an IO
action to every chunk of the input
stream. These IO
actions are run asynchronously in a limited
parallel way. Don't forget to evaluate
progressGen :: (MonadIO m, NullPoint s, ListLike s a) => (Int -> a -> String) -> Int -> (String -> IO ()) -> Enumeratee s s m b Source #
A general progress indicator that prints some message after a set number of records have passed through.
progressNum :: (MonadIO m, NullPoint s, ListLike s a) => String -> Int -> (String -> IO ()) -> Enumeratee s s m b Source #
A simple progress indicator that prints the number of records.
progressPos :: (MonadIO m, ListLike s a, NullPoint s) => (a -> (Refseq, Int)) -> String -> Refs -> Int -> (String -> IO ()) -> Enumeratee s s m b Source #
A simple progress indicator that prints a position every set number of passed records.
($==) :: Monad m => Enumerator' hdr input m (Iteratee output m result) -> Enumeratee input output m result -> Enumerator' hdr output m result infixl 1 Source #
Compose an 'Enumerator\'' with an Enumeratee
, giving a new
'Enumerator\''.
class (FoldableLL full item, Monoid full) => ListLike full item | full -> item #
The class implementing list-like functions.
It is worth noting that types such as Map
can be instances of
ListLike
. Due to their specific ways of operating, they may not behave
in the expected way in some cases. For instance, cons
may not increase
the size of a map if the key you have given is already in the map; it will
just replace the value already there.
Implementators must define at least:
- singleton
- head
- tail
- null or genericLength
singleton, uncons, null | singleton, uncons, genericLength | singleton, head, tail, null | singleton, head, tail, genericLength
ListLike [a] a | |
class Monad m => MonadIO m where #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
MonadIO IO | |
MonadIO m => MonadIO (ListT m) | |
MonadIO m => MonadIO (MaybeT m) | |
(Error e, MonadIO m) => MonadIO (ErrorT e m) | |
MonadIO m => MonadIO (ExceptT e m) | |
MonadIO m => MonadIO (StateT s m) | |
MonadIO m => MonadIO (StateT s m) | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
MonadIO m => MonadIO (IdentityT * m) | |
(MonadIO m, Nullable s, NullPoint s) => MonadIO (Iteratee s m) # | |
MonadIO m => MonadIO (ContT * r m) | |
MonadIO m => MonadIO (ReaderT * r m) | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
class MonadCatch m => MonadMask m #
A class for monads which provide for the ability to account for all
possible exit points from a computation, and to mask asynchronous
exceptions. Continuation-based monads, and stacks such as ErrorT e IO
which provide for multiple failure modes, are invalid instances of this
class.
Note that this package does provide a MonadMask
instance for CatchT
.
This instance is only valid if the base monad provides no ability to
provide multiple exit. For example, IO
or Either
would be invalid base
monads, but Reader
or State
would be acceptable.
Instances should ensure that, in the following code:
f `finally` g
The action g
is called regardless of what occurs within f
, including
async exceptions.
MonadMask IO | |
(~) * e SomeException => MonadMask (Either e) | Since: 0.8.3 |
MonadMask m => MonadMask (StateT s m) | |
MonadMask m => MonadMask (StateT s m) | |
(MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
(MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
MonadMask m => MonadMask (IdentityT * m) | |
(MonadMask m, Nullable s, NullPoint s) => MonadMask (Iteratee s m) # | |
MonadMask m => MonadMask (ReaderT * r m) | |
(MonadMask m, Monoid w) => MonadMask (RWST r w s m) | |
(MonadMask m, Monoid w) => MonadMask (RWST r w s m) | |
lift :: MonadTrans t => forall m a. Monad m => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
enumAuxFile :: (MonadIO m, MonadMask m) => FilePath -> Iteratee ByteString m a -> m a Source #
enumInputs :: (MonadIO m, MonadMask m) => [FilePath] -> Enumerator ByteString m a Source #
enumDefaultInputs :: (MonadIO m, MonadMask m) => Enumerator ByteString m a Source #
mergeSortStreams :: (Monad m, ListLike s a, Nullable s) => (a -> a -> Ordering' a) -> Enumeratee s s (Iteratee s m) b Source #
type Enumerator' h eo m b = (h -> Iteratee eo m b) -> m (Iteratee eo m b) Source #
:: (Nullable s2, Nullable s1, Monad m) | |
=> Enumerator' hi s1 m a | inner enumerator |
-> Enumerator' ho s2 (Iteratee s1 m) a | outer enumerator |
-> (ho -> Enumeratee s2 s1 (Iteratee s1 m) a) | merging enumeratee |
-> Enumerator' hi s1 m a |
Merge two 'Enumerator\''s into one. The header provided by the inner 'Enumerator\'' is passed to the output iterator, the header provided by the outer 'Enumerator\'' is passed to the merging iteratee
XXX Something about those headers is unsatisfactory... there should be an unobtrusive way to combine headers.
data ParseError Source #
ParseError | |
|
parserToIteratee :: Parser a -> Iteratee ByteString m a Source #
A function to convert attoparsec Parser
s into Iteratee
s.
stream2vector :: (MonadIO m, ListLike s a, Nullable s, Vector v a) => Iteratee s m (v a) Source #
Reads the whole stream into a Vector
.
stream2vectorN :: (MonadIO m, ListLike s a, Nullable s, Vector v a) => Int -> Iteratee s m (v a) Source #
Equivalent to joinI $ takeStream n $ stream2vector
, but more
efficient.
module Bio.Iteratee.Binary
module Bio.Iteratee.Char
module Bio.Iteratee.IO
module Bio.Iteratee.Iteratee
module Bio.Iteratee.ListLike