biohazard-1.0.0: bioinformatics support library

Safe HaskellNone
LanguageHaskell2010

Bio.Iteratee

Synopsis

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.

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.

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

parRunIO :: MonadIO m => Int -> Enumeratee [IO a] a m b Source #

progressGen :: MonadIO m => (Int -> a -> String) -> Int -> (String -> IO ()) -> Enumeratee [a] [a] m b Source #

A general progress indicator that prints some message after a set number of records have passed through.

progressNum :: MonadIO m => String -> Int -> (String -> IO ()) -> Enumeratee [a] [a] m b Source #

A simple progress indicator that prints the number of records.

progressPos :: MonadIO m => (a -> (Refseq, Int)) -> String -> Refs -> Int -> (String -> IO ()) -> Enumeratee [a] [a] 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 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:

Minimal complete definition

liftIO

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances

MonadIO IO

Since: 4.9.0.0

Methods

liftIO :: IO a -> IO a #

MonadIO m => MonadIO (ListT m) 

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (MaybeT m) 

Methods

liftIO :: IO a -> MaybeT m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (ExceptT e m) 

Methods

liftIO :: IO a -> ExceptT e m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (IdentityT * m) 

Methods

liftIO :: IO a -> IdentityT * m a #

(MonadIO m, Nullable s, NullPoint s) => MonadIO (Iteratee s m) # 

Methods

liftIO :: IO a -> Iteratee s m a #

MonadIO m => MonadIO (ContT * r m) 

Methods

liftIO :: IO a -> ContT * r m a #

MonadIO m => MonadIO (ReaderT * r m) 

Methods

liftIO :: IO a -> ReaderT * r m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

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

MonadMask IO 

Methods

mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

(~) * e SomeException => MonadMask (Either e)

Since: 0.8.3

Methods

mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

MonadMask m => MonadMask (StateT s m) 

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

MonadMask m => MonadMask (StateT s m) 

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

MonadMask m => MonadMask (IdentityT * m) 

Methods

mask :: ((forall a. IdentityT * m a -> IdentityT * m a) -> IdentityT * m b) -> IdentityT * m b #

uninterruptibleMask :: ((forall a. IdentityT * m a -> IdentityT * m a) -> IdentityT * m b) -> IdentityT * m b #

(MonadMask m, Nullable s, NullPoint s) => MonadMask (Iteratee s m) # 

Methods

mask :: ((forall a. Iteratee s m a -> Iteratee s m a) -> Iteratee s m b) -> Iteratee s m b #

uninterruptibleMask :: ((forall a. Iteratee s m a -> Iteratee s m a) -> Iteratee s m b) -> Iteratee s m b #

MonadMask m => MonadMask (ReaderT * r m) 

Methods

mask :: ((forall a. ReaderT * r m a -> ReaderT * r m a) -> ReaderT * r m b) -> ReaderT * r m b #

uninterruptibleMask :: ((forall a. ReaderT * r m a -> ReaderT * r m a) -> ReaderT * r m b) -> ReaderT * r m b #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

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.

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.

data Ordering' a Source #

Constructors

Less 
Equal a 
NotLess 

mergeSortStreams :: Monad m => (a -> a -> Ordering' a) -> Enumeratee [a] [a] (Iteratee [a] 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

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 :: Parser a -> Iteratee ByteString m a Source #

A function to convert attoparsec Parsers into Iteratees.

stream2vector :: (MonadIO m, Vector v a) => Iteratee [a] m (v a) Source #

Reads the whole stream into a Vector.

stream2vectorN :: (MonadIO m, Vector v a) => Int -> Iteratee [a] m (v a) Source #

Equivalent to joinI $ takeStream n $ stream2vector, but more efficient.

data Fd :: * #

Instances

Bounded Fd 

Methods

minBound :: Fd #

maxBound :: Fd #

Enum Fd 

Methods

succ :: Fd -> Fd #

pred :: Fd -> Fd #

toEnum :: Int -> Fd #

fromEnum :: Fd -> Int #

enumFrom :: Fd -> [Fd] #

enumFromThen :: Fd -> Fd -> [Fd] #

enumFromTo :: Fd -> Fd -> [Fd] #

enumFromThenTo :: Fd -> Fd -> Fd -> [Fd] #

Eq Fd 

Methods

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

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

Integral Fd 

Methods

quot :: Fd -> Fd -> Fd #

rem :: Fd -> Fd -> Fd #

div :: Fd -> Fd -> Fd #

mod :: Fd -> Fd -> Fd #

quotRem :: Fd -> Fd -> (Fd, Fd) #

divMod :: Fd -> Fd -> (Fd, Fd) #

toInteger :: Fd -> Integer #

Num Fd 

Methods

(+) :: Fd -> Fd -> Fd #

(-) :: Fd -> Fd -> Fd #

(*) :: Fd -> Fd -> Fd #

negate :: Fd -> Fd #

abs :: Fd -> Fd #

signum :: Fd -> Fd #

fromInteger :: Integer -> Fd #

Ord Fd 

Methods

compare :: Fd -> Fd -> Ordering #

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

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

(>) :: Fd -> Fd -> Bool #

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

max :: Fd -> Fd -> Fd #

min :: Fd -> Fd -> Fd #

Read Fd 
Real Fd 

Methods

toRational :: Fd -> Rational #

Show Fd 

Methods

showsPrec :: Int -> Fd -> ShowS #

show :: Fd -> String #

showList :: [Fd] -> ShowS #

Storable Fd 

Methods

sizeOf :: Fd -> Int #

alignment :: Fd -> Int #

peekElemOff :: Ptr Fd -> Int -> IO Fd #

pokeElemOff :: Ptr Fd -> Int -> Fd -> IO () #

peekByteOff :: Ptr b -> Int -> IO Fd #

pokeByteOff :: Ptr b -> Int -> Fd -> IO () #

peek :: Ptr Fd -> IO Fd #

poke :: Ptr Fd -> Fd -> IO () #

Bits Fd 

Methods

(.&.) :: Fd -> Fd -> Fd #

(.|.) :: Fd -> Fd -> Fd #

xor :: Fd -> Fd -> Fd #

complement :: Fd -> Fd #

shift :: Fd -> Int -> Fd #

rotate :: Fd -> Int -> Fd #

zeroBits :: Fd #

bit :: Int -> Fd #

setBit :: Fd -> Int -> Fd #

clearBit :: Fd -> Int -> Fd #

complementBit :: Fd -> Int -> Fd #

testBit :: Fd -> Int -> Bool #

bitSizeMaybe :: Fd -> Maybe Int #

bitSize :: Fd -> Int #

isSigned :: Fd -> Bool #

shiftL :: Fd -> Int -> Fd #

unsafeShiftL :: Fd -> Int -> Fd #

shiftR :: Fd -> Int -> Fd #

unsafeShiftR :: Fd -> Int -> Fd #

rotateL :: Fd -> Int -> Fd #

rotateR :: Fd -> Int -> Fd #

popCount :: Fd -> Int #

FiniteBits Fd 

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