sousit-0.3: Source/Sink/Transform: An alternative to lazy IO and iteratees.

Safe HaskellNone

Data.SouSiT.Trans

Contents

Synopsis

Element Transformation

map :: (a -> b) -> Transform a bSource

Transforms each input individually by applying the function.

mapM :: Monad m => (b -> m a) -> Sink a m r -> Sink b m rSource

Transforms each input individually by applying the monadic function. Warning: This is not really a Transform, since it isn't pure.

mapWithState :: (s -> a -> (b, s)) -> s -> Transform a bSource

Transforms each input and carry a state between the inputs.

zipWithIndex :: Transform a (a, Int)Source

Transforms each input to a tuple (input, index of input). I.e. for Mario: (M, 0), (a, 1), (r, 2), (i, 3), (o, 4)

take :: (Num n, Ord n) => n -> Transform a aSource

Takes only the first n inputs, then returns done.

takeUntil :: (a -> Bool) -> Transform a aSource

Takes inputs until the input fullfils the predicate. The matching input is not passed on.

takeUntilEq :: Eq a => a -> Transform a aSource

Takes inputs until the input matches the argument. The matching input is not passed on.

takeWhile :: (a -> Bool) -> Transform a aSource

Take inputs while the input fullfils the predicate. As soon as the first non-matching input is encountered no more inputs will be passed on.

drop :: (Num n, Ord n) => n -> Transform a aSource

Drops the first n inputs then passes through all inputs unchanged

dropUntil :: (a -> Bool) -> Transform a aSource

Drops inputs until the predicate is matched. The matching input and all subsequent inputs are passed on unchanged.

dropWhile :: (a -> Bool) -> Transform a aSource

Drops inputs as long as they match the predicate. The first non-matching input and all following inputs are passed on unchanged.

Filter / FlatMap

filter :: (a -> Bool) -> Transform a aSource

Only retains elements that match the filter function

filterMap :: (a -> Maybe b) -> Transform a bSource

Map that allows to filter out elements.

flatMap :: (a -> [b]) -> Transform a bSource

Applies a function to each element and passes on every element of the result list seperatly.

Accumulation

accumulate :: b -> (b -> a -> b) -> Transform a bSource

Accumulates all elements with the accumulator function.

buffer :: Int -> b -> (b -> a -> b) -> Transform a bSource

Accumulates up to n elements with the accumulator function and then releases it.

count :: Num n => Transform a nSource

Counts the received elements.

Dispersing

disperse :: Transform [a] aSource

Yield all elements of the array as seperate outputs.

Chaining/Looping

andThen :: Transform a b -> Transform a b -> Transform a bSource

Executes with t1 and when t1 ends, then the next input is fed to through t2.

loop :: Transform a b -> Transform a bSource

Loops the given transform forever.

loopN :: Int -> Transform a b -> Transform a bSource

Loops the given transform n times

sequence :: [Transform a b] -> Transform a bSource

Executes the given transforms in a sequence, as soon as one ends the next input is passed to the next transform.

Handling of Either

eitherRight :: Transform (Either a b) bSource

Only lets the rights of Either pass.

eitherLeft :: Transform (Either a b) aSource

Only lets the lefts of Either pass.

Serialization (cereal)

serialize :: Serialize a => Transform a ByteStringSource

Serialize the elements into ByteString using cereal. For every input there is exactly one output.

deserialize :: Serialize b => Transform ByteString bSource

Deserializes ByteString elements. The ByteStrings may be chunked, but the beginnings of values must be aligned to the chunks. If this is not the case then consider splitting the ByteStrings by the appropriate start delimiter (if available) or split them up into singletons.

Utilities

mapSinkStatus :: Monad m => (SinkStatus a m r -> SinkStatus b m r) -> Sink a m r -> Sink b m rSource

type TransFun a b m r = (a -> Sink a m r) -> m r -> b -> Sink b m rSource

applyTransFun :: Monad m => TransFun a b m r -> SinkStatus a m r -> SinkStatus b m rSource

mapSinkTransFun :: Monad m => TransFun a b m r -> Sink a m r -> Sink b m rSource

applyMapping :: Monad m => (Sink a m r -> Sink b m r) -> (b -> a) -> SinkStatus a m r -> SinkStatus b m rSource

mapSinkMapping :: Monad m => (Sink a m r -> Sink b m r) -> (b -> a) -> Sink a m r -> Sink b m rSource

toDoneTrans :: Monad m => Sink a m r -> Sink a m rSource

debug :: (Show a, Show r, MonadIO m) => String -> Sink a m r -> Sink a m rSource

Outputs every element received and the result to the System-out (using putStrLn). Format: label: element label is result