biohazard-0.6.5: bioinformatics support library

Safe HaskellNone
LanguageHaskell98

Bio.Iteratee

Description

Basically a reexport of Data.Iteratee less the names that clash with Prelude plus a handful of utilities.

Synopsis

Documentation

groupStreamBy :: (Monad m, ListLike l t, NullPoint l, Nullable l) => (t -> t -> Bool) -> m (Iteratee l m t2) -> Enumeratee l [t2] m a Source

Grouping on Iteratees. groupStreamBy cmp inner outer executes inner to obtain an Iteratee i, then passes elements e to i as long as cmp e0 e, where e0 is some preceeding element, is true. Else, the result of run i is passed to outer and groupStreamBy restarts. At end of input, the resulting outer is returned.

groupStreamOn :: (Monad m, ListLike l e, Eq t1, NullPoint l, Nullable l) => (e -> t1) -> (t1 -> m (Iteratee l m t2)) -> Enumeratee l [(t1, t2)] m a Source

Grouping on Iteratees. groupStreamOn proj inner outer executes inner (proj e), where e is the first input element, to obtain an Iteratee i, then passes elements e to i as long as proj e produces the same result. If proj e changes or the input ends, the pair of proj e and the result of run i is passed to outer. At end of input, the resulting outer is returned.

iGetString :: Monad m => Int -> Iteratee ByteString m ByteString Source

Collects a string of a given length. Don't use this for long strings, use takeStream instead.

iterGet :: Monad m => Get a -> Iteratee ByteString m a Source

Convert a Get into an Iteratee. The Get is applied once, the decoded data is returned, unneded input remains in the stream.

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.

headStream :: ListLike s el => Iteratee s m el Source

Take first element of a stream or fail.

takeStream :: (Monad m, Nullable s, ListLike s el) => Int -> Enumeratee s s m a Source

Take a prefix of a stream, the equivalent of take.

dropStream :: (Nullable s, ListLike s el) => Int -> Iteratee s m () Source

