streaming-0.1.0.1: A general free monad transformer optimized for streaming applications.

Safe HaskellNone
LanguageHaskell2010

Streaming

Contents

Synopsis

Free monad transformer

The Stream data type is equivalent to FreeT and can represent any effectful succession of steps, where the form of the steps or commands is specified by the first (functor) parameter.

data Stream f m r = Step !(f (Stream f m r)) | Delay (m (Stream f m r)) | Return r

In the simplest case, the base functor is (,) a . Here the news or command at each step is an individual element of type a , i.e. a yield statement. In Prelude, (a,b) is replaced by the left-strict pair Of a b. Various operations are defined for types like

Stream (Of a) m r                   -- a producer in the pipes sense 
                                       -- i.e. an effectful, streaming [a], or rather ([a],r) 
Stream (Of a) m (Stream (Of a) m r) -- the effectful splitting of a producer
                                       -- i.e. an effectful ([a],[a]) or rather ([a],([a],r))
Stream (Stream (Of a) m) m r        -- successive, segmentation of a producer
  • - i.e. [[a]], or ([a],([a],([a]... r))) and so on. But of course any functor can be used.

To avoid breaking reasoning principles, the constructors should not be used directly. A pattern-match should go by way of inspect - or, in the producer case, next The constructors are exported by the Internal module.

data Stream f m r Source

Instances

Functor f => MFunctor (Stream f) Source 
Functor f => MMonad (Stream f) Source 
Functor f => MonadTrans (Stream f) Source 
(Functor f, Monad m) => Monad (Stream f m) Source 
(Functor f, Monad m) => Functor (Stream f m) Source 
(Functor f, Monad m) => Applicative (Stream f m) Source 
(MonadIO m, Functor f) => MonadIO (Stream f m) Source 
(Eq r, Eq (m (Stream f m r)), Eq (f (Stream f m r))) => Eq (Stream f m r) Source 
(Typeable (* -> *) f, Typeable (* -> *) m, Data r, Data (m (Stream f m r)), Data (f (Stream f m r))) => Data (Stream f m r) Source 
(Show r, Show (m (Stream f m r)), Show (f (Stream f m r))) => Show (Stream f m r) Source 

Constructing a Stream on a base functor

unfold :: (Monad m, Functor f) => (s -> m (Either r (f s))) -> s -> Stream f m r Source

Build a Stream by unfolding steps starting from a seed.

unfold inspect = id -- modulo the quotient we work with
unfold Pipes.next :: Monad m => Producer a m r -> Stream ((,) a) m r
unfold (curry (:>) . Pipes.next) :: Monad m => Producer a m r -> Stream (Of a) m r

for :: (Monad m, Functor f) => Stream (Of a) m r -> (a -> Stream f m x) -> Stream f m r Source

for replaces each element of a stream with an associated stream. Note that the associated stream may layer any functor.

construct :: (forall b. (f b -> b) -> (m b -> b) -> (r -> b) -> b) -> Stream f m r Source

Reflect a church-encoded stream; cp. GHC.Exts.build

Transforming streams

maps :: (Monad m, Functor f) => (forall x. f x -> g x) -> Stream f m r -> Stream g m r Source

Map layers of one functor to another with a natural transformation

maps' :: (Monad m, Functor f) => (forall x. f x -> m (a, x)) -> Stream f m r -> Stream (Of a) m r Source

Map free layers of a functor to a corresponding stream of individual elements. This simplifies the use of folds marked with a ''' in Streaming.Prelude

maps' sum' :: (Monad m, Num a) => Stream (Stream (Of a) m) m r -> Stream (Of a) m r
maps' (Pipes.fold' (+) (0::Int) id) :: Monad m => Stream (Producer Int m) m r -> Stream (Of Int) m r

mapsM :: (Monad m, Functor f) => (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r Source

Map layers of one functor to another with a transformation involving the base monad

Inspecting a stream

inspect :: (Functor f, Monad m) => Stream f m r -> m (Either r (f (Stream f m r))) Source

Inspect the first stage of a freely layered sequence. Compare Pipes.next and the replica Streaming.Prelude.next. This is the uncons for the general unfold.

unfold inspect = id
Streaming.Prelude.unfoldr StreamingPrelude.next = id

Eliminating a Stream

destroy :: (Functor f, Monad m) => Stream f m r -> (f b -> b) -> (m b -> b) -> (r -> b) -> b Source

Map a stream to its church encoding; compare list foldr

intercalates :: (Monad m, Monad (t m), MonadTrans t) => t m a -> Stream (t m) m b -> t m b Source

concats :: (MonadTrans t, Monad (t m), Monad m) => Stream (t m) m a -> t m a Source

iterTM :: (Functor f, Monad m, MonadTrans t, Monad (t m)) => (f (t m a) -> t m a) -> Stream f m a -> t m a Source

iterT :: (Functor f, Monad m) => (f (m a) -> m a) -> Stream f m a -> m a Source

Splitting and joining Streams

split :: (Monad m, Functor f) => Int -> Stream f m r -> Stream f m (Stream f m r) Source

chunksOf :: (Monad m, Functor f) => Int -> Stream f m r -> Stream (Stream f m) m r Source

concats :: (MonadTrans t, Monad (t m), Monad m) => Stream (t m) m a -> t m a Source

Useful functors

data Of a b Source

A left-strict pair; the base functor for streams of individual elements.

Constructors

!a :> b infixr 4 

Instances

Functor (Of a) Source 
Foldable (Of a) Source 
Traversable (Of a) Source 
(Eq a, Eq b) => Eq (Of a b) Source 
(Data a, Data b) => Data (Of a b) Source 
(Ord a, Ord b) => Ord (Of a b) Source 
(Read a, Read b) => Read (Of a b) Source 
(Show a, Show b) => Show (Of a b) Source 

lazily :: Of a b -> (a, b) Source

strictly :: (a, b) -> Of a b Source

re-exports

class MFunctor t where

A functor in the category of monads, using hoist as the analog of fmap:

hoist (f . g) = hoist f . hoist g

hoist id = id

Methods

hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b

Lift a monad morphism from m to n into a monad morphism from (t m) to (t n)

class MonadTrans t where

The class of monad transformers. Instances should satisfy the following laws, which state that lift is a monad transformation:

Methods

lift :: Monad m => m a -> t m a

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