{-#LANGUAGE RankNTypes #-} module Streaming ( -- * Free monad transformer -- $stream Stream, -- * Constructing a 'Stream' on a given functor unfold, yields, replicates, repeats, repeatsM, effect, wrap, streamBuild, -- * Transforming streams decompose, maps, mapsM, mapped, distribute, groups, -- * Inspecting a stream inspect, -- * Zipping and unzipping streams zipsWith, zips, unzips, interleaves, separate, unseparate, -- * Eliminating a 'Stream' iterTM, iterT, destroy, streamFold, mapsM_, run, -- * Splitting and joining 'Stream's splitsAt, takes, chunksOf, concats, intercalates, -- period, -- periods, -- * Base functor for streams of individual items Of (..), lazily, strictly, -- * ResourceT help bracketStream, -- * re-exports MFunctor(..), MMonad(..), MonadTrans(..), MonadIO(..), Compose(..), MonadThrow(..), MonadResource(..), MonadBase(..), ResourceT(..), runResourceT, join, liftA2, liftA3, void, ) where import Streaming.Internal import Streaming.Prelude import Control.Monad.Morph import Control.Monad import Control.Applicative import Control.Monad.Trans import Data.Functor.Compose import Control.Monad.Base import Control.Monad.Trans.Resource {- $stream The 'Stream' data type can be used to represent any effectful succession of steps arising in some monad. The form of the steps is specified by the first (\"functor\") parameter in @Stream f m r@, the monad of effects by the second. This module exports combinators that pertain to that general case. Some of these are quite abstract and pervade any use of the library, e.g. > maps :: (forall x . f x -> g x) -> Stream f m r -> Stream g m r > mapped :: (forall x . f x -> m (g x)) -> Stream f m r -> Stream g m r > hoist :: (forall x . m x -> n x) -> Stream f m r -> Stream f n r > concats :: Stream (Stream f m) m r -> Stream f m r (assuming here and thoughout that @m@ or @n@ satisfies a @Monad@ constraint, and @f@ or @g@ a @Functor@ constraint.) Others are surprisingly determinate in content: > chunksOf :: Int -> Stream f m r -> Stream (Stream f m) m r > splits :: One way to see that /any/ streaming library needs some such general type is that it is required to represent the segmentation of a stream, and to express the equivalents of @Prelude/Data.List@ combinators that involve 'lists of lists' and the like. The module @Streaming.Prelude@ exports combinators relating to > Stream (Of a) m r where @Of a r = !a :> r@ is a left-strict pair. > mapped Streaming.Prelude.length :: Stream (Stream (Of a) m) r -> Stream (Of Int) m r -} {-| Map a stream to its church encoding; compare @Data.List.foldr@ This is the @safe_destroy@ exported by the @Internal@ module. Typical @FreeT@ operators can be defined in terms of @destroy@ e.g. > iterT :: (Functor f, Monad m) => (f (m a) -> m a) -> Stream f m a -> m a > iterT out stream = destroy stream out join return > iterTM :: (Functor f, Monad m, MonadTrans t, Monad (t m)) => (f (t m a) -> t m a) -> Stream f m a -> t m a > iterTM out stream = destroy stream out (join . lift) return > concats :: (Monad m, MonadTrans t, Monad (t m)) => Stream (t m) m a -> t m a > concats stream = destroy stream join (join . lift) return -}