Safe Haskell | None |
---|
- map :: (a -> b) -> Transform a b
- mapM :: Monad m => (b -> m a) -> Sink a m r -> Sink b m r
- mapWithState :: (s -> a -> (b, s)) -> s -> Transform a b
- zipWithIndex :: Transform a (a, Int)
- take :: (Num n, Ord n) => n -> Transform a a
- takeUntil :: (a -> Bool) -> Transform a a
- takeUntilEq :: Eq a => a -> Transform a a
- takeWhile :: (a -> Bool) -> Transform a a
- drop :: (Num n, Ord n) => n -> Transform a a
- dropUntil :: (a -> Bool) -> Transform a a
- dropWhile :: (a -> Bool) -> Transform a a
- filter :: (a -> Bool) -> Transform a a
- filterMap :: (a -> Maybe b) -> Transform a b
- flatMap :: (a -> [b]) -> Transform a b
- accumulate :: b -> (b -> a -> b) -> Transform a b
- buffer :: Int -> b -> (b -> a -> b) -> Transform a b
- count :: Num n => Transform a n
- disperse :: Transform [a] a
- andThen :: Transform a b -> Transform a b -> Transform a b
- loop :: Transform a b -> Transform a b
- loopN :: Int -> Transform a b -> Transform a b
- sequence :: [Transform a b] -> Transform a b
- eitherRight :: Transform (Either a b) b
- eitherLeft :: Transform (Either a b) a
- serialize :: Serialize a => Transform a ByteString
- deserialize :: Serialize b => Transform ByteString b
- mapSinkStatus :: Monad m => (SinkStatus a m r -> SinkStatus b m r) -> Sink a m r -> Sink b m r
- type TransFun a b m r = (a -> m (Sink a m r)) -> m r -> b -> m (Sink b m r)
- applyTransFun :: Monad m => TransFun a b m r -> SinkStatus a m r -> SinkStatus b m r
- mapSinkTransFun :: Monad m => TransFun a b m r -> Sink a m r -> Sink b m r
- applyMapping :: Monad m => (Sink a m r -> Sink b m r) -> (b -> a) -> SinkStatus a m r -> SinkStatus b m r
- mapSinkMapping :: Monad m => (Sink a m r -> Sink b m r) -> (b -> a) -> Sink a m r -> Sink b m r
- toDoneTrans :: Monad m => Sink a m r -> Sink a m r
- debug :: (Show a, MonadIO m) => String -> Sink a m r -> Sink a m r
Element Transformation
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)
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
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.
Dispersing
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.
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
applyTransFun :: Monad m => TransFun a b m r -> SinkStatus a m r -> SinkStatus 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