streaming-0.1.3.4: an elementary streaming prelude and a general stream type.

Safe HaskellNone
LanguageHaskell2010

Streaming.Internal

Contents

Synopsis

The 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)) | Effect (m (Stream f m r)) | Return r

The producer concept uses the simple functor (a,_) - or the stricter Of a _ . Then the news at each step or layer is just: an individual item of type a. Since Stream (Of a) m r is equivalent to Pipe.Producer a m r, much of the pipes Prelude can easily be mirrored in a streaming Prelude. Similarly, a simple Consumer a m r or Parser a m r concept arises when the base functor is (a -> _) . Stream ((->) input) m result consumes input until it returns a result.

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

Constructors

Step !(f (Stream f m r)) 
Effect (m (Stream f m r)) 
Return r 

Instances

(MonadBase b m, Functor f) => MonadBase b (Stream f m) Source 
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 
(MonadThrow m, Functor f) => MonadThrow (Stream f m) Source 
(MonadCatch m, Functor f) => MonadCatch (Stream f m) Source 
(MonadIO m, Functor f) => MonadIO (Stream f m) Source 
(MonadResource m, Functor f) => MonadResource (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 

Introducing a stream

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. See also the specialized unfoldr in the prelude.

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

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

Repeat a functorial layer, command or instruct several times.

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

Repeat a functorial layer, command or instruction forever.

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

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

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

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

Lift for items in the base functor. Makes a singleton or one-layer succession. It is named by similarity to lift:

lift :: (Monad m, Functor f)     => m r -> Stream f m r
yields ::  (Monad m, Functor f) => f r -> Stream f m r

streamBuild :: (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

destroy a b c (streamBuild psi)  = 

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

Construct an infinite stream by cycling a finite one

cycles = forever
>>> 

Eliminating a stream

intercalates :: (Monad m, Monad (t m), MonadTrans t) => t m x -> Stream (t m) m r -> t m r Source

Interpolate a layer at each segment. This specializes to e.g.

intercalates :: (Monad m, Functor f) => Stream f m () -> Stream (Stream f m) m r -> Stream f m r

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

Dissolves the segmentation into layers of Stream f m layers.

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

Specialized fold following the usage of Control.Monad.Trans.Free

iterT alg = streamFold return join alg 

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

Specialized fold following the usage of Control.Monad.Trans.Free

iterTM alg = streamFold return (join . lift)

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

Map a stream directly to its church encoding; compare Data.List.foldr

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

streamFold reorders the arguments of destroy to be more akin to foldr It is more convenient to query in ghci to figure out what kind of 'algebra' you need to write.

>>> :t streamFold return join
(Monad m, Functor f) => 
     (f (m a) -> m a) -> Stream f m a -> m a        -- iterT
>>> :t streamFold return (join . lift)
(Monad m, Monad (t m), Functor f, MonadTrans t) =>
     (f (t m a) -> t m a) -> Stream f m a -> t m a  -- iterTM
>>> :t streamFold return effect
(Monad m, Functor f, Functor g) =>
     (f (Stream g m r) -> Stream g m r) -> Stream f m r -> Stream g m r
>>> :t \f -> streamFold return effect (wrap . f)
(Monad m, Functor f, Functor g) =>
     (f (Stream g m a) -> g (Stream g m a))
     -> Stream f m a -> Stream g m a                 -- maps
>>> :t \f -> streamFold return effect (effect . liftM wrap . f)
(Monad m, Functor f, Functor g) =>
     (f (Stream g m a) -> m (g (Stream g m a)))
     -> Stream f m a -> Stream g m a                 -- mapped

So for example, when we realize that

>>> :t streamFold return Q.mwrap
(Monad m, Functor f) =>
   (f (Q.ByteString m a) -> Q.ByteString m a)
   -> Stream f m a -> Q.ByteString m a

it is easy to see how to write fromChunks:

>>> streamFold return Q.mwrap (\(a:>b) -> Q.chunk a >>  b)
Monad m => Stream (Of B.ByteString) m a -> Q.ByteString m a -- fromChunks

Inspecting a stream wrap by wrap

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

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 transformation. Compare hoist, which has a similar effect on the monadic parameter.

maps id = id
maps f . maps g = maps (f . g)

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 maps is more fundamental than mapsM, which is best understood as a convenience for effecting this frequent composition:

mapsM phi = decompose . maps (Compose . phi)

mapped :: (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 maps is more fundamental than mapped, which is best understood as a convenience for effecting this frequent composition:

mapped = mapsM 
mapsM phi = decompose . maps (Compose . phi)  

mapped obeys these rules:

mapped return       = id
mapped f . mapped g = mapped (f <=< g)
map f . mapped g    = mapped (liftM f . g)
mapped f . map g    = mapped (f . g)

decompose :: (Monad m, Functor f) => Stream (Compose m f) m r -> Stream f m r Source

Resort a succession of layers of the form m (f x). Though mapsM is best understood as:

mapsM phi = decompose . maps (Compose . phi)

we could as well define decompose by mapsM:

decompose = mapsM getCompose

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

Map each layer to an effect, and run them all.

run :: Monad m => Stream m m r -> m r Source

Run the effects in a stream that merely layers effects.

distribute :: (Monad m, Functor f, MonadTrans t, MFunctor t, Monad (t (Stream f m))) => Stream f (t m) r -> t (Stream f m) r Source

Make it possible to 'run' the underlying transformed monad.

groups :: (Monad m, Functor f, Functor g) => Stream (Sum f g) m r -> Stream (Sum (Stream f m) (Stream g m)) m r Source

Group layers in an alternating stream into adjoining sub-streams of one type or another.

Splitting streams

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

Break a stream into substreams each with n functorial layers.

>>> S.print $ mapped S.sum $ chunksOf 2 $ each [1,1,1,1,1]
2
2
1

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

Split a succession of layers after some number, returning a streaming or effectful pair.

>>> rest <- S.print $ S.splitAt 1 $ each [1..3]
1
>>> S.print rest
2
3
splitAt 0 = return
splitAt n >=> splitAt m = splitAt (m+n)

Thus, e.g.

>>> rest <- S.print $ splitsAt 2 >=> splitsAt 2 $ each [1..5]
1
2
3
4
>>> S.print rest
5

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

Zipping and unzipping streams

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

zips :: (Monad m, Functor f, Functor g) => Stream f m r -> Stream g m r -> Stream (Compose f g) m r Source

unzips :: (Monad m, Functor f, Functor g) => Stream (Compose f g) m r -> Stream f (Stream g m) r Source

interleaves :: (Monad m, Applicative h) => Stream h m r -> Stream h m r -> Stream h m r Source

Interleave functor layers, with the effects of the first preceding the effects of the second.

interleaves = zipsWith (liftA2 (,))
>>> let paste = \a b -> interleaves (Q.lines a) (maps (Q.cons' '\t') (Q.lines b))
>>> Q.stdout $ Q.unlines $ paste "hello\nworld\n" "goodbye\nworld\n"
hello	goodbye
world	world

separate :: (Monad m, Functor f, Functor g) => Stream (Sum f g) m r -> Stream f (Stream g m) r Source

Given a stream on a sum of functors, make it a stream on the left functor, with the streaming on the other functor as the governing monad. This is useful for acting on one or the other functor with a fold.

>>> let odd_even = S.maps (S.distinguish even) $ S.each [1..10::Int]
>>> :t separate odd_even
separate odd_even
  :: Monad m => Stream (Of Int) (Stream (Of Int) m) ()

Now, for example, it is convenient to fold on the left and right values separately:

>>> toList $ toList $ separate odd_even
[2,4,6,8,10] :> ([1,3,5,7,9] :> ())

We can achieve the above effect more simply in the case of Stream (Of a) m r by using duplicate

>>> S.toList . S.filter even $ S.toList . S.filter odd $ S.duplicate $ each [1..10::Int]
[2,4,6,8,10] :> ([1,3,5,7,9] :> ())

But separate and unseparate are functor-general.

unseparate :: (Monad m, Functor f, Functor g) => Stream f (Stream g m) r -> Stream (Sum f g) m r Source

Assorted Data.Functor.x help

switch :: Sum f g r -> Sum g f r Source

Swap the order of functors in a sum of functors.

>>> S.toListM' $ S.print $ separate $ maps S.switch $ maps (S.distinguish (=='a')) $ S.each "banana"
'a'
'a'
'a'
"bnn" :> ()
>>> S.toListM' $ S.print $ separate $ maps (S.distinguish (=='a')) $ S.each "banana"
'b'
'n'
'n'
"aaa" :> ()

ResourceT help

bracketStream :: (Functor f, MonadResource m) => IO a -> (a -> IO ()) -> (a -> Stream f m b) -> Stream f m b Source

For use in implementation

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

This is akin to the observe of Pipes.Internal . It reeffects the layering in instances of Stream f m r so that it replicates that of FreeT.

hoistExposed :: (Monad m1, Functor f) => (m1 (Stream f m r) -> m (Stream f m r)) -> Stream f m1 r -> Stream f m r Source

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

mapsMExposed :: (Monad m, Functor f1) => (f1 (Stream f m r) -> m (f (Stream f m r))) -> Stream f1 m r -> Stream f m r Source

destroyExposed :: (Monad m, Functor f) => Stream f m t -> (f b -> b) -> (m b -> b) -> (t -> b) -> b Source