mapStreamM :: (Monad m, ListLike (s el) el, ListLike (s el') el', NullPoint (s el), Nullable (s el), LooseMap s el el') => (el -> m el') -> Enumeratee (s el) (s el') m a Source

Map a monadic function over an Iteratee.

mapStreamM_ :: (Monad m, Nullable s, ListLike s el) => (el -> m b) -> Iteratee s m () Source

Map a monadic function over an Iteratee, discarding the results.

filterStream :: (Monad m, ListLike s a, NullPoint s) => (a -> Bool) -> Enumeratee s s m r Source

Apply a filter predicate to an Iteratee.

filterStreamM :: (Monad m, ListLike s a, Nullable s, NullPoint s) => (a -> m Bool) -> Enumeratee s s m r Source

Apply a monadic filter predicate to an Iteratee.

foldStream :: (Monad m, Nullable s, ListLike s a) => (b -> a -> b) -> b -> Iteratee s m b Source

Fold a function over an Iteratee.

foldStreamM :: (Monad m, Nullable s, ListLike s a) => (b -> a -> m b) -> b -> Iteratee s m b Source

Fold a monadic function over an Iteratee.

zipStreams :: (Nullable s, ListLike s el, Monad m) => Iteratee s m a -> Iteratee s m b -> Iteratee s m (a, b) Source

Apply two Iteratees to the same stream.

protectTerm :: (Nullable s, MonadIO m) => Iteratee s m a -> Iteratee s m a Source

Protects the terminal from binary junk. If i is an Iteratee that might write binary to stdout, then protectTerm i is the same Iteratee, but it will abort if stdout is a terminal device.

concatMapStream :: (Monad m, ListLike s a, NullPoint s, ListLike t b) => (a -> t) -> Enumeratee s t m r Source

Apply a function to the elements of a stream, concatenate the results into a stream. No giant intermediate list is produced.

concatMapStreamM :: (Monad m, ListLike s a, NullPoint s, ListLike t b) => (a -> m t) -> Enumeratee s t m r Source

Apply a monadic function to the elements of a stream, concatenate the results into a stream. No giant intermediate list is produced.

mapMaybeStream :: (Monad m, ListLike s a, NullPoint s, ListLike t b) => (a -> Maybe b) -> Enumeratee s t m r Source

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

progressNum :: (MonadIO m, Nullable s, NullPoint s, ListLike s a) => String -> (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 -> (String -> IO ()) -> Refs -> Enumeratee s s m b Source

A simple progress indicator that prints a position.

mapStream :: (ListLike (s el) el, ListLike (s el') el', NullPoint (s el), LooseMap s el el') => (el -> el') -> Enumeratee (s el) (s el') m a

Map the stream: another iteratee transformer Given the stream of elements of the type el and the function (el->el'), build a nested stream of elements of the type el' and apply the given iteratee to it.

The analog of List.map

takeWhileE :: (ListLike s el, NullPoint s) => (el -> Bool) -> Enumeratee s s m a

Takes an element predicate and an iteratee, running the iteratee on all elements of the stream while the predicate is met.

This is preferred to takeWhile.

tryHead :: ListLike s el => Iteratee s m (Maybe el)

Similar to head, except it returns Nothing if the stream is terminated.

isFinished :: Nullable s => Iteratee s m Bool

Check if a stream has received EOF.

heads :: (Monad m, Nullable s, ListLike s el, Eq el) => s -> Iteratee s m Int

Given a sequence of characters, attempt to match them against the characters on the stream. Return the count of how many characters matched. The matched characters are removed from the stream. For example, if the stream contains abd, then (heads abc) will remove the characters ab and return 2.

breakE :: (ListLike s el, NullPoint s) => (el -> Bool) -> Enumeratee s s m a

Takes an element predicate and an iteratee, running the iteratee on all elements of the stream until the predicate is met.

the following rule relates break to breakE break pred === joinI (breakE pred stream2stream)

breakE should be used in preference to break whenever possible.

($==) :: 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\''.

mBind :: Monad m => m a -> (a -> Iteratee s m b) -> Iteratee s m b infixl 1 Source

Lifts a monadic action and combines it with a continuation. mBind m f is the same as lift m >>= f, but does not require a Nullable constraint on the stream type.

mBind_ :: Monad m => m a -> Iteratee s m b -> Iteratee s m b infixl 1 Source

Lifts a monadic action, ignored the result and combines it with a continuation. mBind_ m f is the same as lift m >>= f, but does not require a Nullable constraint on the stream type.

ioBind :: MonadIO m => IO a -> (a -> Iteratee s m b) -> Iteratee s m b infixl 1 Source

Lifts an IO action and combines it with a continuation. ioBind m f is the same as liftIO m >>= f, but does not require a Nullable constraint on the stream type.

ioBind_ :: MonadIO m => IO a -> Iteratee s m b -> Iteratee s m b infixl 1 Source

Lifts an IO action, ignores its result, and combines it with a continuation. ioBind_ m f is the same as liftIO m >> f, but does not require a Nullable constraint on the stream type.

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

Minimal complete definition

singleton, head, tail

Instances

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:

Methods

liftIO :: IO a -> m a

Lift a computation from the IO monad.

Instances

MonadIO IO 
MonadIO m => MonadIO (ListT m) 
MonadIO m => MonadIO (MaybeT 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) 
MonadIO m => MonadIO (StateT s m) 
MonadIO m => MonadIO (StateT s m) 
MonadIO m => MonadIO (ExceptT e m) 
(Error e, MonadIO m) => MonadIO (ErrorT e m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w 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.

Minimal complete definition

mask, uninterruptibleMask

Instances

lift :: MonadTrans t => forall m a. Monad m => m a -> t m a

Lift a computation from the argument monad to the constructed monad.

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1

Left-to-right Kleisli composition of monads.

(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 1

Right-to-left Kleisli composition of monads. (>=>), with the arguments flipped

stdin :: Handle

A handle managing input from the Haskell program's standard input channel.

stdout :: Handle

A handle managing output to the Haskell program's standard output channel.

stderr :: Handle

A handle managing output to the Haskell program's standard error channel.

defaultBufSize :: Int Source

Default buffer size in elements. This is 1024 in Data.Iteratee, which is obviously too small. Since we want to merge many files, a read should take more time than a seek. This sets the sensible buffer size to more than about one MB.

data Ordering' a Source

Constructors

Less 
Equal a 
NotLess 

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

type Enumeratee' h ei eo m b = (h -> Iteratee eo m b) -> Iteratee ei m (Iteratee eo m b) Source

mergeEnums' Source

Arguments

:: (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 QQ a Source

Constructors

QQ !Int [a] [a] 

pushQ :: a -> QQ a -> QQ a Source

popQ :: QQ a -> Maybe (a, QQ a) Source

cancelAll :: MonadIO m => QQ (Async a) -> m () Source

parserToIteratee :: Monad m => Parser a -> Iteratee ByteString m a Source

A function to convert attoparsec Parsers into Iteratees.

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.

withFileFd :: (MonadIO m, MonadMask m) => FilePath -> (Fd -> m a) -> m a Source