-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Dataflow programming and declarative concurrency -- -- Browse the documentation at https://streamly.composewell.com. -- -- Streamly is a streaming framework to build reliable and scalable -- software systems from modular building blocks using dataflow -- programming and declarative concurrency. Stream fusion optimizations -- in streamly result in high-performance, modular combinatorial -- programming. -- -- Performance with simplicity: -- -- -- -- Unified and powerful abstractions: -- -- @package streamly @version 0.8.1.1 -- | Compatibility functions for "base" package. module Streamly.Internal.BaseCompat (#.) :: Coercible b c => (b -> c) -> (a -> b) -> a -> c -- | A variant of error that does not produce a stack trace. errorWithoutStackTrace :: forall (r :: RuntimeRep) (a :: TYPE r). [Char] -> a -- | Return the contents of a Left-value or a default value -- otherwise. -- --

Examples

-- -- Basic usage: -- --
--   >>> fromLeft 1 (Left 3)
--   3
--   
--   >>> fromLeft 1 (Right "foo")
--   1
--   
fromLeft :: a -> Either a b -> a -- | Return the contents of a Right-value or a default value -- otherwise. -- --

Examples

-- -- Basic usage: -- --
--   >>> fromRight 1 (Right 3)
--   3
--   
--   >>> fromRight 1 (Left "foo")
--   1
--   
fromRight :: b -> Either a b -> b unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b oneShot :: (a -> b) -> a -> b module Streamly.Internal.Control.Concurrent -- | A monad that can perform concurrent or parallel IO operations. Streams -- that can be composed concurrently require the underlying monad to be -- MonadAsync. -- -- Since: 0.1.0 (Streamly) type MonadAsync m = (MonadIO m, MonadBaseControl IO m, MonadThrow m) newtype RunInIO m RunInIO :: (forall b. m b -> IO (StM m b)) -> RunInIO m [runInIO] :: RunInIO m -> forall b. m b -> IO (StM m b) -- | When we run computations concurrently, we completely isolate the state -- of the concurrent computations from the parent computation. The -- invariant is that we should never be running two concurrent -- computations in the same thread without using the runInIO function. -- Also, we should never be running a concurrent computation in the -- parent thread, otherwise it may affect the state of the parent which -- is against the defined semantics of concurrent execution. captureMonadState :: MonadBaseControl IO m => m (RunInIO m) -- | Fork a thread to run the given computation, installing the provided -- exception handler. Lifted to any monad with 'MonadBaseControl IO m' -- capability. -- -- TODO: the RunInIO argument can be removed, we can directly pass the -- action as "mrun action" instead. doFork :: MonadBaseControl IO m => m () -> RunInIO m -> (SomeException -> IO ()) -> m ThreadId -- | fork lifted to any monad with 'MonadBaseControl IO m' -- capability. fork :: MonadBaseControl IO m => m () -> m ThreadId -- | Fork a thread that is automatically killed as soon as the reference to -- the returned threadId is garbage collected. forkManaged :: (MonadIO m, MonadBaseControl IO m) => m () -> m ThreadId -- | Additional Control.Exception utilities. module Streamly.Internal.Control.Exception assertM :: Applicative f => Bool -> f () -- | Like assert but is not removed by the compiler, it is always -- present in production code. -- -- Pre-release verify :: Bool -> a -> a verifyM :: Applicative f => Bool -> f () -- | Additional Control.Monad utilities. module Streamly.Internal.Control.Monad -- | Discard any exceptions or value returned by an effectful action. -- -- Pre-release discard :: MonadCatch m => m b -> m () module Streamly.Internal.Data.Atomics atomicModifyIORefCAS :: IORef a -> (a -> (a, b)) -> IO b atomicModifyIORefCAS_ :: IORef t -> (t -> t) -> IO () writeBarrier :: IO () storeLoadBarrier :: IO () -- | Continuation style utilities. module Streamly.Internal.Data.Cont -- | Given a continuation based transformation from a to -- b and a continuation based transformation from [b] -- to c, make continuation based transformation from -- [a] to c. -- -- Pre-release contListMap :: (a -> (b -> r) -> r) -> ([b] -> (c -> r) -> r) -> [a] -> (c -> r) -> r -- | | Strict data types to be used as accumulator for strict left folds -- and scans. For more comprehensive strict data types see -- https://hackage.haskell.org/package/strict-base-types . The -- names have been suffixed by a prime so that programmers can easily -- distinguish the strict versions from the lazy ones. -- -- One major advantage of strict data structures as accumulators in folds -- and scans is that it helps the compiler optimize the code much better -- by unboxing. In a big tight loop the difference could be huge. module Streamly.Internal.Data.Either.Strict -- | A strict Either data Either' a b Left' :: !a -> Either' a b Right' :: !b -> Either' a b -- | Return True if the given value is a Left', False -- otherwise. isLeft' :: Either' a b -> Bool -- | Return True if the given value is a Right', False -- otherwise. isRight' :: Either' a b -> Bool -- | Return the contents of a Left'-value or errors out. fromLeft' :: Either' a b -> a -- | Return the contents of a Right'-value or errors out. fromRight' :: Either' a b -> b instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Streamly.Internal.Data.Either.Strict.Either' a b) module Streamly.Internal.Data.Fold.Step -- | Represents the result of the step of a Fold. -- Partial returns an intermediate state of the fold, the fold -- step can be called again with the state or the driver can use -- extract on the state to get the result out. Done -- returns the final result and the fold cannot be driven further. -- -- Pre-release data Step s b Partial :: !s -> Step s b Done :: !b -> Step s b -- | Map a monadic function over the result b in Step s -- b. -- -- Internal mapMStep :: Applicative m => (a -> m b) -> Step s a -> m (Step s b) -- | If Partial then map the state, if Done then call the -- next step. chainStepM :: Applicative m => (s1 -> m s2) -> (a -> m (Step s2 b)) -> Step s1 a -> m (Step s2 b) instance Data.Bifunctor.Bifunctor Streamly.Internal.Data.Fold.Step.Step instance GHC.Base.Functor (Streamly.Internal.Data.Fold.Step.Step s) -- | A value associated with an IO action that is automatically called -- whenever the value is garbage collected. module Streamly.Internal.Data.IOFinalizer -- | An IOFinalizer has an associated IO action that is -- automatically called whenever the finalizer is garbage collected. The -- action can be run and cleared prematurely. -- -- You can hold a reference to the finalizer in your data structure, if -- the data structure gets garbage collected the finalizer will be -- called. -- -- It is implemented using mkWeakIORef. -- -- Pre-release data IOFinalizer -- | Create a finalizer that calls the supplied function automatically when -- the it is garbage collected. -- -- /The finalizer is always run using the state of the monad that is -- captured at the time of calling newFinalizer./ -- -- Note: To run it on garbage collection we have no option but to use the -- monad state captured at some earlier point of time. For the case when -- the finalizer is run manually before GC we could run it with the -- current state of the monad but we want to keep both the cases -- consistent. -- -- Pre-release newIOFinalizer :: (MonadIO m, MonadBaseControl IO m) => m a -> m IOFinalizer -- | Run the action associated with the finalizer and deactivate it so that -- it never runs again. Note, the finalizing action runs with async -- exceptions masked. -- -- Pre-release runIOFinalizer :: MonadIO m => IOFinalizer -> m () -- | Run an action clearing the finalizer atomically wrt async exceptions. -- The action is run with async exceptions masked. -- -- Pre-release clearingIOFinalizer :: MonadBaseControl IO m => IOFinalizer -> m a -> m a -- | | Strict data types to be used as accumulator for strict left folds -- and scans. For more comprehensive strict data types see -- https://hackage.haskell.org/package/strict-base-types . The -- names have been suffixed by a prime so that programmers can easily -- distinguish the strict versions from the lazy ones. -- -- One major advantage of strict data structures as accumulators in folds -- and scans is that it helps the compiler optimize the code much better -- by unboxing. In a big tight loop the difference could be huge. module Streamly.Internal.Data.Maybe.Strict -- | A strict Maybe data Maybe' a Just' :: !a -> Maybe' a Nothing' :: Maybe' a -- | Convert strict Maybe' to lazy Maybe toMaybe :: Maybe' a -> Maybe a -- | Returns True iff its argument is of the form "Just' _". isJust' :: Maybe' a -> Bool -- | Extract the element out of a Just' and throws an error if its argument -- is Nothing'. fromJust' :: Maybe' a -> a instance GHC.Show.Show a => GHC.Show.Show (Streamly.Internal.Data.Maybe.Strict.Maybe' a) -- | The Fold type embeds a default initial value, therefore, it -- is like a Monoid whereas the Refold type has to be -- supplied with an initial value, therefore, it is more like a -- Semigroup operation. -- -- Refolds can be appended to each other or to a fold to build the fold -- incrementally. This is useful in incremental builder like use cases. -- -- See the file splitting example in the streamly-examples -- repository for an application of the Refold type. The -- Fold type does not perform as well in this situation. -- -- Refold type is to Fold as Unfold type is to -- Stream. Unfold provides better optimizaiton than -- stream in nested operations, similarly, Refold provides better -- optimization than Fold. module Streamly.Internal.Data.Refold.Type -- | Like Fold except that the initial state of the accmulator can -- be generated using a dynamically supplied input. This affords better -- stream fusion optimization in nested fold operations where the initial -- fold state is determined based on a dynamic value. -- -- Internal data Refold m c a b -- | Fold step inject extract Refold :: (s -> a -> m (Step s b)) -> (c -> m (Step s b)) -> (s -> m b) -> Refold m c a b -- | Make a consumer from a left fold style pure step function. -- -- If your Fold returns only Partial (i.e. never returns -- a Done) then you can use foldl'* constructors. -- -- See also: Streamly.Prelude.foldl' -- -- Internal foldl' :: Monad m => (b -> a -> b) -> Refold m b a b -- | Append the elements of an input stream to a provided starting value. -- --
--   >>> stream = Stream.map Data.Monoid.Sum $ Stream.enumerateFromTo 1 10
--   
--   >>> Stream.fold (Fold.fromRefold Refold.sconcat 10) stream
--   Sum {getSum = 65}
--   
-- --
--   >>> sconcat = Refold.foldl' (<>)
--   
-- -- Internal sconcat :: (Monad m, Semigroup a) => Refold m a a a -- | Internal drainBy :: Monad m => (c -> a -> m b) -> Refold m c a () -- | Keep running the same consumer over and over again on the input, -- feeding the output of the previous run to the next. -- -- Internal iterate :: Monad m => Refold m b a b -> Refold m b a b -- | lmapM f fold maps the monadic function f on the -- input of the fold. -- -- Internal lmapM :: Monad m => (a -> m b) -> Refold m c b r -> Refold m c a r -- | Map a monadic function on the output of a fold. -- -- Internal rmapM :: Monad m => (b -> m c) -> Refold m x a b -> Refold m x a c -- | Supply the output of the first consumer as input to the second -- consumer. -- -- Internal append :: Monad m => Refold m x a b -> Refold m b a b -> Refold m x a b -- | Take at most n input elements and fold them using the -- supplied fold. A negative count is treated as 0. -- -- Internal take :: Monad m => Int -> Refold m x a b -> Refold m x a b instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Streamly.Internal.Data.Refold.Type.Tuple'Fused a b) module Streamly.Internal.Data.Ring data Ring a Ring :: MutableArray (PrimState IO) a -> IORef Int -> !Int -> Ring a [arr] :: Ring a -> MutableArray (PrimState IO) a [ringHead] :: Ring a -> IORef Int [ringMax] :: Ring a -> !Int createRing :: Int -> IO (Ring a) unsafeInsertRing :: Ring a -> Int -> a -> IO () module Streamly.Internal.Data.Sink.Type -- | A Sink is a special type of Fold that does not -- accumulate any value, but runs only effects. A Sink has no -- state to maintain therefore can be a bit more efficient than a -- Fold with () as the state, especially when -- Sinks are composed with other operations. A Sink can be -- upgraded to a Fold, but a Fold cannot be converted -- into a Sink. newtype Sink m a Sink :: (a -> m ()) -> Sink m a -- | Small arrays are boxed (im)mutable arrays. -- -- The underlying structure of the Array type contains a card -- table, allowing segments of the array to be marked as having been -- mutated. This allows the garbage collector to only re-traverse -- segments of the array that have been marked during certain phases, -- rather than having to traverse the entire array. -- -- SmallArray lacks this table. This means that it takes up less -- memory and has slightly faster writes. It is also more efficient -- during garbage collection so long as the card table would have a -- single entry covering the entire array. These advantages make them -- suitable for use as arrays that are known to be small. -- -- The card size is 128, so for uses much larger than that, -- Array would likely be superior. -- -- The underlying type, SmallArray#, was introduced in GHC 7.10, -- so prior to that version, this module simply implements small arrays -- as Array. module Streamly.Internal.Data.SmallArray.Type data SmallArray a SmallArray :: SmallArray# a -> SmallArray a data SmallMutableArray s a SmallMutableArray :: SmallMutableArray# s a -> SmallMutableArray s a -- | Create a new small mutable array. newSmallArray :: PrimMonad m => Int -> a -> m (SmallMutableArray (PrimState m) a) -- | Read the element at a given index in a mutable array. readSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> m a -- | Write an element at the given idex in a mutable array. writeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> a -> m () -- | Copy a slice of an immutable array into a mutable array. copySmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> SmallArray a -> Int -> Int -> m () -- | Copy a slice of one mutable array into another. copySmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> SmallMutableArray (PrimState m) a -> Int -> Int -> m () -- | Look up an element in an immutable array. indexSmallArray :: SmallArray a -> Int -> a -- | Look up an element in an immutable array. -- -- The purpose of returning a result using a monad is to allow the caller -- to avoid retaining references to the array. Evaluating the return -- value will cause the array lookup to be performed, even though it may -- not require the element of the array to be evaluated (which could -- throw an exception). For instance: -- --
--   data Box a = Box a
--   ...
--   
--   f sa = case indexSmallArrayM sa 0 of
--     Box x -> ...
--   
-- -- x is not a closure that references sa as it would be -- if we instead wrote: -- --
--   let x = indexSmallArray sa 0
--   
-- -- And does not prevent sa from being garbage collected. -- -- Note that Identity is not adequate for this use, as it is a -- newtype, and cannot be evaluated without evaluating the element. indexSmallArrayM :: Monad m => SmallArray a -> Int -> m a -- | Read a value from the immutable array at the given index, returning -- the result in an unboxed unary tuple. This is currently used to -- implement folds. indexSmallArray## :: SmallArray a -> Int -> (# a #) -- | Create a copy of a slice of an immutable array. cloneSmallArray :: SmallArray a -> Int -> Int -> SmallArray a -- | Create a copy of a slice of a mutable array. cloneSmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> Int -> m (SmallMutableArray (PrimState m) a) -- | Create an immutable array corresponding to a slice of a mutable array. -- -- This operation copies the portion of the array to be frozen. freezeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> Int -> m (SmallArray a) -- | Render a mutable array immutable. -- -- This operation performs no copying, so care must be taken not to -- modify the input array after freezing. unsafeFreezeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> m (SmallArray a) -- | Create a mutable array corresponding to a slice of an immutable array. -- -- This operation copies the portion of the array to be thawed. thawSmallArray :: PrimMonad m => SmallArray a -> Int -> Int -> m (SmallMutableArray (PrimState m) a) runSmallArray :: (forall s. ST s (SmallMutableArray s a)) -> SmallArray a -- | Render an immutable array mutable. -- -- This operation performs no copying, so care must be taken with its -- use. unsafeThawSmallArray :: PrimMonad m => SmallArray a -> m (SmallMutableArray (PrimState m) a) sizeofSmallArray :: SmallArray a -> Int sizeofSmallMutableArray :: SmallMutableArray s a -> Int -- | Create a SmallArray from a list. smallArrayFromList :: [a] -> SmallArray a -- | Create a SmallArray from a list of a known length. If the -- length of the list does not match the given length, this throws an -- exception. smallArrayFromListN :: Int -> [a] -> SmallArray a -- | Strict map over the elements of the array. mapSmallArray' :: (a -> b) -> SmallArray a -> SmallArray b -- | This is the fastest, most straightforward way to traverse an array, -- but it only works correctly with a sufficiently "affine" -- PrimMonad instance. In particular, it must only produce *one* -- result array. ListT-transformed monads, for example, will not -- work right at all. traverseSmallArrayP :: PrimMonad m => (a -> m b) -> SmallArray a -> m (SmallArray b) instance GHC.Base.Monad Streamly.Internal.Data.SmallArray.Type.SmallArray instance GHC.Classes.Eq (Streamly.Internal.Data.SmallArray.Type.SmallMutableArray s a) instance (Data.Typeable.Internal.Typeable s, Data.Typeable.Internal.Typeable a) => Data.Data.Data (Streamly.Internal.Data.SmallArray.Type.SmallMutableArray s a) instance Data.Functor.Classes.Eq1 Streamly.Internal.Data.SmallArray.Type.SmallArray instance GHC.Classes.Eq a => GHC.Classes.Eq (Streamly.Internal.Data.SmallArray.Type.SmallArray a) instance Data.Functor.Classes.Ord1 Streamly.Internal.Data.SmallArray.Type.SmallArray instance GHC.Classes.Ord a => GHC.Classes.Ord (Streamly.Internal.Data.SmallArray.Type.SmallArray a) instance Data.Foldable.Foldable Streamly.Internal.Data.SmallArray.Type.SmallArray instance Data.Traversable.Traversable Streamly.Internal.Data.SmallArray.Type.SmallArray instance GHC.Base.Functor Streamly.Internal.Data.SmallArray.Type.SmallArray instance GHC.Base.Applicative Streamly.Internal.Data.SmallArray.Type.SmallArray instance GHC.Base.Alternative Streamly.Internal.Data.SmallArray.Type.SmallArray instance Control.Monad.Fail.MonadFail Streamly.Internal.Data.SmallArray.Type.SmallArray instance GHC.Base.MonadPlus Streamly.Internal.Data.SmallArray.Type.SmallArray instance Control.Monad.Zip.MonadZip Streamly.Internal.Data.SmallArray.Type.SmallArray instance Control.Monad.Fix.MonadFix Streamly.Internal.Data.SmallArray.Type.SmallArray instance GHC.Base.Semigroup (Streamly.Internal.Data.SmallArray.Type.SmallArray a) instance GHC.Base.Monoid (Streamly.Internal.Data.SmallArray.Type.SmallArray a) instance GHC.Exts.IsList (Streamly.Internal.Data.SmallArray.Type.SmallArray a) instance GHC.Show.Show a => GHC.Show.Show (Streamly.Internal.Data.SmallArray.Type.SmallArray a) instance Data.Functor.Classes.Show1 Streamly.Internal.Data.SmallArray.Type.SmallArray instance GHC.Read.Read a => GHC.Read.Read (Streamly.Internal.Data.SmallArray.Type.SmallArray a) instance Data.Functor.Classes.Read1 Streamly.Internal.Data.SmallArray.Type.SmallArray instance Data.Data.Data a => Data.Data.Data (Streamly.Internal.Data.SmallArray.Type.SmallArray a) module Streamly.Internal.Data.Stream.StreamD.Step -- | A stream is a succession of Steps. A Yield produces a -- single value and the next state of the stream. Stop indicates -- there are no more values in the stream. data Step s a Yield :: a -> s -> Step s a Skip :: s -> Step s a Stop :: Step s a instance GHC.Base.Functor (Streamly.Internal.Data.Stream.StreamD.Step.Step s) -- | See Streamly.Internal.Data.Producer for introduction. module Streamly.Internal.Data.Producer.Type -- | A Producer m a b is a generator of a stream of values of type -- b from a seed of type a in Monad m. -- -- Pre-release data Producer m a b -- |
--   Producer step inject extract
--   
Producer :: (s -> m (Step s b)) -> (a -> m s) -> (s -> m a) -> Producer m a b nil :: Monad m => Producer m a b nilM :: Monad m => (a -> m c) -> Producer m a b unfoldrM :: Monad m => (a -> m (Maybe (b, a))) -> Producer m a b -- | Convert a list of pure values to a Stream -- -- Pre-release fromList :: Monad m => Producer m [a] a -- | Interconvert the producer between two interconvertible input types. -- -- Pre-release translate :: Functor m => (a -> c) -> (c -> a) -> Producer m c b -> Producer m a b -- | Map the producer input to another value of the same type. -- -- Pre-release lmap :: (a -> a) -> Producer m a b -> Producer m a b -- | State representing a nested loop. data NestedLoop s1 s2 OuterLoop :: s1 -> NestedLoop s1 s2 InnerLoop :: s1 -> s2 -> NestedLoop s1 s2 -- | Apply the second unfold to each output element of the first unfold and -- flatten the output in a single stream. -- -- Pre-release concat :: Monad m => Producer m a b -> Producer m b c -> Producer m (NestedLoop a b) c instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Producer.Type.Producer m a) -- | A CPS style stream using a constructor based representation instead of -- a function based representation. -- -- Streamly internally uses two fundamental stream representations, (1) -- streams with an open or arbitrary control flow (we call it StreamK), -- (2) streams with a structured or closed loop control flow (we call it -- StreamD). The higher level stream types can use any of these -- representations under the hood and can interconvert between the two. -- -- StreamD: -- -- StreamD is a non-recursive data type in which the state of the stream -- and the step function are separate. When the step function is called, -- a stream element and the new stream state is yielded. The generated -- element and the state are passed to the next consumer in the loop. The -- state is threaded around in the loop until control returns back to the -- original step function to run the next step. This creates a structured -- closed loop representation (like "for" loops in C) with state of each -- step being hidden/abstracted or existential within that step. This -- creates a loop representation identical to the "for" or "while" loop -- constructs in imperative languages, the states of the steps combined -- together constitute the state of the loop iteration. -- -- Internally most combinators use a closed loop representation because -- it provides very high efficiency due to stream fusion. The performance -- of this representation is competitive to the C language -- implementations. -- -- Pros and Cons of StreamD: -- -- 1) stream-fusion: This representation can be optimized very -- efficiently by the compiler because the state is explicitly separated -- from step functions, represented using pure data constructors and -- visible to the compiler, the stream steps can be fused using -- case-of-case transformations and the state can be specialized using -- spec-constructor optimization, yielding a C like tight loop/state -- machine with no constructors, the state is used unboxed and therefore -- no unnecessary allocation. -- -- 2) Because of a closed representation consing too many elements in -- this type of stream does not scale, it will have quadratic performance -- slowdown. Each cons creates a layer that needs to return the control -- back to the caller. Another implementation of cons is possible but -- that will have to box/unbox the state and will not fuse. So -- effectively cons breaks fusion. -- -- 3) unconsing an item from the stream breaks fusion, we have to "pause" -- the loop, rebox and save the state. -- -- 3) Exception handling is easy to implement in this model because -- control flow is structured in the loop and cannot be arbitrary. -- Therefore, implementing "bracket" is natural. -- -- 4) Round-robin scheduling for co-operative multitasking is easy to -- implement. -- -- 5) It fuses well with the direct style Fold implementation. -- -- StreamK/StreamDK: -- -- StreamDK i.e. the stream defined in this module, like StreamK, is a -- recursive data type which has no explicit state defined using -- constructors, each step yields an element and a computation -- representing the rest of the stream. Stream state is part of the -- function representing the rest of the stream. This creates an open -- computation representation, or essentially a continuation passing -- style computation. After the stream step is executed, the caller is -- free to consume the produced element and then send the control -- wherever it wants, there is no restriction on the control to return -- back somewhere, the control is free to go anywhere. The caller may -- decide not to consume the rest of the stream. This representation is -- more like a "goto" based implementation in imperative languages. -- -- Pros and Cons of StreamK: -- -- 1) The way StreamD can be optimized using stream-fusion, this type can -- be optimized using foldrbuild fusion. However, foldrbuild has -- not yet been fully implemented for StreamK/StreamDK. -- -- 2) Using cons is natural in this representation, unlike in StreamD it -- does not have a quadratic slowdown. Currently, we in fact wrap StreamD -- in StreamK to support a better cons operation. -- -- 3) Similarly, uncons is natural in this representation. -- -- 4) Exception handling is not easy to implement because of the "goto" -- nature of CPS. -- -- 5) Composable folds are not implemented/proven, however, intuition -- says that a push style CPS representation should be able to be used -- along with StreamK to efficiently implement composable folds. module Streamly.Internal.Data.Stream.StreamDK.Type data Step m a Yield :: a -> Stream m a -> Step m a Stop :: Step m a newtype Stream m a Stream :: m (Step m a) -> Stream m a module Streamly.Internal.Data.Stream.StreamDK data Stream m a data Step m a Yield :: a -> Stream m a -> Step m a Stop :: Step m a nil :: Monad m => Stream m a cons :: Monad m => a -> Stream m a -> Stream m a consM :: Monad m => m a -> Stream m a -> Stream m a unfoldr :: Monad m => (b -> Maybe (a, b)) -> b -> Stream m a unfoldrM :: Monad m => (s -> m (Maybe (a, s))) -> s -> Stream m a replicateM :: Monad m => Int -> a -> Stream m a uncons :: Monad m => Stream m a -> m (Maybe (a, Stream m a)) -- | Lazy right associative fold to a stream. foldrS :: Monad m => (a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b drain :: Monad m => Stream m a -> m () -- | Time utilities for reactive programming. -- | Deprecated: Please use the "rate" combinator instead of the -- functions in this module module Streamly.Internal.Data.Time -- | Run an action forever periodically at the given frequency specified in -- per second (Hz). periodic :: Int -> IO () -> IO () -- | Run a computation on every clock tick, the clock runs at the specified -- frequency. It allows running a computation at high frequency -- efficiently by maintaining a local clock and adjusting it with the -- provided base clock at longer intervals. The first argument is a base -- clock returning some notion of time in microseconds. The second -- argument is the frequency in per second (Hz). The third argument is -- the action to run, the action is provided the local time as an -- argument. withClock :: IO Int -> Int -> (Int -> IO ()) -> IO () module Streamly.Internal.Data.Time.TimeSpec -- | Data type to represent practically large quantities of time -- efficiently. It can represent time up to ~292 billion years at -- nanosecond resolution. data TimeSpec TimeSpec :: {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> TimeSpec -- | seconds [sec] :: TimeSpec -> {-# UNPACK #-} !Int64 -- | nanoseconds [nsec] :: TimeSpec -> {-# UNPACK #-} !Int64 instance GHC.Show.Show Streamly.Internal.Data.Time.TimeSpec.TimeSpec instance GHC.Read.Read Streamly.Internal.Data.Time.TimeSpec.TimeSpec instance GHC.Classes.Eq Streamly.Internal.Data.Time.TimeSpec.TimeSpec instance GHC.Classes.Ord Streamly.Internal.Data.Time.TimeSpec.TimeSpec instance GHC.Num.Num Streamly.Internal.Data.Time.TimeSpec.TimeSpec instance Foreign.Storable.Storable Streamly.Internal.Data.Time.TimeSpec.TimeSpec module Streamly.Internal.Data.Time.Units -- | A type class for converting between time units using Integer as -- the intermediate and the widest representation with a nanosecond -- resolution. This system of units can represent arbitrarily large times -- but provides least efficient arithmetic operations due to -- Integer arithmetic. -- -- NOTE: Converting to and from units may truncate the value depending on -- the original value and the size and resolution of the destination -- unit. -- -- A type class for converting between units of time using -- TimeSpec as the intermediate representation. This system of -- units can represent up to ~292 billion years at nanosecond resolution -- with reasonably efficient arithmetic operations. -- -- NOTE: Converting to and from units may truncate the value depending on -- the original value and the size and resolution of the destination -- unit. class TimeUnit a -- | A type class for converting between units of time using Int64 -- as the intermediate representation with a nanosecond resolution. This -- system of units can represent up to ~292 years at nanosecond -- resolution with fast arithmetic operations. -- -- NOTE: Converting to and from units may truncate the value depending on -- the original value and the size and resolution of the destination -- unit. class TimeUnit64 a -- | Data type to represent practically large quantities of time -- efficiently. It can represent time up to ~292 billion years at -- nanosecond resolution. data TimeSpec TimeSpec :: {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> TimeSpec -- | seconds [sec] :: TimeSpec -> {-# UNPACK #-} !Int64 -- | nanoseconds [nsec] :: TimeSpec -> {-# UNPACK #-} !Int64 -- | An Int64 time representation with a nanosecond resolution. It -- can represent time up to ~292 years. newtype NanoSecond64 NanoSecond64 :: Int64 -> NanoSecond64 -- | An Int64 time representation with a microsecond resolution. It -- can represent time up to ~292,000 years. newtype MicroSecond64 MicroSecond64 :: Int64 -> MicroSecond64 -- | An Int64 time representation with a millisecond resolution. It -- can represent time up to ~292 million years. newtype MilliSecond64 MilliSecond64 :: Int64 -> MilliSecond64 -- | Convert nanoseconds to a string showing time in an appropriate unit. showNanoSecond64 :: NanoSecond64 -> String -- | Absolute times are relative to a predefined epoch in time. -- AbsTime represents times using TimeSpec which can -- represent times up to ~292 billion years at a nanosecond resolution. newtype AbsTime AbsTime :: TimeSpec -> AbsTime -- | Convert a TimeUnit to an absolute time. toAbsTime :: TimeUnit a => a -> AbsTime -- | Convert absolute time to a TimeUnit. fromAbsTime :: TimeUnit a => AbsTime -> a data RelTime toRelTime :: TimeUnit a => a -> RelTime fromRelTime :: TimeUnit a => RelTime -> a diffAbsTime :: AbsTime -> AbsTime -> RelTime addToAbsTime :: AbsTime -> RelTime -> AbsTime -- | Relative times are relative to some arbitrary point of time. Unlike -- AbsTime they are not relative to a predefined epoch. data RelTime64 -- | Convert a TimeUnit to a relative time. toRelTime64 :: TimeUnit64 a => a -> RelTime64 -- | Convert relative time to a TimeUnit. fromRelTime64 :: TimeUnit64 a => RelTime64 -> a -- | Difference between two absolute points of time. diffAbsTime64 :: AbsTime -> AbsTime -> RelTime64 addToAbsTime64 :: AbsTime -> RelTime64 -> AbsTime showRelTime64 :: RelTime64 -> String instance Data.Primitive.Types.Prim Streamly.Internal.Data.Time.Units.NanoSecond64 instance GHC.Classes.Ord Streamly.Internal.Data.Time.Units.NanoSecond64 instance GHC.Real.Integral Streamly.Internal.Data.Time.Units.NanoSecond64 instance GHC.Real.Real Streamly.Internal.Data.Time.Units.NanoSecond64 instance GHC.Num.Num Streamly.Internal.Data.Time.Units.NanoSecond64 instance GHC.Enum.Bounded Streamly.Internal.Data.Time.Units.NanoSecond64 instance GHC.Enum.Enum Streamly.Internal.Data.Time.Units.NanoSecond64 instance GHC.Show.Show Streamly.Internal.Data.Time.Units.NanoSecond64 instance GHC.Read.Read Streamly.Internal.Data.Time.Units.NanoSecond64 instance GHC.Classes.Eq Streamly.Internal.Data.Time.Units.NanoSecond64 instance Data.Primitive.Types.Prim Streamly.Internal.Data.Time.Units.MicroSecond64 instance GHC.Classes.Ord Streamly.Internal.Data.Time.Units.MicroSecond64 instance GHC.Real.Integral Streamly.Internal.Data.Time.Units.MicroSecond64 instance GHC.Real.Real Streamly.Internal.Data.Time.Units.MicroSecond64 instance GHC.Num.Num Streamly.Internal.Data.Time.Units.MicroSecond64 instance GHC.Enum.Bounded Streamly.Internal.Data.Time.Units.MicroSecond64 instance GHC.Enum.Enum Streamly.Internal.Data.Time.Units.MicroSecond64 instance GHC.Show.Show Streamly.Internal.Data.Time.Units.MicroSecond64 instance GHC.Read.Read Streamly.Internal.Data.Time.Units.MicroSecond64 instance GHC.Classes.Eq Streamly.Internal.Data.Time.Units.MicroSecond64 instance Data.Primitive.Types.Prim Streamly.Internal.Data.Time.Units.MilliSecond64 instance GHC.Classes.Ord Streamly.Internal.Data.Time.Units.MilliSecond64 instance GHC.Real.Integral Streamly.Internal.Data.Time.Units.MilliSecond64 instance GHC.Real.Real Streamly.Internal.Data.Time.Units.MilliSecond64 instance GHC.Num.Num Streamly.Internal.Data.Time.Units.MilliSecond64 instance GHC.Enum.Bounded Streamly.Internal.Data.Time.Units.MilliSecond64 instance GHC.Enum.Enum Streamly.Internal.Data.Time.Units.MilliSecond64 instance GHC.Show.Show Streamly.Internal.Data.Time.Units.MilliSecond64 instance GHC.Read.Read Streamly.Internal.Data.Time.Units.MilliSecond64 instance GHC.Classes.Eq Streamly.Internal.Data.Time.Units.MilliSecond64 instance GHC.Show.Show Streamly.Internal.Data.Time.Units.AbsTime instance GHC.Classes.Ord Streamly.Internal.Data.Time.Units.AbsTime instance GHC.Classes.Eq Streamly.Internal.Data.Time.Units.AbsTime instance GHC.Classes.Ord Streamly.Internal.Data.Time.Units.RelTime64 instance GHC.Real.Integral Streamly.Internal.Data.Time.Units.RelTime64 instance GHC.Real.Real Streamly.Internal.Data.Time.Units.RelTime64 instance GHC.Num.Num Streamly.Internal.Data.Time.Units.RelTime64 instance GHC.Enum.Bounded Streamly.Internal.Data.Time.Units.RelTime64 instance GHC.Enum.Enum Streamly.Internal.Data.Time.Units.RelTime64 instance GHC.Show.Show Streamly.Internal.Data.Time.Units.RelTime64 instance GHC.Read.Read Streamly.Internal.Data.Time.Units.RelTime64 instance GHC.Classes.Eq Streamly.Internal.Data.Time.Units.RelTime64 instance GHC.Classes.Ord Streamly.Internal.Data.Time.Units.RelTime instance GHC.Num.Num Streamly.Internal.Data.Time.Units.RelTime instance GHC.Show.Show Streamly.Internal.Data.Time.Units.RelTime instance GHC.Read.Read Streamly.Internal.Data.Time.Units.RelTime instance GHC.Classes.Eq Streamly.Internal.Data.Time.Units.RelTime instance Streamly.Internal.Data.Time.Units.TimeUnit64 Streamly.Internal.Data.Time.Units.NanoSecond64 instance Streamly.Internal.Data.Time.Units.TimeUnit64 Streamly.Internal.Data.Time.Units.MicroSecond64 instance Streamly.Internal.Data.Time.Units.TimeUnit64 Streamly.Internal.Data.Time.Units.MilliSecond64 instance Streamly.Internal.Data.Time.Units.TimeUnit Streamly.Internal.Data.Time.TimeSpec.TimeSpec instance Streamly.Internal.Data.Time.Units.TimeUnit Streamly.Internal.Data.Time.Units.NanoSecond64 instance Streamly.Internal.Data.Time.Units.TimeUnit Streamly.Internal.Data.Time.Units.MicroSecond64 instance Streamly.Internal.Data.Time.Units.TimeUnit Streamly.Internal.Data.Time.Units.MilliSecond64 module Streamly.Internal.Data.Time.Clock.Type -- | Clock types. A clock may be system-wide (that is, visible to all -- processes) or per-process (measuring time that is meaningful only -- within a process). All implementations shall support CLOCK_REALTIME. -- (The only suspend-aware monotonic is CLOCK_BOOTTIME on Linux.) data Clock -- | The identifier for the system-wide monotonic clock, which is defined -- as a clock measuring real time, whose value cannot be set via -- clock_settime and which cannot have negative clock jumps. The -- maximum possible clock jump shall be implementation defined. For this -- clock, the value returned by getTime represents the amount of -- time (in seconds and nanoseconds) since an unspecified point in the -- past (for example, system start-up time, or the Epoch). This point -- does not change after system start-up time. Note that the absolute -- value of the monotonic clock is meaningless (because its origin is -- arbitrary), and thus there is no need to set it. Furthermore, realtime -- applications can rely on the fact that the value of this clock is -- never set. Monotonic :: Clock -- | The identifier of the system-wide clock measuring real time. For this -- clock, the value returned by getTime represents the amount of -- time (in seconds and nanoseconds) since the Epoch. Realtime :: Clock -- | The identifier of the CPU-time clock associated with the calling -- process. For this clock, the value returned by getTime -- represents the amount of execution time of the current process. ProcessCPUTime :: Clock -- | The identifier of the CPU-time clock associated with the calling OS -- thread. For this clock, the value returned by getTime -- represents the amount of execution time of the current OS thread. ThreadCPUTime :: Clock -- | (since Linux 2.6.28; Linux and Mac OSX) Similar to CLOCK_MONOTONIC, -- but provides access to a raw hardware-based time that is not subject -- to NTP adjustments or the incremental adjustments performed by -- adjtime(3). MonotonicRaw :: Clock -- | (since Linux 2.6.32; Linux and Mac OSX) A faster but less precise -- version of CLOCK_MONOTONIC. Use when you need very fast, but not -- fine-grained timestamps. MonotonicCoarse :: Clock -- | (since Linux 2.6.39; Linux and Mac OSX) Identical to CLOCK_MONOTONIC, -- except it also includes any time that the system is suspended. This -- allows applications to get a suspend-aware monotonic clock without -- having to deal with the complications of CLOCK_REALTIME, which may -- have discontinuities if the time is changed using settimeofday(2). Uptime :: Clock -- | (since Linux 2.6.32; Linux-specific) A faster but less precise version -- of CLOCK_REALTIME. Use when you need very fast, but not fine-grained -- timestamps. RealtimeCoarse :: Clock getTime :: Clock -> IO AbsTime instance GHC.Show.Show Streamly.Internal.Data.Time.Clock.Type.Clock instance GHC.Read.Read Streamly.Internal.Data.Time.Clock.Type.Clock instance GHC.Generics.Generic Streamly.Internal.Data.Time.Clock.Type.Clock instance GHC.Enum.Enum Streamly.Internal.Data.Time.Clock.Type.Clock instance GHC.Classes.Eq Streamly.Internal.Data.Time.Clock.Type.Clock module Streamly.Internal.Data.SVar.Type data ThreadAbort ThreadAbort :: ThreadAbort -- | Events that a child thread may send to a parent thread. data ChildEvent a ChildYield :: a -> ChildEvent a ChildStop :: ThreadId -> Maybe SomeException -> ChildEvent a -- | Sorting out-of-turn outputs in a heap for Ahead style streams data AheadHeapEntry (t :: (Type -> Type) -> Type -> Type) m a AheadEntryNull :: AheadHeapEntry (t :: (Type -> Type) -> Type -> Type) m a AheadEntryPure :: a -> AheadHeapEntry (t :: (Type -> Type) -> Type -> Type) m a AheadEntryStream :: (RunInIO m, t m a) -> AheadHeapEntry (t :: (Type -> Type) -> Type -> Type) m a newtype Count Count :: Int64 -> Count data Limit Unlimited :: Limit Limited :: Word -> Limit -- | Identify the type of the SVar. Two computations using the same style -- can be scheduled on the same SVar. data SVarStyle AsyncVar :: SVarStyle WAsyncVar :: SVarStyle ParallelVar :: SVarStyle AheadVar :: SVarStyle data SVarStopStyle StopNone :: SVarStopStyle StopAny :: SVarStopStyle StopBy :: SVarStopStyle data SVarStats SVarStats :: IORef Int -> IORef Int -> IORef Int -> IORef Int -> IORef Int -> IORef (Count, NanoSecond64) -> IORef NanoSecond64 -> IORef NanoSecond64 -> IORef (Maybe AbsTime) -> SVarStats [totalDispatches] :: SVarStats -> IORef Int [maxWorkers] :: SVarStats -> IORef Int [maxOutQSize] :: SVarStats -> IORef Int [maxHeapSize] :: SVarStats -> IORef Int [maxWorkQSize] :: SVarStats -> IORef Int [avgWorkerLatency] :: SVarStats -> IORef (Count, NanoSecond64) [minWorkerLatency] :: SVarStats -> IORef NanoSecond64 [maxWorkerLatency] :: SVarStats -> IORef NanoSecond64 [svarStopTime] :: SVarStats -> IORef (Maybe AbsTime) -- | An SVar or a Stream Var is a conduit to the output from multiple -- streams running concurrently and asynchronously. An SVar can be -- thought of as an asynchronous IO handle. We can write any number of -- streams to an SVar in a non-blocking manner and then read them back at -- any time at any pace. The SVar would run the streams asynchronously -- and accumulate results. An SVar may not really execute the stream -- completely and accumulate all the results. However, it ensures that -- the reader can read the results at whatever paces it wants to read. -- The SVar monitors and adapts to the consumer's pace. -- -- An SVar is a mini scheduler, it has an associated workLoop that holds -- the stream tasks to be picked and run by a pool of worker threads. It -- has an associated output queue where the output stream elements are -- placed by the worker threads. A outputDoorBell is used by the worker -- threads to intimate the consumer thread about availability of new -- results in the output queue. More workers are added to the SVar by -- fromStreamVar on demand if the output produced is not keeping -- pace with the consumer. On bounded SVars, workers block on the output -- queue to provide throttling of the producer when the consumer is not -- pulling fast enough. The number of workers may even get reduced -- depending on the consuming pace. -- -- New work is enqueued either at the time of creation of the SVar or as -- a result of executing the parallel combinators i.e. <| and -- <|> when the already enqueued computations get -- evaluated. See joinStreamVarAsync. data WorkerInfo WorkerInfo :: Count -> IORef Count -> IORef (Count, AbsTime) -> WorkerInfo [workerYieldMax] :: WorkerInfo -> Count [workerYieldCount] :: WorkerInfo -> IORef Count [workerLatencyStart] :: WorkerInfo -> IORef (Count, AbsTime) -- | Buffering policy for persistent push workers (in ParallelT). In a pull -- style SVar (in AsyncT, AheadT etc.), the consumer side dispatches -- workers on demand, workers terminate if the buffer is full or if the -- consumer is not cosuming fast enough. In a push style SVar, a worker -- is dispatched only once, workers are persistent and keep pushing work -- to the consumer via a bounded buffer. If the buffer becomes full the -- worker either blocks, or it can drop an item from the buffer to make -- space. -- -- Pull style SVars are useful in lazy stream evaluation whereas push -- style SVars are useful in strict left Folds. -- -- XXX Maybe we can separate the implementation in two different types -- instead of using a common SVar type. data PushBufferPolicy PushBufferDropNew :: PushBufferPolicy PushBufferDropOld :: PushBufferPolicy PushBufferBlock :: PushBufferPolicy data LatencyRange LatencyRange :: NanoSecond64 -> NanoSecond64 -> LatencyRange [minLatency] :: LatencyRange -> NanoSecond64 [maxLatency] :: LatencyRange -> NanoSecond64 data YieldRateInfo YieldRateInfo :: NanoSecond64 -> LatencyRange -> Int -> IORef Count -> IORef (Count, AbsTime) -> Maybe NanoSecond64 -> IORef Count -> IORef (Count, Count, NanoSecond64) -> IORef (Count, Count, NanoSecond64) -> IORef NanoSecond64 -> YieldRateInfo [svarLatencyTarget] :: YieldRateInfo -> NanoSecond64 [svarLatencyRange] :: YieldRateInfo -> LatencyRange [svarRateBuffer] :: YieldRateInfo -> Int [svarGainedLostYields] :: YieldRateInfo -> IORef Count [svarAllTimeLatency] :: YieldRateInfo -> IORef (Count, AbsTime) [workerBootstrapLatency] :: YieldRateInfo -> Maybe NanoSecond64 [workerPollingInterval] :: YieldRateInfo -> IORef Count [workerPendingLatency] :: YieldRateInfo -> IORef (Count, Count, NanoSecond64) [workerCollectedLatency] :: YieldRateInfo -> IORef (Count, Count, NanoSecond64) [workerMeasuredLatency] :: YieldRateInfo -> IORef NanoSecond64 data SVar t m a SVar :: SVarStyle -> RunInIO m -> SVarStopStyle -> IORef ThreadId -> IORef ([ChildEvent a], Int) -> MVar () -> m [ChildEvent a] -> m Bool -> IORef ([ChildEvent a], Int) -> MVar () -> Limit -> Limit -> IORef Count -> PushBufferPolicy -> MVar () -> Maybe (IORef Count) -> Maybe YieldRateInfo -> ((RunInIO m, t m a) -> IO ()) -> IO Bool -> IO Bool -> IORef Bool -> (Maybe WorkerInfo -> m ()) -> IORef (Set ThreadId) -> IORef Int -> (ThreadId -> m ()) -> MVar () -> SVarStats -> Maybe (IORef ()) -> Bool -> ThreadId -> IORef (Heap (Entry Int (AheadHeapEntry t m a)), Maybe Int) -> IORef ([t m a], Int) -> SVar t m a [svarStyle] :: SVar t m a -> SVarStyle [svarMrun] :: SVar t m a -> RunInIO m [svarStopStyle] :: SVar t m a -> SVarStopStyle [svarStopBy] :: SVar t m a -> IORef ThreadId [outputQueue] :: SVar t m a -> IORef ([ChildEvent a], Int) [outputDoorBell] :: SVar t m a -> MVar () [readOutputQ] :: SVar t m a -> m [ChildEvent a] [postProcess] :: SVar t m a -> m Bool [outputQueueFromConsumer] :: SVar t m a -> IORef ([ChildEvent a], Int) [outputDoorBellFromConsumer] :: SVar t m a -> MVar () [maxWorkerLimit] :: SVar t m a -> Limit [maxBufferLimit] :: SVar t m a -> Limit [pushBufferSpace] :: SVar t m a -> IORef Count [pushBufferPolicy] :: SVar t m a -> PushBufferPolicy [pushBufferMVar] :: SVar t m a -> MVar () [remainingWork] :: SVar t m a -> Maybe (IORef Count) [yieldRateInfo] :: SVar t m a -> Maybe YieldRateInfo [enqueue] :: SVar t m a -> (RunInIO m, t m a) -> IO () [isWorkDone] :: SVar t m a -> IO Bool [isQueueDone] :: SVar t m a -> IO Bool [needDoorBell] :: SVar t m a -> IORef Bool [workLoop] :: SVar t m a -> Maybe WorkerInfo -> m () [workerThreads] :: SVar t m a -> IORef (Set ThreadId) [workerCount] :: SVar t m a -> IORef Int [accountThread] :: SVar t m a -> ThreadId -> m () [workerStopMVar] :: SVar t m a -> MVar () [svarStats] :: SVar t m a -> SVarStats [svarRef] :: SVar t m a -> Maybe (IORef ()) [svarInspectMode] :: SVar t m a -> Bool [svarCreator] :: SVar t m a -> ThreadId [outputHeap] :: SVar t m a -> IORef (Heap (Entry Int (AheadHeapEntry t m a)), Maybe Int) [aheadWorkQueue] :: SVar t m a -> IORef ([t m a], Int) -- | Specifies the stream yield rate in yields per second (Hertz). -- We keep accumulating yield credits at rateGoal. At any point of -- time we allow only as many yields as we have accumulated as per -- rateGoal since the start of time. If the consumer or the -- producer is slower or faster, the actual rate may fall behind or -- exceed rateGoal. We try to recover the gap between the two by -- increasing or decreasing the pull rate from the producer. However, if -- the gap becomes more than rateBuffer we try to recover only as -- much as rateBuffer. -- -- rateLow puts a bound on how low the instantaneous rate can go -- when recovering the rate gap. In other words, it determines the -- maximum yield latency. Similarly, rateHigh puts a bound on how -- high the instantaneous rate can go when recovering the rate gap. In -- other words, it determines the minimum yield latency. We reduce the -- latency by increasing concurrency, therefore we can say that it puts -- an upper bound on concurrency. -- -- If the rateGoal is 0 or negative the stream never yields a -- value. If the rateBuffer is 0 or negative we do not attempt to -- recover. -- -- Since: 0.5.0 (Streamly) data Rate Rate :: Double -> Double -> Double -> Int -> Rate -- | The lower rate limit [rateLow] :: Rate -> Double -- | The target rate we want to achieve [rateGoal] :: Rate -> Double -- | The upper rate limit [rateHigh] :: Rate -> Double -- | Maximum slack from the goal [rateBuffer] :: Rate -> Int data State t m a magicMaxBuffer :: Word defState :: State t m a -- | Adapt the stream state from one type to another. adaptState :: State t m a -> State t n b getMaxThreads :: State t m a -> Limit setMaxThreads :: Int -> State t m a -> State t m a getMaxBuffer :: State t m a -> Limit setMaxBuffer :: Int -> State t m a -> State t m a getStreamRate :: State t m a -> Maybe Rate setStreamRate :: Maybe Rate -> State t m a -> State t m a getStreamLatency :: State t m a -> Maybe NanoSecond64 setStreamLatency :: Int -> State t m a -> State t m a getYieldLimit :: State t m a -> Maybe Count setYieldLimit :: Maybe Int64 -> State t m a -> State t m a getInspectMode :: State t m a -> Bool setInspectMode :: State t m a -> State t m a instance GHC.Classes.Ord Streamly.Internal.Data.SVar.Type.Count instance GHC.Real.Integral Streamly.Internal.Data.SVar.Type.Count instance GHC.Real.Real Streamly.Internal.Data.SVar.Type.Count instance GHC.Num.Num Streamly.Internal.Data.SVar.Type.Count instance GHC.Enum.Bounded Streamly.Internal.Data.SVar.Type.Count instance GHC.Enum.Enum Streamly.Internal.Data.SVar.Type.Count instance GHC.Show.Show Streamly.Internal.Data.SVar.Type.Count instance GHC.Read.Read Streamly.Internal.Data.SVar.Type.Count instance GHC.Classes.Eq Streamly.Internal.Data.SVar.Type.Count instance GHC.Show.Show Streamly.Internal.Data.SVar.Type.ThreadAbort instance GHC.Show.Show Streamly.Internal.Data.SVar.Type.SVarStyle instance GHC.Classes.Eq Streamly.Internal.Data.SVar.Type.SVarStyle instance GHC.Show.Show Streamly.Internal.Data.SVar.Type.LatencyRange instance GHC.Show.Show Streamly.Internal.Data.SVar.Type.Limit instance GHC.Show.Show Streamly.Internal.Data.SVar.Type.SVarStopStyle instance GHC.Classes.Eq Streamly.Internal.Data.SVar.Type.SVarStopStyle instance GHC.Classes.Eq Streamly.Internal.Data.SVar.Type.Limit instance GHC.Classes.Ord Streamly.Internal.Data.SVar.Type.Limit instance GHC.Exception.Type.Exception Streamly.Internal.Data.SVar.Type.ThreadAbort -- | Continuation passing style (CPS) stream implementation. The symbol -- K below denotes a function as well as a Kontinuation. module Streamly.Internal.Data.Stream.StreamK.Type -- | The type Stream m a represents a monadic stream of values of -- type a constructed using actions in monad m. It uses -- stop, singleton and yield continuations equivalent to the following -- direct style type: -- --
--   data Stream m a = Stop | Singleton a | Yield a (Stream m a)
--   
-- -- To facilitate parallel composition we maintain a local state in an -- SVar that is shared across and is used for synchronization of -- the streams being composed. -- -- The singleton case can be expressed in terms of stop and yield but we -- have it as a separate case to optimize composition operations for -- streams with single element. We build singleton streams in the -- implementation of pure for Applicative and Monad, and in -- lift for MonadTrans. newtype Stream m a MkStream :: (forall r. State Stream m a -> (a -> Stream m a -> m r) -> (a -> m r) -> m r -> m r) -> Stream m a toStreamK :: Stream m a -> Stream m a fromStreamK :: Stream m a -> Stream m a mkStream :: (forall r. State Stream m a -> (a -> Stream m a -> m r) -> (a -> m r) -> m r -> m r) -> Stream m a -- | Fold a stream by providing a State, stop continuation, a singleton -- continuation and a yield continuation. The stream will not use the -- SVar passed via State. foldStream :: State Stream m a -> (a -> Stream m a -> m r) -> (a -> m r) -> m r -> Stream m a -> m r -- | Fold a stream by providing an SVar, a stop continuation, a singleton -- continuation and a yield continuation. The stream would share the -- current SVar passed via the State. foldStreamShared :: State Stream m a -> (a -> Stream m a -> m r) -> (a -> m r) -> m r -> Stream m a -> m r -- | Lazy right fold with a monadic step function. foldrM :: (a -> m b -> m b) -> m b -> Stream m a -> m b -- | Lazy right associative fold to a stream. foldrS :: (a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b -- | Fold sharing the SVar state within the reconstructed stream foldrSShared :: (a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b foldrSM :: Monad m => (m a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b build :: forall m a. (forall b. (a -> b -> b) -> b -> b) -> Stream m a buildS :: ((a -> Stream m a -> Stream m a) -> Stream m a -> Stream m a) -> Stream m a buildM :: Monad m => (forall r. (a -> Stream m a -> m r) -> (a -> m r) -> m r -> m r) -> Stream m a buildSM :: Monad m => ((m a -> Stream m a -> Stream m a) -> Stream m a -> Stream m a) -> Stream m a augmentS :: ((a -> Stream m a -> Stream m a) -> Stream m a -> Stream m a) -> Stream m a -> Stream m a augmentSM :: Monad m => ((m a -> Stream m a -> Stream m a) -> Stream m a -> Stream m a) -> Stream m a -> Stream m a -- | Make an empty stream from a stop function. fromStopK :: StopK m -> Stream m a -- | Make a singleton stream from a callback function. The callback -- function calls the one-shot yield continuation to yield an element. fromYieldK :: YieldK m a -> Stream m a -- | Add a yield function at the head of the stream. consK :: YieldK m a -> Stream m a -> Stream m a -- | Construct a stream by adding a pure value at the head of an existing -- stream. For serial streams this is the same as (return a) `consM` -- r but more efficient. For concurrent streams this is not -- concurrent whereas consM is concurrent. For example: -- --
--   > toList $ 1 `cons` 2 `cons` 3 `cons` nil
--   [1,2,3]
--   
cons :: a -> Stream m a -> Stream m a infixr 5 `cons` -- | Operator equivalent of cons. -- --
--   > toList $ 1 .: 2 .: 3 .: nil
--   [1,2,3]
--   
(.:) :: a -> Stream m a -> Stream m a infixr 5 .: consM :: Monad m => m a -> Stream m a -> Stream m a infixr 5 `consM` consMBy :: Monad m => (Stream m a -> Stream m a -> Stream m a) -> m a -> Stream m a -> Stream m a -- | An empty stream. -- --
--   > toList nil
--   []
--   
nil :: Stream m a -- | An empty stream producing a side effect. -- --
--   > toList (nilM (print "nil"))
--   "nil"
--   []
--   
-- -- Pre-release nilM :: Applicative m => m b -> Stream m a fromEffect :: Monad m => m a -> Stream m a fromPure :: a -> Stream m a unfoldr :: (b -> Maybe (a, b)) -> b -> Stream m a unfoldrMWith :: Monad m => (m a -> Stream m a -> Stream m a) -> (b -> m (Maybe (a, b))) -> b -> Stream m a -- | Generate an infinite stream by repeating a pure value. -- -- Pre-release repeat :: a -> Stream m a -- | Like repeatM but takes a stream cons operation to -- combine the actions in a stream specific manner. A serial cons would -- repeat the values serially while an async cons would repeat -- concurrently. -- -- Pre-release repeatMWith :: (m a -> t m a -> t m a) -> m a -> t m a replicateMWith :: (m a -> Stream m a -> Stream m a) -> Int -> m a -> Stream m a fromIndicesMWith :: (m a -> Stream m a -> Stream m a) -> (Int -> m a) -> Stream m a iterateMWith :: Monad m => (m a -> Stream m a -> Stream m a) -> (a -> m a) -> m a -> Stream m a -- |
--   fromFoldable = foldr cons nil
--   
-- -- Construct a stream from a Foldable containing pure values: fromFoldable :: Foldable f => f a -> Stream m a fromFoldableM :: (Foldable f, Monad m) => f (m a) -> Stream m a mfix :: Monad m => (m a -> Stream m a) -> Stream m a uncons :: Applicative m => Stream m a -> m (Maybe (a, Stream m a)) -- | Strict left associative fold. foldl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b -- | Strict left fold with an extraction function. Like the standard strict -- left fold, but applies a user supplied extraction function (the third -- argument) to the folded value at the end. This is designed to work -- with the foldl library. The suffix x is a mnemonic -- for extraction. -- -- Note that the accumulator is always evaluated including the initial -- value. foldlx' :: forall m a b x. Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream m a -> m b -- |
--   drain = foldl' (\_ _ -> ()) ()
--   drain = mapM_ (\_ -> return ())
--   
drain :: Monad m => Stream m a -> m () null :: Monad m => Stream m a -> m Bool tail :: Applicative m => Stream m a -> m (Maybe (Stream m a)) init :: Applicative m => Stream m a -> m (Maybe (Stream m a)) conjoin :: Monad m => Stream m a -> Stream m a -> Stream m a -- | Appends two streams sequentially, yielding all elements from the first -- stream, and then all elements from the second stream. serial :: Stream m a -> Stream m a -> Stream m a infixr 6 `serial` map :: (a -> b) -> Stream m a -> Stream m b mapMWith :: (m b -> Stream m b -> Stream m b) -> (a -> m b) -> Stream m a -> Stream m b mapMSerial :: Monad m => (a -> m b) -> Stream m a -> Stream m b -- | Detach a stream from an SVar unShare :: Stream m a -> Stream m a -- | Perform a concatMap using a specified concat strategy. The -- first argument specifies a merge or concat function that is used to -- merge the streams generated by the map function. For example, the -- concat function could be serial, parallel, -- async, ahead or any other zip or merge function. concatMapWith :: (Stream m b -> Stream m b -> Stream m b) -> (a -> Stream m b) -> Stream m a -> Stream m b concatMap :: (a -> Stream m b) -> Stream m a -> Stream m b bindWith :: (Stream m b -> Stream m b -> Stream m b) -> Stream m a -> (a -> Stream m b) -> Stream m b -- | See concatPairsWith for documentation. concatPairsWith :: (Stream m b -> Stream m b -> Stream m b) -> (a -> Stream m b) -> Stream m a -> Stream m b apWith :: (Stream m b -> Stream m b -> Stream m b) -> Stream m (a -> b) -> Stream m a -> Stream m b apSerial :: Stream m (a -> b) -> Stream m a -> Stream m b apSerialDiscardFst :: Stream m a -> Stream m b -> Stream m b apSerialDiscardSnd :: Stream m a -> Stream m b -> Stream m a -- | Lazy left fold to a stream. foldlS :: (Stream m b -> a -> Stream m b) -> Stream m b -> Stream m a -> Stream m b reverse :: Stream m a -> Stream m a withLocal :: MonadReader r m => (r -> r) -> Stream m a -> Stream m a instance GHC.Base.Semigroup (Streamly.Internal.Data.Stream.StreamK.Type.Stream m a) instance GHC.Base.Monoid (Streamly.Internal.Data.Stream.StreamK.Type.Stream m a) instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Stream.StreamK.Type.Stream m) instance Control.Monad.Trans.Class.MonadTrans Streamly.Internal.Data.Stream.StreamK.Type.Stream instance GHC.Base.Monad m => GHC.Base.Applicative (Streamly.Internal.Data.Stream.StreamK.Type.Stream m) instance GHC.Base.Monad m => GHC.Base.Monad (Streamly.Internal.Data.Stream.StreamK.Type.Stream m) -- | | Strict data types to be used as accumulator for strict left folds -- and scans. For more comprehensive strict data types see -- https://hackage.haskell.org/package/strict-base-types . The -- names have been suffixed by a prime so that programmers can easily -- distinguish the strict versions from the lazy ones. -- -- One major advantage of strict data structures as accumulators in folds -- and scans is that it helps the compiler optimize the code much better -- by unboxing. In a big tight loop the difference could be huge. module Streamly.Internal.Data.Tuple.Strict -- | A strict (,) data Tuple' a b Tuple' :: !a -> !b -> Tuple' a b -- | A strict (,,) data Tuple3' a b c Tuple3' :: !a -> !b -> !c -> Tuple3' a b c -- | A strict (,,,) data Tuple4' a b c d Tuple4' :: !a -> !b -> !c -> !d -> Tuple4' a b c d instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Streamly.Internal.Data.Tuple.Strict.Tuple' a b) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c) => GHC.Show.Show (Streamly.Internal.Data.Tuple.Strict.Tuple3' a b c) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c, GHC.Show.Show d) => GHC.Show.Show (Streamly.Internal.Data.Tuple.Strict.Tuple4' a b c d) module Streamly.Internal.Data.Pipe.Type data Step s a Yield :: a -> s -> Step s a Continue :: s -> Step s a data Pipe m a b Pipe :: (s1 -> a -> m (Step (PipeState s1 s2) b)) -> (s2 -> m (Step (PipeState s1 s2) b)) -> s1 -> Pipe m a b -- | Represents a stateful transformation over an input stream of values of -- type a to outputs of type b in Monad -- m. data PipeState s1 s2 Consume :: s1 -> PipeState s1 s2 Produce :: s2 -> PipeState s1 s2 -- | The composed pipe distributes the input to both the constituent pipes -- and zips the output of the two using a supplied zipping function. zipWith :: Monad m => (a -> b -> c) -> Pipe m i a -> Pipe m i b -> Pipe m i c -- | The composed pipe distributes the input to both the constituent pipes -- and merges the outputs of the two. tee :: Monad m => Pipe m a b -> Pipe m a b -> Pipe m a b -- | Lift a pure function to a Pipe. map :: Monad m => (a -> b) -> Pipe m a b -- | Compose two pipes such that the output of the second pipe is attached -- to the input of the first pipe. compose :: Monad m => Pipe m b c -> Pipe m a b -> Pipe m a c instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Pipe.Type.Pipe m a) instance GHC.Base.Monad m => GHC.Base.Applicative (Streamly.Internal.Data.Pipe.Type.Pipe m a) instance GHC.Base.Monad m => GHC.Base.Semigroup (Streamly.Internal.Data.Pipe.Type.Pipe m a b) instance GHC.Base.Monad m => Control.Category.Category (Streamly.Internal.Data.Pipe.Type.Pipe m) instance GHC.Base.Monad m => Control.Arrow.Arrow (Streamly.Internal.Data.Pipe.Type.Pipe m) -- | There are three fundamental types in streamly. They are streams -- (Streamly.Prelude), pipes (Streamly.Internal.Data.Pipe) -- and folds (Streamly.Data.Fold). Streams are sources or -- producers of values, multiple sources can be merged into a single -- source but a source cannot be split into multiple stream sources. -- Folds are sinks or consumers, a stream can be split and distributed to -- multiple folds but the results cannot be merged back into a stream -- source again. Pipes are transformations, a stream source can be split -- and distributed to multiple pipes each pipe can apply its own -- transform on the stream and the results can be merged back into a -- single pipe. Pipes can be attached to a source to produce a source or -- they can be attached to a fold to produce a fold, or multiple pipes -- can be merged or zipped into a single pipe. -- --
--   import qualified Streamly.Internal.Data.Pipe as Pipe
--   
module Streamly.Internal.Data.Pipe data Pipe m a b -- | Lift a pure function to a Pipe. map :: Monad m => (a -> b) -> Pipe m a b -- | Lift a monadic function to a Pipe. mapM :: Monad m => (a -> m b) -> Pipe m a b -- | The composed pipe distributes the input to both the constituent pipes -- and merges the outputs of the two. tee :: Monad m => Pipe m a b -> Pipe m a b -> Pipe m a b -- | The composed pipe distributes the input to both the constituent pipes -- and zips the output of the two using a supplied zipping function. zipWith :: Monad m => (a -> b -> c) -> Pipe m i a -> Pipe m i b -> Pipe m i c -- | Compose two pipes such that the output of the second pipe is attached -- to the input of the first pipe. compose :: Monad m => Pipe m b c -> Pipe m a b -> Pipe m a c -- |

Stream Consumers

-- -- We can classify stream consumers in the following categories in order -- of increasing complexity and power: -- --

Accumulators

-- -- These are the simplest folds that never fail and never terminate, they -- accumulate the input values forever and can always accept new inputs -- (never terminate) and always have a valid result value. A sum -- operation is an example of an accumulator. Traditional Haskell left -- folds like foldl are accumulators. -- -- We can distribute an input stream to two or more accumulators using a -- tee style composition. Accumulators cannot be applied on a -- stream one after the other, which we call a serial append -- style composition of folds. This is because accumulators never -- terminate, since the first accumulator in a series will never -- terminate, the next one will never get to run. -- --

Terminating Folds

-- -- Terminating folds are accumulators that can terminate. Once a fold -- terminates it no longer accepts any more inputs. Terminating folds can -- be used in a serial append style composition where one fold -- can be applied after the other on an input stream. We can apply a -- terminating fold repeatedly on an input stream, splitting the stream -- and consuming it in fragments. Terminating folds never fail, -- therefore, they do not need backtracking. -- -- The take operation is an example of a terminating fold It -- terminates after consuming n items. Coupled with an -- accumulator (e.g. sum) it can be used to split and process the stream -- into chunks of fixed size. -- --

Terminating Folds with Leftovers

-- -- The next upgrade after terminating folds is terminating folds with -- leftover inputs. Consider the example of takeWhile operation, -- it needs to inspect an element for termination decision. However, it -- does not consume the element on which it terminates. To implement -- takeWhile a terminating fold will have to implement a way to -- return unconsumed input to the fold driver. -- -- Single element leftover case is the most common and its easy to -- implement it in terminating folds using a Done1 constructor -- in the Step type which indicates that the last element was not -- consumed by the fold. The following additional operations can be -- implemented as terminating folds if we do that. -- --
--   takeWhile
--   groupBy
--   wordBy
--   
-- -- However, it creates several complications. The many combinator -- requires a Partial1 (Partial with leftover) to handle -- a Done1 from the top level fold, for efficient -- implementation. If the collecting fold in "many" returns a -- Partial1 or Done1 then what to do with all the -- elements that have been consumed? -- -- Similarly, in distribute, if one fold consumes a value and others say -- its a leftover then what do we do? Folds like "many" require the -- leftover to be fed to it again. So in a distribute operation those -- folds which gave a leftover will have to be fed the leftover while the -- folds that consumed will have to be fed the next input. This is very -- complicated to implement. We have the same issue in backtracking -- parsers being used in a distribute operation. -- -- To avoid these issues we want to enforce by typing that the collecting -- folds can never return a leftover. So we need a fold type without -- Done1 or Partial1. This leads us to design folds to -- never return a leftover and the use cases of single leftover are -- transferred to parsers where we have general backtracking mechanism -- and single leftover is just a special case of backtracking. -- -- This means: takeWhile, groupBy, wordBy would be implemented as -- parsers. "take 0" can implemented as a fold if we make initial return -- Step type. "takeInterval" can be implemented without -- Done1. -- --

Parsers

-- -- The next upgrade after terminating folds with a leftover are parsers. -- Parsers are terminating folds that can fail and backtrack. Parsers can -- be composed using an alternative style composition where they -- can backtrack and apply another parser if one parser fails. -- satisfy is a simple example of a parser, it would succeed if -- the condition is satisfied and it would fail otherwise, on failure an -- alternative parser can be used on the same input. -- --

Types for Stream Consumers

-- -- In streamly, there is no separate type for accumulators. Terminating -- folds are a superset of accumulators and to avoid too many types we -- represent both using the same type, Fold. -- -- We do not club the leftovers functionality with terminating folds -- because of the reasons explained earlier. Instead combinators that -- require leftovers are implemented as the Parser type. This is a -- sweet spot to balance ease of use, type safety and performance. Using -- separate Accumulator and terminating fold types would encode more -- information in types but it would make ease of use, implementation, -- maintenance effort worse. Combining Accumulator, terminating folds and -- Parser into a single Parser type would make ease of use even -- better but type safety and performance worse. -- -- One of the design requirements that we have placed for better ease of -- use and code reuse is that Parser type should be a strict -- superset of the Fold type i.e. it can do everything that a -- Fold can do and more. Therefore, folds can be easily upgraded -- to parsers and we can use parser combinators on folds as well when -- needed. -- --

Fold Design

-- -- A fold is represented by a collection of "initial", "step" and -- "extract" functions. The "initial" action generates the initial state -- of the fold. The state is internal to the fold and maintains the -- accumulated output. The "step" function is invoked using the current -- state and the next input value and results in a Partial or -- Done. A Partial returns the next intermediate state -- of the fold, a Done indicates that the fold has terminated -- and returns the final value of the accumulator. -- -- Every Partial indicates that a new accumulated output is -- available. The accumulated output can be extracted from the state at -- any point using "extract". "extract" can never fail. A fold returns a -- valid output even without any input i.e. even if you call "extract" on -- "initial" state it provides an output. This is not true for parsers. -- -- In general, "extract" is used in two cases: -- -- -- --

Alternate Designs

-- -- An alternate and simpler design would be to return the intermediate -- output via Partial along with the state, instead of using -- "extract" on the yielded state and remove the extract function -- altogether. -- -- This may even facilitate more efficient implementation. Extract from -- the intermediate state after each yield may be more costly compared to -- the fold step itself yielding the output. The fold may have more -- efficient ways to retrieve the output rather than stuffing it in the -- state and using extract on the state. -- -- However, removing extract altogether may lead to less optimal code in -- some cases because the driver of the fold needs to thread around the -- intermediate output to return it if the stream stops before the fold -- could Done. When using this approach, the parseMany -- (FL.take filesize) benchmark shows a 2x worse performance even -- after ensuring everything fuses. So we keep the "extract" approach to -- ensure better perf in all cases. -- -- But we could still yield both state and the output in -- Partial, the output can be used for the scan use case, -- instead of using extract. Extract would then be used only for the case -- when the stream stops before the fold completes. -- --

Accumulators and Terminating Folds

-- -- Folds in this module can be classified in two categories viz. -- accumulators and terminating folds. Accumulators do not have a -- terminating condition, they run forever and consume the entire stream, -- for example the length fold. Terminating folds have a -- terminating condition and can terminate without consuming the entire -- stream, for example, the head fold. -- --

Monoids

-- -- Monoids allow generalized, modular folding. The accumulators in this -- module can be expressed using mconcat and a suitable -- Monoid. Instead of writing folds we can write Monoids and turn -- them into folds. -- --

Performance Notes

-- -- Prelude module provides fold functions to directly fold streams -- e.g. Streamly.Prelude/sum serves the same purpose as -- Fold/sum. However, the functions in Streamly.Prelude cannot be -- efficiently combined together e.g. we cannot drive the input stream -- through sum and length fold functions -- simultaneously. Using the Fold type we can efficiently split -- the stream across multiple folds because it allows the compiler to -- perform stream fusion optimizations. module Streamly.Internal.Data.Fold.Type -- | Represents the result of the step of a Fold. -- Partial returns an intermediate state of the fold, the fold -- step can be called again with the state or the driver can use -- extract on the state to get the result out. Done -- returns the final result and the fold cannot be driven further. -- -- Pre-release data Step s b Partial :: !s -> Step s b Done :: !b -> Step s b -- | The type Fold m a b having constructor Fold step initial -- extract represents a fold over an input stream of values of type -- a to a final value of type b in Monad -- m. -- -- The fold uses an intermediate state s as accumulator, the -- type s is internal to the specific fold definition. The -- initial value of the fold state s is returned by -- initial. The step function consumes an input and -- either returns the final result b if the fold is done or the -- next intermediate state (see Step). At any point the fold -- driver can extract the result from the intermediate state using the -- extract function. -- -- NOTE: The constructor is not yet exposed via exposed modules, smart -- constructors are provided to create folds. If you think you need the -- constructor of this type please consider using the smart constructors -- in Streamly.Internal.Data.Fold instead. -- -- since 0.8.0 (type changed) data Fold m a b -- | Fold step initial extract Fold :: (s -> a -> m (Step s b)) -> m (Step s b) -> (s -> m b) -> Fold m a b -- | Make a fold from a left fold style pure step function and initial -- value of the accumulator. -- -- If your Fold returns only Partial (i.e. never returns a -- Done) then you can use foldl'* constructors. -- -- A fold with an extract function can be expressed using fmap: -- --
--   mkfoldlx :: Monad m => (s -> a -> s) -> s -> (s -> b) -> Fold m a b
--   mkfoldlx step initial extract = fmap extract (foldl' step initial)
--   
-- -- See also: Streamly.Prelude.foldl' foldl' :: Monad m => (b -> a -> b) -> b -> Fold m a b -- | Make a fold from a left fold style monadic step function and initial -- value of the accumulator. -- -- A fold with an extract function can be expressed using rmapM: -- --
--   mkFoldlxM :: Functor m => (s -> a -> m s) -> m s -> (s -> m b) -> Fold m a b
--   mkFoldlxM step initial extract = rmapM extract (foldlM' step initial)
--   
-- -- See also: Streamly.Prelude.foldlM' foldlM' :: Monad m => (b -> a -> m b) -> m b -> Fold m a b -- | Make a strict left fold, for non-empty streams, using first element as -- the starting value. Returns Nothing if the stream is empty. -- -- See also: Streamly.Prelude.foldl1' -- -- Pre-release foldl1' :: Monad m => (a -> a -> a) -> Fold m a (Maybe a) -- | Make a fold using a right fold style step function and a terminal -- value. It performs a strict right fold via a left fold using function -- composition. Note that this is strict fold, it can only be useful for -- constructing strict structures in memory. For reductions this will be -- very inefficient. -- -- For example, -- --
--   toList = foldr (:) []
--   
-- -- See also: foldr foldr :: Monad m => (a -> b -> b) -> b -> Fold m a b -- | Like foldr but with a monadic step function. -- -- For example, -- --
--   toList = foldrM (\a xs -> return $ a : xs) (return [])
--   
-- -- See also: foldrM -- -- Pre-release foldrM :: Monad m => (a -> b -> m b) -> m b -> Fold m a b -- | Make a terminating fold using a pure step function, a pure initial -- state and a pure state extraction function. -- -- Pre-release mkFold :: Monad m => (s -> a -> Step s b) -> Step s b -> (s -> b) -> Fold m a b -- | Similar to mkFold but the final state extracted is identical to -- the intermediate state. -- --
--   mkFold_ step initial = mkFold step initial id
--   
-- -- Pre-release mkFold_ :: Monad m => (b -> a -> Step b b) -> Step b b -> Fold m a b -- | Make a terminating fold with an effectful step function and initial -- state, and a state extraction function. -- --
--   mkFoldM = Fold
--   
-- -- We can just use Fold but it is provided for completeness. -- -- Pre-release mkFoldM :: (s -> a -> m (Step s b)) -> m (Step s b) -> (s -> m b) -> Fold m a b -- | Similar to mkFoldM but the final state extracted is identical -- to the intermediate state. -- --
--   mkFoldM_ step initial = mkFoldM step initial return
--   
-- -- Pre-release mkFoldM_ :: Monad m => (b -> a -> m (Step b b)) -> m (Step b b) -> Fold m a b -- | A fold that always yields a pure value without consuming any input. -- -- Pre-release fromPure :: Applicative m => b -> Fold m a b -- | A fold that always yields the result of an effectful action without -- consuming any input. -- -- Pre-release fromEffect :: Applicative m => m b -> Fold m a b -- | Make a fold from a consumer. -- -- Internal fromRefold :: Refold m c a b -> c -> Fold m a b -- | A fold that drains all its input, running the effects and discarding -- the results. -- --
--   drain = drainBy (const (return ()))
--   
drain :: Monad m => Fold m a () -- | Folds the input stream to a list. -- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using -- Streamly.Data.Array.Foreign instead. -- --
--   toList = foldr (:) []
--   
toList :: Monad m => Fold m a [a] -- | A fold that buffers its input to a pure stream. -- --
--   >>> toStreamK = foldr StreamK.cons StreamK.nil
--   
--   >>> toStreamK = fmap StreamK.reverse Fold.toStreamKRev
--   
-- -- Internal toStreamK :: Monad m => Fold m a (Stream n a) -- | Buffers the input stream to a pure stream in the reverse order of the -- input. -- --
--   >>> toStreamKRev = Foldable.foldl' (flip StreamK.cons) StreamK.nil
--   
-- -- This is more efficient than toStreamK. toStreamK has exactly -- the same performance as reversing the stream after toStreamKRev. -- -- Pre-release toStreamKRev :: Monad m => Fold m a (Stream n a) -- | Map a monadic function on the output of a fold. rmapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c -- | lmap f fold maps the function f on the input of the -- fold. -- --
--   >>> Stream.fold (Fold.lmap (\x -> x * x) Fold.sum) (Stream.enumerateFromTo 1 100)
--   338350
--   
-- --
--   lmap = Fold.lmapM return
--   
lmap :: (a -> b) -> Fold m b r -> Fold m a r -- | lmapM f fold maps the monadic function f on the -- input of the fold. lmapM :: Monad m => (a -> m b) -> Fold m b r -> Fold m a r -- | Include only those elements that pass a predicate. -- --
--   >>> Stream.fold (Fold.filter (> 5) Fold.sum) $ Stream.fromList [1..10]
--   40
--   
-- --
--   filter f = Fold.filterM (return . f)
--   
filter :: Monad m => (a -> Bool) -> Fold m a r -> Fold m a r -- | Like filter but with a monadic predicate. filterM :: Monad m => (a -> m Bool) -> Fold m a r -> Fold m a r -- | Modify a fold to receive a Maybe input, the Just values -- are unwrapped and sent to the original fold, Nothing values are -- discarded. catMaybes :: Monad m => Fold m a b -> Fold m (Maybe a) b -- | Take at most n input elements and fold them using the -- supplied fold. A negative count is treated as 0. -- --
--   >>> Stream.fold (Fold.take 2 Fold.toList) $ Stream.fromList [1..10]
--   [1,2]
--   
take :: Monad m => Int -> Fold m a b -> Fold m a b -- | Sequential fold application. Apply two folds sequentially to an input -- stream. The input is provided to the first fold, when it is done - the -- remaining input is provided to the second fold. When the second fold -- is done or if the input stream is over, the outputs of the two folds -- are combined using the supplied function. -- --
--   >>> f = Fold.serialWith (,) (Fold.take 8 Fold.toList) (Fold.takeEndBy (== '\n') Fold.toList)
--   
--   >>> Stream.fold f $ Stream.fromList "header: hello\n"
--   ("header: ","hello\n")
--   
-- -- Note: This is dual to appending streams using serial. -- -- Note: this implementation allows for stream fusion but has quadratic -- time complexity, because each composition adds a new branch that each -- subsequent fold's input element has to traverse, therefore, it cannot -- scale to a large number of compositions. After around 100 compositions -- the performance starts dipping rapidly compared to a CPS style -- implementation. -- -- Time: O(n^2) where n is the number of compositions. serialWith :: Monad m => (a -> b -> c) -> Fold m x a -> Fold m x b -> Fold m x c -- | Same as applicative *>. Run two folds serially one after the -- other discarding the result of the first. -- -- This was written in the hope that it might be faster than implementing -- it using serialWith, but the current benchmarks show that it has the -- same performance. So do not expose it unless some benchmark shows -- benefit. serial_ :: Monad m => Fold m x a -> Fold m x b -> Fold m x b -- | teeWith k f1 f2 distributes its input to both f1 and -- f2 until both of them terminate and combines their output -- using k. -- --
--   >>> avg = Fold.teeWith (/) Fold.sum (fmap fromIntegral Fold.length)
--   
--   >>> Stream.fold avg $ Stream.fromList [1.0..100.0]
--   50.5
--   
-- --
--   teeWith k f1 f2 = fmap (uncurry k) ((Fold.tee f1 f2)
--   
-- -- For applicative composition using this combinator see -- Streamly.Internal.Data.Fold.Tee. -- -- See also: Streamly.Internal.Data.Fold.Tee teeWith :: Monad m => (a -> b -> c) -> Fold m x a -> Fold m x b -> Fold m x c -- | Like teeWith but terminates as soon as the first fold -- terminates. -- -- Pre-release teeWithFst :: Monad m => (b -> c -> d) -> Fold m a b -> Fold m a c -> Fold m a d -- | Like teeWith but terminates as soon as any one of the two folds -- terminates. -- -- Pre-release teeWithMin :: Monad m => (b -> c -> d) -> Fold m a b -> Fold m a c -> Fold m a d -- | Shortest alternative. Apply both folds in parallel but choose the -- result from the one which consumed least input i.e. take the shortest -- succeeding fold. -- -- If both the folds finish at the same time or if the result is -- extracted before any of the folds could finish then the left one is -- taken. -- -- Pre-release shortest :: Monad m => Fold m x a -> Fold m x b -> Fold m x (Either a b) -- | Longest alternative. Apply both folds in parallel but choose the -- result from the one which consumed more input i.e. take the longest -- succeeding fold. -- -- If both the folds finish at the same time or if the result is -- extracted before any of the folds could finish then the left one is -- taken. -- -- Pre-release longest :: Monad m => Fold m x a -> Fold m x b -> Fold m x (Either a b) data ManyState s1 s2 -- | Collect zero or more applications of a fold. many split -- collect applies the split fold repeatedly on the input -- stream and accumulates zero or more fold results using -- collect. -- --
--   >>> two = Fold.take 2 Fold.toList
--   
--   >>> twos = Fold.many two Fold.toList
--   
--   >>> Stream.fold twos $ Stream.fromList [1..10]
--   [[1,2],[3,4],[5,6],[7,8],[9,10]]
--   
-- -- Stops when collect stops. -- -- See also: concatMap, foldMany many :: Monad m => Fold m a b -> Fold m b c -> Fold m a c -- | Like many, but inner fold emits an output at the end even if no input -- is received. -- -- Internal -- -- See also: concatMap, foldMany manyPost :: Monad m => Fold m a b -> Fold m b c -> Fold m a c -- | chunksOf n split collect repeatedly applies the -- split fold to chunks of n items in the input stream -- and supplies the result to the collect fold. -- --
--   >>> twos = Fold.chunksOf 2 Fold.toList Fold.toList
--   
--   >>> Stream.fold twos $ Stream.fromList [1..10]
--   [[1,2],[3,4],[5,6],[7,8],[9,10]]
--   
-- --
--   chunksOf n split = many (take n split)
--   
-- -- Stops when collect stops. chunksOf :: Monad m => Int -> Fold m a b -> Fold m b c -> Fold m a c -- | Like many but uses a Refold for collecting. refoldMany :: Monad m => Fold m a b -> Refold m x b c -> Refold m x a c -- | Like many but uses a Refold for splitting. -- -- Internal refoldMany1 :: Monad m => Refold m x a b -> Fold m b c -> Refold m x a c -- | Extract the output of a fold and refold it using a Refold. -- -- Internal refold :: Monad m => Fold m a b -> Refold m b a b -> Fold m a b -- | Map a Fold returning function on the result of a Fold -- and run the returned fold. This operation can be used to express data -- dependencies between fold operations. -- -- Let's say the first element in the stream is a count of the following -- elements that we have to add, then: -- --
--   >>> import Data.Maybe (fromJust)
--   
--   >>> count = fmap fromJust Fold.head
--   
--   >>> total n = Fold.take n Fold.sum
--   
--   >>> Stream.fold (Fold.concatMap total count) $ Stream.fromList [10,9..1]
--   45
--   
-- -- Time: O(n^2) where n is the number of compositions. -- -- See also: foldIterateM concatMap :: Monad m => (b -> Fold m a c) -> Fold m a b -> Fold m a c -- | Run the initialization effect of a fold. The returned fold would use -- the value returned by this effect as its initial value. -- -- Pre-release initialize :: Monad m => Fold m a b -> m (Fold m a b) -- | Append a singleton value to the fold. -- --
--   >>> import qualified Data.Foldable as Foldable
--   
--   >>> Foldable.foldlM Fold.snoc Fold.toList [1..3] >>= Fold.finish
--   [1,2,3]
--   
-- -- Compare with duplicate which allows appending a stream to the -- fold. -- -- Pre-release snoc :: Monad m => Fold m a b -> a -> m (Fold m a b) -- | duplicate provides the ability to run a fold in parts. The -- duplicated fold consumes the input and returns the same fold as output -- instead of returning the final result, the returned fold can be run -- later to consume more input. -- -- We can append a stream to a fold as follows: -- --
--   >>> :{
--   foldAppend :: Monad m => Fold m a b -> SerialT m a -> m (Fold m a b)
--   foldAppend f = Stream.fold (Fold.duplicate f)
--   :}
--   
-- --
--   >>> :{
--   do
--    sum1 <- foldAppend Fold.sum (Stream.enumerateFromTo 1 10)
--    sum2 <- foldAppend sum1 (Stream.enumerateFromTo 11 20)
--    Stream.fold sum2 (Stream.enumerateFromTo 21 30)
--   :}
--   465
--   
-- -- duplicate essentially appends a stream to the fold without -- finishing the fold. Compare with snoc which appends a singleton -- value to the fold. -- -- Pre-release duplicate :: Monad m => Fold m a b -> Fold m a (Fold m a b) -- | Finish the fold to extract the current value of the fold. -- --
--   >>> Fold.finish Fold.toList
--   []
--   
-- -- Pre-release finish :: Monad m => Fold m a b -> m b instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Streamly.Internal.Data.Fold.Type.Tuple'Fused a b) instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Fold.Type.Fold m a) -- | Continuation passing style (CPS) stream implementation. The symbol -- K below denotes a function as well as a Kontinuation. -- --
--   import qualified Streamly.Internal.Data.Stream.StreamK as K
--   
module Streamly.Internal.Data.Stream.StreamK -- | The type Stream m a represents a monadic stream of values of -- type a constructed using actions in monad m. It uses -- stop, singleton and yield continuations equivalent to the following -- direct style type: -- --
--   data Stream m a = Stop | Singleton a | Yield a (Stream m a)
--   
-- -- To facilitate parallel composition we maintain a local state in an -- SVar that is shared across and is used for synchronization of -- the streams being composed. -- -- The singleton case can be expressed in terms of stop and yield but we -- have it as a separate case to optimize composition operations for -- streams with single element. We build singleton streams in the -- implementation of pure for Applicative and Monad, and in -- lift for MonadTrans. newtype Stream m a MkStream :: (forall r. State Stream m a -> (a -> Stream m a -> m r) -> (a -> m r) -> m r -> m r) -> Stream m a mkStream :: (forall r. State Stream m a -> (a -> Stream m a -> m r) -> (a -> m r) -> m r -> m r) -> Stream m a -- | An empty stream. -- --
--   > toList nil
--   []
--   
nil :: Stream m a -- | An empty stream producing a side effect. -- --
--   > toList (nilM (print "nil"))
--   "nil"
--   []
--   
-- -- Pre-release nilM :: Applicative m => m b -> Stream m a -- | Construct a stream by adding a pure value at the head of an existing -- stream. For serial streams this is the same as (return a) `consM` -- r but more efficient. For concurrent streams this is not -- concurrent whereas consM is concurrent. For example: -- --
--   > toList $ 1 `cons` 2 `cons` 3 `cons` nil
--   [1,2,3]
--   
cons :: a -> Stream m a -> Stream m a infixr 5 `cons` -- | Operator equivalent of cons. -- --
--   > toList $ 1 .: 2 .: 3 .: nil
--   [1,2,3]
--   
(.:) :: a -> Stream m a -> Stream m a infixr 5 .: -- | Fold a stream by providing a State, stop continuation, a singleton -- continuation and a yield continuation. The stream will not use the -- SVar passed via State. foldStream :: State Stream m a -> (a -> Stream m a -> m r) -> (a -> m r) -> m r -> Stream m a -> m r -- | Fold a stream by providing an SVar, a stop continuation, a singleton -- continuation and a yield continuation. The stream would share the -- current SVar passed via the State. foldStreamShared :: State Stream m a -> (a -> Stream m a -> m r) -> (a -> m r) -> m r -> Stream m a -> m r -- | Detach a stream from an SVar unShare :: Stream m a -> Stream m a uncons :: Applicative m => Stream m a -> m (Maybe (a, Stream m a)) unfoldr :: (b -> Maybe (a, b)) -> b -> Stream m a unfoldrM :: Monad m => (b -> m (Maybe (a, b))) -> b -> Stream m a -- | Generate an infinite stream by repeating a pure value. -- -- Pre-release repeat :: a -> Stream m a repeatM :: Monad m => m a -> Stream m a replicate :: Int -> a -> Stream m a replicateM :: Monad m => Int -> m a -> Stream m a fromIndices :: (Int -> a) -> Stream m a fromIndicesM :: Monad m => (Int -> m a) -> Stream m a iterate :: (a -> a) -> a -> Stream m a iterateM :: Monad m => (a -> m a) -> m a -> Stream m a fromPure :: a -> Stream m a fromEffect :: Monad m => m a -> Stream m a -- |
--   fromFoldable = foldr cons nil
--   
-- -- Construct a stream from a Foldable containing pure values: fromFoldable :: Foldable f => f a -> Stream m a fromList :: [a] -> Stream m a -- | Lazy right associative fold to a stream. foldrS :: (a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b foldrSM :: Monad m => (m a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b buildS :: ((a -> Stream m a -> Stream m a) -> Stream m a -> Stream m a) -> Stream m a augmentS :: ((a -> Stream m a -> Stream m a) -> Stream m a -> Stream m a) -> Stream m a -> Stream m a -- | Lazy right associative fold. foldr :: Monad m => (a -> b -> b) -> b -> Stream m a -> m b foldr1 :: Monad m => (a -> a -> a) -> Stream m a -> m (Maybe a) -- | Lazy right fold with a monadic step function. foldrM :: (a -> m b -> m b) -> m b -> Stream m a -> m b -- | Right associative fold to an arbitrary transformer monad. foldrT :: (Monad m, Monad (s m), MonadTrans s) => (a -> s m b -> s m b) -> s m b -> Stream m a -> s m b -- | Strict left associative fold. foldl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b -- | Like foldl' but with a monadic step function. foldlM' :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> m b -- | Lazy left fold to a stream. foldlS :: (Stream m b -> a -> Stream m b) -> Stream m b -> Stream m a -> Stream m b -- | Lazy left fold to an arbitrary transformer monad. foldlT :: (Monad m, Monad (s m), MonadTrans s) => (s m b -> a -> s m b) -> s m b -> Stream m a -> s m b -- | Strict left fold with an extraction function. Like the standard strict -- left fold, but applies a user supplied extraction function (the third -- argument) to the folded value at the end. This is designed to work -- with the foldl library. The suffix x is a mnemonic -- for extraction. -- -- Note that the accumulator is always evaluated including the initial -- value. foldlx' :: forall m a b x. Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream m a -> m b -- | Like foldx, but with a monadic step function. foldlMx' :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream m a -> m b fold :: Monad m => Fold m a b -> Stream m a -> m b -- |
--   drain = foldl' (\_ _ -> ()) ()
--   drain = mapM_ (\_ -> return ())
--   
drain :: Monad m => Stream m a -> m () null :: Monad m => Stream m a -> m Bool head :: Monad m => Stream m a -> m (Maybe a) tail :: Applicative m => Stream m a -> m (Maybe (Stream m a)) init :: Applicative m => Stream m a -> m (Maybe (Stream m a)) elem :: (Monad m, Eq a) => a -> Stream m a -> m Bool notElem :: (Monad m, Eq a) => a -> Stream m a -> m Bool all :: Monad m => (a -> Bool) -> Stream m a -> m Bool any :: Monad m => (a -> Bool) -> Stream m a -> m Bool -- | Extract the last element of the stream, if any. last :: Monad m => Stream m a -> m (Maybe a) minimum :: (Monad m, Ord a) => Stream m a -> m (Maybe a) minimumBy :: Monad m => (a -> a -> Ordering) -> Stream m a -> m (Maybe a) maximum :: (Monad m, Ord a) => Stream m a -> m (Maybe a) maximumBy :: Monad m => (a -> a -> Ordering) -> Stream m a -> m (Maybe a) findIndices :: (a -> Bool) -> Stream m a -> Stream m Int lookup :: (Monad m, Eq a) => a -> Stream m (a, b) -> m (Maybe b) findM :: Monad m => (a -> m Bool) -> Stream m a -> m (Maybe a) find :: Monad m => (a -> Bool) -> Stream m a -> m (Maybe a) (!!) :: Monad m => Stream m a -> Int -> m (Maybe a) -- | Apply a monadic action to each element of the stream and discard the -- output of the action. mapM_ :: Monad m => (a -> m b) -> Stream m a -> m () toList :: Monad m => Stream m a -> m [a] hoist :: (Monad m, Monad n) => (forall x. m x -> n x) -> Stream m a -> Stream n a scanl' :: (b -> a -> b) -> b -> Stream m a -> Stream m b scanlx' :: (x -> a -> x) -> x -> (x -> b) -> Stream m a -> Stream m b filter :: (a -> Bool) -> Stream m a -> Stream m a take :: Int -> Stream m a -> Stream m a takeWhile :: (a -> Bool) -> Stream m a -> Stream m a drop :: Int -> Stream m a -> Stream m a dropWhile :: (a -> Bool) -> Stream m a -> Stream m a map :: (a -> b) -> Stream m a -> Stream m b mapM :: Monad m => (a -> m b) -> Stream m a -> Stream m b sequence :: Monad m => Stream m (m a) -> Stream m a intersperseM :: Monad m => m a -> Stream m a -> Stream m a intersperse :: Monad m => a -> Stream m a -> Stream m a insertBy :: (a -> a -> Ordering) -> a -> Stream m a -> Stream m a deleteBy :: (a -> a -> Bool) -> a -> Stream m a -> Stream m a reverse :: Stream m a -> Stream m a mapMaybe :: (a -> Maybe b) -> Stream m a -> Stream m b -- | Zip two streams serially using a pure zipping function. zipWith :: (a -> b -> c) -> Stream m a -> Stream m b -> Stream m c -- | Zip two streams serially using a monadic zipping function. zipWithM :: Monad m => (a -> b -> m c) -> Stream m a -> Stream m b -> Stream m c mergeBy :: (a -> a -> Ordering) -> Stream m a -> Stream m a -> Stream m a mergeByM :: Monad m => (a -> a -> m Ordering) -> Stream m a -> Stream m a -> Stream m a -- | Perform a concatMap using a specified concat strategy. The -- first argument specifies a merge or concat function that is used to -- merge the streams generated by the map function. For example, the -- concat function could be serial, parallel, -- async, ahead or any other zip or merge function. concatMapWith :: (Stream m b -> Stream m b -> Stream m b) -> (a -> Stream m b) -> Stream m a -> Stream m b concatMap :: (a -> Stream m b) -> Stream m a -> Stream m b bindWith :: (Stream m b -> Stream m b -> Stream m b) -> Stream m a -> (a -> Stream m b) -> Stream m b -- | See concatPairsWith for documentation. concatPairsWith :: (Stream m b -> Stream m b -> Stream m b) -> (a -> Stream m b) -> Stream m a -> Stream m b apWith :: (Stream m b -> Stream m b -> Stream m b) -> Stream m (a -> b) -> Stream m a -> Stream m b apSerial :: Stream m (a -> b) -> Stream m a -> Stream m b apSerialDiscardFst :: Stream m a -> Stream m b -> Stream m b apSerialDiscardSnd :: Stream m a -> Stream m b -> Stream m a the :: (Eq a, Monad m) => Stream m a -> m (Maybe a) -- | Appends two streams sequentially, yielding all elements from the first -- stream, and then all elements from the second stream. serial :: Stream m a -> Stream m a -> Stream m a infixr 6 `serial` consM :: Monad m => m a -> Stream m a -> Stream m a infixr 5 `consM` withLocal :: MonadReader r m => (r -> r) -> Stream m a -> Stream m a mfix :: Monad m => (m a -> Stream m a) -> Stream m a -- | The Sink type is a just a special case of Fold and we -- can do without it. However, in some cases Sink is a simpler -- type and may provide better performance than Fold because it -- does not maintain any state. Folds can be used for both pure and -- monadic computations. Sinks are not applicable to pure computations. module Streamly.Internal.Data.Sink -- | A Sink is a special type of Fold that does not -- accumulate any value, but runs only effects. A Sink has no -- state to maintain therefore can be a bit more efficient than a -- Fold with () as the state, especially when -- Sinks are composed with other operations. A Sink can be -- upgraded to a Fold, but a Fold cannot be converted -- into a Sink. newtype Sink m a Sink :: (a -> m ()) -> Sink m a -- | Convert a Sink to a Fold. When you want to compose sinks -- and folds together, upgrade a sink to a fold before composing. toFold :: Monad m => Sink m a -> Fold m a () -- | Distribute one copy each of the input to both the sinks. -- --
--                   |-------Sink m a
--   ---stream m a---|
--                   |-------Sink m a
--   
-- --
--   > let pr x = Sink.drainM (putStrLn . ((x ++ " ") ++) . show)
--   > sink (Sink.tee (pr "L") (pr "R")) (S.enumerateFromTo 1 2)
--   L 1
--   R 1
--   L 2
--   R 2
--   
tee :: Monad m => Sink m a -> Sink m a -> Sink m a -- | Distribute copies of the input to all the sinks in a container. -- --
--                   |-------Sink m a
--   ---stream m a---|
--                   |-------Sink m a
--                   |
--                         ...
--   
-- --
--   > let pr x = Sink.drainM (putStrLn . ((x ++ " ") ++) . show)
--   > sink (Sink.distribute [(pr "L"), (pr "R")]) (S.enumerateFromTo 1 2)
--   L 1
--   R 1
--   L 2
--   R 2
--   
-- -- This is the consumer side dual of the producer side sequence_ -- operation. distribute :: Monad m => [Sink m a] -> Sink m a -- | Demultiplex to multiple consumers without collecting the results. -- Useful to run different effectful computations depending on the value -- of the stream elements, for example handling network packets of -- different types using different handlers. -- --
--                               |-------Sink m a
--   -----stream m a-----Map-----|
--                               |-------Sink m a
--                               |
--                                         ...
--   
-- --
--   > let pr x = Sink.drainM (putStrLn . ((x ++ " ") ++) . show)
--   > let table = Data.Map.fromList [(1, pr "One"), (2, pr "Two")]
--     in Sink.sink (Sink.demux id table) (S.enumerateFromTo 1 100)
--   One 1
--   Two 2
--   
demux :: (Monad m, Ord k) => Map k (Sink m a) -> Sink m (a, k) -- | Split elements in the input stream into two parts using a monadic -- unzip function, direct each part to a different sink. -- --
--                             |-------Sink m b
--   -----Stream m a----(b,c)--|
--                             |-------Sink m c
--   
-- --
--   > let pr x = Sink.drainM (putStrLn . ((x ++ " ") ++) . show)
--     in Sink.sink (Sink.unzip return (pr "L") (pr "R")) (S.fromPure (1,2))
--   L 1
--   R 2
--   
unzipM :: Monad m => (a -> m (b, c)) -> Sink m b -> Sink m c -> Sink m a -- | Same as unzipM but with a pure unzip function. unzip :: Monad m => (a -> (b, c)) -> Sink m b -> Sink m c -> Sink m a -- | Map a pure function on the input of a Sink. lmap :: (a -> b) -> Sink m b -> Sink m a -- | Map a monadic function on the input of a Sink. lmapM :: Monad m => (a -> m b) -> Sink m b -> Sink m a -- | Filter the input of a Sink using a pure predicate function. lfilter :: Monad m => (a -> Bool) -> Sink m a -> Sink m a -- | Filter the input of a Sink using a monadic predicate function. lfilterM :: Monad m => (a -> m Bool) -> Sink m a -> Sink m a -- | Drain all input, running the effects and discarding the results. drain :: Monad m => Sink m a -- |
--   drainM f = lmapM f drain
--   
-- -- Drain all input after passing it through a monadic function. drainM :: Monad m => (a -> m b) -> Sink m a -- | Streaming and backtracking parsers. -- -- Parsers just extend folds. Please read the Fold design notes in -- Streamly.Internal.Data.Fold.Type for background on the design. -- --

Parser Design

-- -- The Parser type or a parsing fold is a generalization of the -- Fold type. The Fold type always succeeds on each -- input. Therefore, it does not need to buffer the input. In contrast, a -- Parser may fail and backtrack to replay the input again to -- explore another branch of the parser. Therefore, it needs to buffer -- the input. Therefore, a Parser is a fold with some additional -- requirements. To summarize, unlike a Fold, a Parser: -- --
    --
  1. may not generate a new value of the accumulator on every input, it -- may generate a new accumulator only after consuming multiple input -- elements (e.g. takeEQ).
  2. --
  3. on success may return some unconsumed input (e.g. takeWhile)
  4. --
  5. may fail and return all input without consuming it (e.g. -- satisfy)
  6. --
  7. backtrack and start inspecting the past input again (e.g. -- alt)
  8. --
-- -- These use cases require buffering and replaying of input. To -- facilitate this, the step function of the Fold is augmented to -- return the next state of the fold along with a command tag using a -- Step functor, the tag tells the fold driver to manipulate the -- future input as the parser wishes. The Step functor provides -- the following commands to the fold driver corresponding to the use -- cases outlined in the previous para: -- --
    --
  1. Continue: buffer the current input and optionally go back -- to a previous position in the stream
  2. --
  3. Partial: buffer the current input and optionally go back to -- a previous position in the stream, drop the buffer before that -- position.
  4. --
  5. Done: parser succeeded, returns how much input was -- leftover
  6. --
  7. Error: indicates that the parser has failed without a -- result
  8. --
-- --

How a Parser Works?

-- -- A parser is just like a fold, it keeps consuming inputs from the -- stream and accumulating them in an accumulator. The accumulator of the -- parser could be a singleton value or it could be a collection of -- values e.g. a list. -- -- The parser may build a new output value from multiple input items. -- When it consumes an input item but needs more input to build a -- complete output item it uses Continue 0 s, yielding the -- intermediate state s and asking the driver to provide more -- input. When the parser determines that a new output value is complete -- it can use a Done n b to terminate the parser with n -- items of input unused and the final value of the accumulator returned -- as b. If at any time the parser determines that the parse has -- failed it can return Error err. -- -- A parser building a collection of values (e.g. a list) can use the -- Partial constructor whenever a new item in the output -- collection is generated. If a parser building a collection of values -- has yielded at least one value then it considered successful and -- cannot fail after that. In the current implementation, this is not -- automatically enforced, there is a rule that the parser MUST use only -- Done for termination after the first Partial, it -- cannot use Error. It may be possible to change the -- implementation so that this rule is not required, but there may be -- some performance cost to it. -- -- takeWhile and some combinators are good examples of -- efficient implementations using all features of this representation. -- It is possible to idiomatically build a collection of parsed items -- using a singleton parser and Alternative instance instead of -- using a multi-yield parser. However, this implementation is amenable -- to stream fusion and can therefore be much faster. -- --

Error Handling

-- -- When a parser's step function is invoked it may terminate by -- either a Done or an Error return value. In an -- Alternative composition an error return can make the composed -- parser backtrack and try another parser. -- -- If the stream stops before a parser could terminate then we use the -- extract function of the parser to retrieve the last yielded -- value of the parser. If the parser has yielded at least one value then -- extract MUST return a value without throwing an error, -- otherwise it uses the ParseError exception to throw an error. -- -- We chose the exception throwing mechanism for extract instead -- of using an explicit error return via an Either type for -- keeping the interface simple as most of the time we do not need to -- catch the error in intermediate layers. Note that we cannot use -- exception throwing mechanism in step function because of -- performance reasons. Error constructor in that case allows loop -- fusion and better performance. -- --

Future Work

-- -- It may make sense to move "takeWhile" type of parsers, which cannot -- fail but need some lookahead, to splitting folds. This will allow such -- combinators to be accepted where we need an unfailing Fold -- type. -- -- Based on application requirements it should be possible to design even -- a richer interface to manipulate the input stream/buffer. For example, -- we could randomly seek into the stream in the forward or reverse -- directions or we can even seek to the end or from the end or seek from -- the beginning. -- -- We can distribute and scan/parse a stream using both folds and parsers -- and merge the resulting streams using different merge strategies (e.g. -- interleaving or serial). module Streamly.Internal.Data.Parser.ParserD.Type -- | The type of a Parser's initial action. -- -- Internal data Initial s b -- | Wait for step function to be called with state s. IPartial :: !s -> Initial s b -- | Return a result right away without an input. IDone :: !b -> Initial s b -- | Return an error right away without an input. IError :: String -> Initial s b -- | The return type of a Parser step. -- -- The parse operation feeds the input stream to the parser one element -- at a time, representing a parse Step. The parser may or may not -- consume the item and returns a result. If the result is Partial -- we can either extract the result or feed more input to the parser. If -- the result is Continue, we must feed more input in order to get -- a result. If the parser returns Done then the parser can no -- longer take any more input. -- -- If the result is Continue, the parse operation retains the -- input in a backtracking buffer, in case the parser may ask to -- backtrack in future. Whenever a 'Partial n' result is returned we -- first backtrack by n elements in the input and then release -- any remaining backtracking buffer. Similarly, 'Continue n' backtracks -- to n elements before the current position and starts feeding -- the input from that point for future invocations of the parser. -- -- If parser is not yet done, we can use the extract operation -- on the state of the parser to extract a result. If the parser -- has not yet yielded a result, the operation fails with a -- ParseError exception. If the parser yielded a Partial -- result in the past the last partial result is returned. Therefore, if -- a parser yields a partial result once it cannot fail later on. -- -- The parser can never backtrack beyond the position where the last -- partial result left it at. The parser must ensure that the backtrack -- position is always after that. -- -- Pre-release data Step s b -- | Partial result with an optional backtrack request. -- -- Partial count state means a partial result is available which -- can be extracted successfully, state is the opaque state of -- the parser to be supplied to the next invocation of the step -- operation. The current input position is reset to count -- elements back and any input before that is dropped from the backtrack -- buffer. Partial :: Int -> s -> Step s b -- | Need more input with an optional backtrack request. -- -- Continue count state means the parser has consumed the -- current input but no new result is generated, state is the -- next state of the parser. The current input is retained in the -- backtrack buffer and the input position is reset to count -- elements back. Continue :: Int -> s -> Step s b -- | Done with leftover input count and result. -- -- Done count result means the parser has finished, it will -- accept no more input, last count elements from the input are -- unused and the result of the parser is in result. Done :: Int -> b -> Step s b -- | Parser failed without generating any output. -- -- The parsing operation may backtrack to the beginning and try another -- alternative. Error :: String -> Step s b -- | A parser is a fold that can fail and is represented as Parser step -- initial extract. Before we drive a parser we call the -- initial action to retrieve the initial state of the fold. The -- parser driver invokes step with the state returned by the -- previous step and the next input element. It results into a new state -- and a command to the driver represented by Step type. The -- driver keeps invoking the step function until it stops or fails. At -- any point of time the driver can call extract to inspect the -- result of the fold. If the parser hits the end of input -- extract is called. It may result in an error or an output -- value. -- -- Pre-release data Parser m a b Parser :: (s -> a -> m (Step s b)) -> m (Initial s b) -> (s -> m b) -> Parser m a b -- | This exception is used for two purposes: -- -- -- -- Pre-release newtype ParseError ParseError :: String -> ParseError -- | Map a monadic function on the output of a parser. -- -- Pre-release rmapM :: Monad m => (b -> m c) -> Parser m a b -> Parser m a c -- | See fromPure. -- -- Pre-release fromPure :: Monad m => b -> Parser m a b -- | See fromEffect. -- -- Pre-release fromEffect :: Monad m => m b -> Parser m a b -- | See serialWith. -- -- Note: this implementation of serialWith is fast because of stream -- fusion but has quadratic time complexity, because each composition -- adds a new branch that each subsequent parse's input element has to go -- through, therefore, it cannot scale to a large number of compositions. -- After around 100 compositions the performance starts dipping rapidly -- beyond a CPS style unfused implementation. -- -- Pre-release serialWith :: MonadThrow m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | See split_. -- -- Pre-release split_ :: MonadThrow m => Parser m x a -> Parser m x b -> Parser m x b -- | See die. -- -- Pre-release die :: MonadThrow m => String -> Parser m a b -- | See dieM. -- -- Pre-release dieM :: MonadThrow m => m String -> Parser m a b -- | See documentation of some. -- -- Pre-release splitSome :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c -- | See documentation of many. -- -- Pre-release splitMany :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c -- | Like splitMany, but inner fold emits an output at the end even if no -- input is received. -- -- Internal splitManyPost :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c -- | See alt. -- -- Pre-release alt :: Monad m => Parser m x a -> Parser m x a -> Parser m x a -- | See concatMap. -- -- Pre-release concatMap :: MonadThrow m => (b -> Parser m a c) -> Parser m a b -> Parser m a c noErrorUnsafeSplit_ :: MonadThrow m => Parser m x a -> Parser m x b -> Parser m x b -- | Works correctly only if the first parser is guaranteed to never fail. noErrorUnsafeSplitWith :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c noErrorUnsafeConcatMap :: MonadThrow m => (b -> Parser m a c) -> Parser m a b -> Parser m a c instance GHC.Show.Show Streamly.Internal.Data.Parser.ParserD.Type.ParseError instance GHC.Exception.Type.Exception Streamly.Internal.Data.Parser.ParserD.Type.ParseError instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Parser.ParserD.Type.Parser m a) instance Control.Monad.Catch.MonadThrow m => GHC.Base.Applicative (Streamly.Internal.Data.Parser.ParserD.Type.Parser m a) instance Control.Monad.Catch.MonadCatch m => GHC.Base.Alternative (Streamly.Internal.Data.Parser.ParserD.Type.Parser m a) instance Control.Monad.Catch.MonadThrow m => GHC.Base.Monad (Streamly.Internal.Data.Parser.ParserD.Type.Parser m a) instance Control.Monad.Catch.MonadCatch m => GHC.Base.MonadPlus (Streamly.Internal.Data.Parser.ParserD.Type.Parser m a) instance (Control.Monad.Catch.MonadThrow m, Control.Monad.Reader.Class.MonadReader r m, Control.Monad.Catch.MonadCatch m) => Control.Monad.Reader.Class.MonadReader r (Streamly.Internal.Data.Parser.ParserD.Type.Parser m a) instance (Control.Monad.Catch.MonadThrow m, Control.Monad.State.Class.MonadState s m) => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Parser.ParserD.Type.Parser m a) instance (Control.Monad.Catch.MonadThrow m, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Parser.ParserD.Type.Parser m a) instance GHC.Base.Functor (Streamly.Internal.Data.Parser.ParserD.Type.Step s) instance Data.Bifunctor.Bifunctor Streamly.Internal.Data.Parser.ParserD.Type.Initial instance GHC.Base.Functor (Streamly.Internal.Data.Parser.ParserD.Type.Initial s) -- | CPS style implementation of parsers. -- -- The CPS representation allows linear performance for Applicative, -- sequenceA, Monad, sequence, and Alternative, choice operations -- compared to the quadratic complexity of the corresponding direct style -- operations. However, direct style operations allow fusion with ~10x -- better performance than CPS. -- -- The direct style representation does not allow for recursive -- definitions of "some" and "many" whereas CPS allows that. module Streamly.Internal.Data.Parser.ParserK.Type -- | A continuation passing style parser representation. newtype Parser m a b MkParser :: (forall r. Int -> (Int, Int) -> ((Int, Int) -> Parse b -> m (Driver m a r)) -> m (Driver m a r)) -> Parser m a b [runParser] :: Parser m a b -> forall r. Int -> (Int, Int) -> ((Int, Int) -> Parse b -> m (Driver m a r)) -> m (Driver m a r) -- | A parser that always yields a pure value without consuming any input. -- -- Pre-release fromPure :: b -> Parser m a b -- | See fromEffect. -- -- Pre-release fromEffect :: Monad m => m b -> Parser m a b -- | A parser that always fails with an error message without consuming any -- input. -- -- Pre-release die :: String -> Parser m a b -- | Convert a direct style Parser to a CPS style Parser. -- -- Pre-release toParserK :: MonadCatch m => Parser m a b -> Parser m a b -- | Convert a CPS style Parser to a direct style Parser. -- -- "initial" returns a continuation which can be called one input at a -- time using the "step" function. -- -- Pre-release fromParserK :: MonadThrow m => Parser m a b -> Parser m a b instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Parser.ParserK.Type.Parser m a) instance GHC.Base.Monad m => GHC.Base.Applicative (Streamly.Internal.Data.Parser.ParserK.Type.Parser m a) instance GHC.Base.Monad m => GHC.Base.Monad (Streamly.Internal.Data.Parser.ParserK.Type.Parser m a) instance GHC.Base.Monad m => Control.Monad.Fail.MonadFail (Streamly.Internal.Data.Parser.ParserK.Type.Parser m a) instance (Control.Monad.Catch.MonadThrow m, Control.Monad.Reader.Class.MonadReader r m, Control.Monad.Catch.MonadCatch m) => Control.Monad.Reader.Class.MonadReader r (Streamly.Internal.Data.Parser.ParserK.Type.Parser m a) instance (Control.Monad.Catch.MonadThrow m, Control.Monad.State.Class.MonadState s m) => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Parser.ParserK.Type.Parser m a) instance (Control.Monad.Catch.MonadThrow m, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Parser.ParserK.Type.Parser m a) instance GHC.Base.Monad m => GHC.Base.Alternative (Streamly.Internal.Data.Parser.ParserK.Type.Parser m a) instance GHC.Base.Monad m => GHC.Base.MonadPlus (Streamly.Internal.Data.Parser.ParserK.Type.Parser m a) instance GHC.Base.Functor Streamly.Internal.Data.Parser.ParserK.Type.Parse instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Parser.ParserK.Type.Driver m a) -- | Parallel parsers. Distributing the input to multiple parsers at the -- same time. -- -- For simplicity, we are using code where a particular state is -- unreachable but it is not prevented by types. Somehow uni-pattern -- match using "let" produces better optimized code compared to using -- case match and using explicit error messages in unreachable -- cases. -- -- There seem to be no way to silence individual warnings so we use a -- global incomplete uni-pattern match warning suppression option for the -- file. Disabling the warning for other code as well has the potential -- to mask off some legit warnings, therefore, we have segregated only -- the code that uses uni-pattern matches in this module. module Streamly.Internal.Data.Parser.ParserD.Tee -- | See teeWith. -- -- Broken teeWith :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | See teeWithFst. -- -- Broken teeWithFst :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | See teeWithMin. -- -- Unimplemented teeWithMin :: (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | See shortest. -- -- Broken shortest :: Monad m => Parser m x a -> Parser m x a -> Parser m x a -- | See longest. -- -- Broken longest :: MonadCatch m => Parser m x a -> Parser m x a -> Parser m x a -- | Direct style parser implementation with stream fusion. module Streamly.Internal.Data.Parser.ParserD -- | A parser is a fold that can fail and is represented as Parser step -- initial extract. Before we drive a parser we call the -- initial action to retrieve the initial state of the fold. The -- parser driver invokes step with the state returned by the -- previous step and the next input element. It results into a new state -- and a command to the driver represented by Step type. The -- driver keeps invoking the step function until it stops or fails. At -- any point of time the driver can call extract to inspect the -- result of the fold. If the parser hits the end of input -- extract is called. It may result in an error or an output -- value. -- -- Pre-release data Parser m a b Parser :: (s -> a -> m (Step s b)) -> m (Initial s b) -> (s -> m b) -> Parser m a b -- | This exception is used for two purposes: -- -- -- -- Pre-release newtype ParseError ParseError :: String -> ParseError -- | The return type of a Parser step. -- -- The parse operation feeds the input stream to the parser one element -- at a time, representing a parse Step. The parser may or may not -- consume the item and returns a result. If the result is Partial -- we can either extract the result or feed more input to the parser. If -- the result is Continue, we must feed more input in order to get -- a result. If the parser returns Done then the parser can no -- longer take any more input. -- -- If the result is Continue, the parse operation retains the -- input in a backtracking buffer, in case the parser may ask to -- backtrack in future. Whenever a 'Partial n' result is returned we -- first backtrack by n elements in the input and then release -- any remaining backtracking buffer. Similarly, 'Continue n' backtracks -- to n elements before the current position and starts feeding -- the input from that point for future invocations of the parser. -- -- If parser is not yet done, we can use the extract operation -- on the state of the parser to extract a result. If the parser -- has not yet yielded a result, the operation fails with a -- ParseError exception. If the parser yielded a Partial -- result in the past the last partial result is returned. Therefore, if -- a parser yields a partial result once it cannot fail later on. -- -- The parser can never backtrack beyond the position where the last -- partial result left it at. The parser must ensure that the backtrack -- position is always after that. -- -- Pre-release data Step s b -- | Partial result with an optional backtrack request. -- -- Partial count state means a partial result is available which -- can be extracted successfully, state is the opaque state of -- the parser to be supplied to the next invocation of the step -- operation. The current input position is reset to count -- elements back and any input before that is dropped from the backtrack -- buffer. Partial :: Int -> s -> Step s b -- | Need more input with an optional backtrack request. -- -- Continue count state means the parser has consumed the -- current input but no new result is generated, state is the -- next state of the parser. The current input is retained in the -- backtrack buffer and the input position is reset to count -- elements back. Continue :: Int -> s -> Step s b -- | Done with leftover input count and result. -- -- Done count result means the parser has finished, it will -- accept no more input, last count elements from the input are -- unused and the result of the parser is in result. Done :: Int -> b -> Step s b -- | Parser failed without generating any output. -- -- The parsing operation may backtrack to the beginning and try another -- alternative. Error :: String -> Step s b -- | The type of a Parser's initial action. -- -- Internal data Initial s b -- | Wait for step function to be called with state s. IPartial :: !s -> Initial s b -- | Return a result right away without an input. IDone :: !b -> Initial s b -- | Return an error right away without an input. IError :: String -> Initial s b -- | Map a monadic function on the output of a parser. -- -- Pre-release rmapM :: Monad m => (b -> m c) -> Parser m a b -> Parser m a c -- | See toFold. -- -- Internal toFold :: MonadThrow m => Parser m a b -> Fold m a b -- | See fromFold. -- -- Pre-release fromFold :: Monad m => Fold m a b -> Parser m a b -- | See fromPure. -- -- Pre-release fromPure :: Monad m => b -> Parser m a b -- | See fromEffect. -- -- Pre-release fromEffect :: Monad m => m b -> Parser m a b -- | See die. -- -- Pre-release die :: MonadThrow m => String -> Parser m a b -- | See dieM. -- -- Pre-release dieM :: MonadThrow m => m String -> Parser m a b -- | See peek. -- -- Pre-release peek :: MonadThrow m => Parser m a a -- | See eof. -- -- Pre-release eof :: Monad m => Parser m a () -- | See satisfy. -- -- Pre-release satisfy :: MonadThrow m => (a -> Bool) -> Parser m a a -- | See next. -- -- Pre-release next :: Monad m => Parser m a (Maybe a) -- | See maybe. -- -- Pre-release maybe :: MonadThrow m => (a -> Maybe b) -> Parser m a b -- | See either. -- -- Pre-release either :: MonadThrow m => (a -> Either String b) -> Parser m a b -- | See takeBetween. -- -- Pre-release takeBetween :: MonadCatch m => Int -> Int -> Fold m a b -> Parser m a b -- | See takeEQ. -- -- Pre-release takeEQ :: MonadThrow m => Int -> Fold m a b -> Parser m a b -- | See takeGE. -- -- Pre-release takeGE :: MonadThrow m => Int -> Fold m a b -> Parser m a b -- | See takeP. -- -- Internal takeP :: Monad m => Int -> Parser m a b -> Parser m a b -- | See lookahead. -- -- Pre-release lookAhead :: MonadThrow m => Parser m a b -> Parser m a b -- | See takeWhile. -- -- Pre-release takeWhile :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b -- | See takeWhile1. -- -- Pre-release takeWhile1 :: MonadThrow m => (a -> Bool) -> Fold m a b -> Parser m a b -- | See sliceSepByP. -- -- Pre-release sliceSepByP :: MonadCatch m => (a -> Bool) -> Parser m a b -> Parser m a b sliceBeginWith :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b -- | See wordBy. wordBy :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b -- | See groupBy. groupBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Parser m a b -- | See groupByRolling. groupByRolling :: Monad m => (a -> a -> Bool) -> Fold m a b -> Parser m a b groupByRollingEither :: MonadCatch m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (Either b c) -- | See eqBy. -- -- Pre-release eqBy :: MonadThrow m => (a -> a -> Bool) -> [a] -> Parser m a () -- | span p f1 f2 composes folds f1 and f2 such -- that f1 consumes the input as long as the predicate -- p is True. f2 consumes the rest of the input. -- --
--   > let span_ p xs = Stream.parse (Parser.span p Fold.toList Fold.toList) $ Stream.fromList xs
--   
--   > span_ (< 1) 1,2,3
--   
--   > span_ (< 2) 1,2,3
--   
--   > span_ (< 4) 1,2,3
--   
-- -- Pre-release span :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (b, c) -- | Break the input stream into two groups, the first group takes the -- input as long as the predicate applied to the first element of the -- stream and next input element holds True, the second group -- takes the rest of the input. -- -- Pre-release spanBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (b, c) -- | Like spanBy but applies the predicate in a rolling fashion i.e. -- predicate is applied to the previous and the next input elements. -- -- Pre-release spanByRolling :: Monad m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (b, c) -- | See serialWith. -- -- Note: this implementation of serialWith is fast because of stream -- fusion but has quadratic time complexity, because each composition -- adds a new branch that each subsequent parse's input element has to go -- through, therefore, it cannot scale to a large number of compositions. -- After around 100 compositions the performance starts dipping rapidly -- beyond a CPS style unfused implementation. -- -- Pre-release serialWith :: MonadThrow m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | See split_. -- -- Pre-release split_ :: MonadThrow m => Parser m x a -> Parser m x b -> Parser m x b -- | See teeWith. -- -- Broken teeWith :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | See teeWithFst. -- -- Broken teeWithFst :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | See teeWithMin. -- -- Unimplemented teeWithMin :: (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | See deintercalate. -- -- Unimplemented deintercalate :: Fold m a y -> Parser m x a -> Fold m b z -> Parser m x b -> Parser m x (y, z) -- | See alt. -- -- Pre-release alt :: Monad m => Parser m x a -> Parser m x a -> Parser m x a -- | See shortest. -- -- Broken shortest :: Monad m => Parser m x a -> Parser m x a -> Parser m x a -- | See longest. -- -- Broken longest :: MonadCatch m => Parser m x a -> Parser m x a -> Parser m x a -- | See sequence. -- -- Unimplemented sequence :: Fold m b c -> t (Parser m a b) -> Parser m a c -- | See concatMap. -- -- Pre-release concatMap :: MonadThrow m => (b -> Parser m a c) -> Parser m a b -> Parser m a c -- | See count. -- -- Unimplemented count :: Int -> Parser m a b -> Fold m b c -> Parser m a c -- | See countBetween. -- -- Unimplemented countBetween :: Int -> Int -> Parser m a b -> Fold m b c -> Parser m a c -- | See many. -- -- Pre-release many :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c -- | See some. -- -- Pre-release some :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c -- | See manyTill. -- -- Pre-release manyTill :: MonadCatch m => Fold m b c -> Parser m a b -> Parser m a x -> Parser m a c -- | See choice. -- -- Broken choice :: (MonadCatch m, Foldable t) => t (Parser m a b) -> Parser m a b instance GHC.Show.Show Streamly.Internal.Data.Parser.ParserD.ParserToFoldError instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Streamly.Internal.Data.Parser.ParserD.Tuple'Fused a b) instance GHC.Exception.Type.Exception Streamly.Internal.Data.Parser.ParserD.ParserToFoldError -- | A Source is a seed that can be unfolded to a stream with a -- buffer. Allows to unread data i.e. push unused data back to the -- source buffer. This is useful in parsing applications with -- backtracking. module Streamly.Internal.Data.Producer.Source -- | A seed with a buffer. It allows us to unread or return some -- data after reading it. Useful in backtracked parsing. data Source a b -- | Make a source from a seed value. The buffer would start as empty. -- -- Pre-release source :: Maybe a -> Source a b -- | Return some unused data back to the source. The data is prepended (or -- consed) to the source. -- -- Pre-release unread :: [b] -> Source a b -> Source a b -- | Determine if the source is empty. isEmpty :: Source a b -> Bool -- | Convert a producer to a producer from a buffered source. Any buffered -- data is read first and then the seed is unfolded. -- -- Pre-release producer :: Monad m => Producer m a b -> Producer m (Source a b) b -- | Parse a buffered source using a parser, returning the parsed value and -- the remaining source. -- -- Pre-release parse :: MonadThrow m => Parser m a b -> Producer m (Source s a) a -> Source s a -> m (b, Source s a) -- | Apply a parser repeatedly on a buffered source producer to generate a -- producer of parsed values. -- -- Pre-release parseMany :: MonadThrow m => Parser m a b -> Producer m (Source x a) a -> Producer m (Source x a) b parseManyD :: MonadThrow m => Parser m a b -> Producer m (Source x a) a -> Producer m (Source x a) b -- | Fast backtracking parsers with stream fusion and native streaming -- capability. -- -- Applicative and Alternative type class based combinators -- from the parser-combinators package can also be used with the -- Parser type. However, there are two important differences -- between parser-combinators and the equivalent ones provided -- in this module in terms of performance: -- -- 1) parser-combinators use plain Haskell lists to collect the -- results, in a strict Monad like IO, the results are necessarily -- buffered before they can be consumed. This may not perform optimally -- in streaming applications processing large amounts of data. Equivalent -- combinators in this module can consume the results of parsing using a -- Fold, thus providing a scalability and a composable consumer. -- -- 2) Several combinators in this module can be many times faster because -- of stream fusion. For example, many combinator in this module -- is much faster than the many combinator of Alternative -- type class. -- --

Errors

-- -- Failing parsers in this module throw the ParseError exception. -- --

Naming

-- -- As far as possible, try that the names of the combinators in this -- module are consistent with: -- -- module Streamly.Internal.Data.Parser -- | A continuation passing style parser representation. newtype Parser m a b MkParser :: (forall r. Int -> (Int, Int) -> ((Int, Int) -> Parse b -> m (Driver m a r)) -> m (Driver m a r)) -> Parser m a b [runParser] :: Parser m a b -> forall r. Int -> (Int, Int) -> ((Int, Int) -> Parse b -> m (Driver m a r)) -> m (Driver m a r) -- | This exception is used for two purposes: -- -- -- -- Pre-release newtype ParseError ParseError :: String -> ParseError -- | The return type of a Parser step. -- -- The parse operation feeds the input stream to the parser one element -- at a time, representing a parse Step. The parser may or may not -- consume the item and returns a result. If the result is Partial -- we can either extract the result or feed more input to the parser. If -- the result is Continue, we must feed more input in order to get -- a result. If the parser returns Done then the parser can no -- longer take any more input. -- -- If the result is Continue, the parse operation retains the -- input in a backtracking buffer, in case the parser may ask to -- backtrack in future. Whenever a 'Partial n' result is returned we -- first backtrack by n elements in the input and then release -- any remaining backtracking buffer. Similarly, 'Continue n' backtracks -- to n elements before the current position and starts feeding -- the input from that point for future invocations of the parser. -- -- If parser is not yet done, we can use the extract operation -- on the state of the parser to extract a result. If the parser -- has not yet yielded a result, the operation fails with a -- ParseError exception. If the parser yielded a Partial -- result in the past the last partial result is returned. Therefore, if -- a parser yields a partial result once it cannot fail later on. -- -- The parser can never backtrack beyond the position where the last -- partial result left it at. The parser must ensure that the backtrack -- position is always after that. -- -- Pre-release data Step s b -- | Partial result with an optional backtrack request. -- -- Partial count state means a partial result is available which -- can be extracted successfully, state is the opaque state of -- the parser to be supplied to the next invocation of the step -- operation. The current input position is reset to count -- elements back and any input before that is dropped from the backtrack -- buffer. Partial :: Int -> s -> Step s b -- | Need more input with an optional backtrack request. -- -- Continue count state means the parser has consumed the -- current input but no new result is generated, state is the -- next state of the parser. The current input is retained in the -- backtrack buffer and the input position is reset to count -- elements back. Continue :: Int -> s -> Step s b -- | Done with leftover input count and result. -- -- Done count result means the parser has finished, it will -- accept no more input, last count elements from the input are -- unused and the result of the parser is in result. Done :: Int -> b -> Step s b -- | Parser failed without generating any output. -- -- The parsing operation may backtrack to the beginning and try another -- alternative. Error :: String -> Step s b -- | Make a Fold from a Parser. The fold just throws an -- exception if the parser fails or tries to backtrack. -- -- This can be useful in combinators that accept a Fold and we know that -- a Parser cannot fail or failure exception is acceptable as there is no -- way to recover. -- -- Pre-release toFold :: MonadThrow m => Parser m a b -> Fold m a b -- | Make a Parser from a Fold. -- -- Pre-release fromFold :: MonadCatch m => Fold m a b -> Parser m a b -- | A parser that always yields a pure value without consuming any input. -- -- Pre-release fromPure :: MonadCatch m => b -> Parser m a b -- | A parser that always yields the result of an effectful action without -- consuming any input. -- -- Pre-release fromEffect :: MonadCatch m => m b -> Parser m a b -- | A parser that always fails with an error message without consuming any -- input. -- -- Pre-release die :: MonadCatch m => String -> Parser m a b -- | A parser that always fails with an effectful error message and without -- consuming any input. -- -- Pre-release dieM :: MonadCatch m => m String -> Parser m a b -- | Peek the head element of a stream, without consuming it. Fails if it -- encounters end of input. -- --
--   >>> Stream.parse ((,) <$> Parser.peek <*> Parser.satisfy (> 0)) $ Stream.fromList [1]
--   (1,1)
--   
-- --
--   peek = lookAhead (satisfy True)
--   
-- -- Pre-release peek :: MonadCatch m => Parser m a a -- | Succeeds if we are at the end of input, fails otherwise. -- --
--   >>> Stream.parse ((,) <$> Parser.satisfy (> 0) <*> Parser.eof) $ Stream.fromList [1]
--   (1,())
--   
-- -- Pre-release eof :: MonadCatch m => Parser m a () -- | Returns the next element if it passes the predicate, fails otherwise. -- --
--   >>> Stream.parse (Parser.satisfy (== 1)) $ Stream.fromList [1,0,1]
--   1
--   
-- -- Pre-release satisfy :: MonadCatch m => (a -> Bool) -> Parser m a a -- | Return the next element of the input. Returns Nothing on end of -- input. Also known as head. -- -- Pre-release next :: MonadCatch m => Parser m a (Maybe a) -- | Map a Maybe returning function on the next element in the -- stream. The parser fails if the function returns Nothing -- otherwise returns the Just value. -- -- Pre-release maybe :: MonadCatch m => (a -> Maybe b) -> Parser m a b -- | Map an Either returning function on the next element in the -- stream. If the function returns 'Left err', the parser fails with the -- error message err otherwise returns the Right value. -- -- Pre-release either :: MonadCatch m => (a -> Either String b) -> Parser m a b -- | takeBetween m n takes a minimum of m and a maximum -- of n input elements and folds them using the supplied fold. -- -- Stops after n elements. Fails if the stream ends before -- m elements could be taken. -- -- Examples: - -- --
--   >>> :{
--     takeBetween' low high ls = Stream.parse prsr (Stream.fromList ls)
--       where prsr = Parser.takeBetween low high Fold.toList
--   :}
--   
-- --
--   >>> takeBetween' 2 4 [1, 2, 3, 4, 5]
--   [1,2,3,4]
--   
-- --
--   >>> takeBetween' 2 4 [1, 2]
--   [1,2]
--   
-- --
--   >>> takeBetween' 2 4 [1]
--   *** Exception: ParseError "takeBetween: Expecting alteast 2 elements, got 1"
--   
-- --
--   >>> takeBetween' 0 0 [1, 2]
--   []
--   
-- --
--   >>> takeBetween' 0 1 []
--   []
--   
-- -- takeBetween is the most general take operation, other take -- operations can be defined in terms of takeBetween. For example: -- --
--   take = takeBetween 0 n  -- equivalent of take
--   take1 = takeBetween 1 n -- equivalent of takeLE1
--   takeEQ = takeBetween n n
--   takeGE = takeBetween n maxBound
--   
-- -- Pre-release takeBetween :: MonadCatch m => Int -> Int -> Fold m a b -> Parser m a b -- | Stops after taking exactly n input elements. -- -- -- --
--   >>> Stream.parse (Parser.takeEQ 4 Fold.toList) $ Stream.fromList [1,0,1]
--   *** Exception: ParseError "takeEQ: Expecting exactly 4 elements, input terminated on 3"
--   
-- -- Pre-release takeEQ :: MonadCatch m => Int -> Fold m a b -> Parser m a b -- | Take at least n input elements, but can collect more. -- -- -- --
--   >>> Stream.parse (Parser.takeGE 4 Fold.toList) $ Stream.fromList [1,0,1]
--   *** Exception: ParseError "takeGE: Expecting at least 4 elements, input terminated on 3"
--   
-- --
--   >>> Stream.parse (Parser.takeGE 4 Fold.toList) $ Stream.fromList [1,0,1,0,1]
--   [1,0,1,0,1]
--   
-- -- Pre-release takeGE :: MonadCatch m => Int -> Fold m a b -> Parser m a b -- | Takes at-most n input elements. -- -- -- --
--   >>> Stream.parse (Parser.takeP 4 (Parser.takeEQ 2 Fold.toList)) $ Stream.fromList [1, 2, 3, 4, 5]
--   [1,2]
--   
-- --
--   >>> Stream.parse (Parser.takeP 4 (Parser.takeEQ 5 Fold.toList)) $ Stream.fromList [1, 2, 3, 4, 5]
--   *** Exception: ParseError "takeEQ: Expecting exactly 5 elements, input terminated on 4"
--   
-- -- Internal takeP :: MonadCatch m => Int -> Parser m a b -> Parser m a b -- | Run a parser without consuming the input. -- -- Pre-release lookAhead :: MonadCatch m => Parser m a b -> Parser m a b -- | Like takeWhile but uses a Parser instead of a -- Fold to collect the input. The combinator stops when the -- condition fails or if the collecting parser stops. -- -- This is a generalized version of takeWhile, for example -- takeWhile1 can be implemented in terms of this: -- --
--   takeWhile1 cond p = takeWhile cond (takeBetween 1 maxBound p)
--   
-- -- Stops: when the condition fails or the collecting parser stops. Fails: -- when the collecting parser fails. -- -- Unimplemented takeWhileP :: (a -> Bool) -> Parser m a b -> Parser m a b -- | Collect stream elements until an element fails the predicate. The -- element on which the predicate fails is returned back to the input -- stream. -- -- -- --
--   >>> Stream.parse (Parser.takeWhile (== 0) Fold.toList) $ Stream.fromList [0,0,1,0,1]
--   [0,0]
--   
-- -- We can implement a breakOn using takeWhile: -- --
--   breakOn p = takeWhile (not p)
--   
-- -- Pre-release takeWhile :: MonadCatch m => (a -> Bool) -> Fold m a b -> Parser m a b -- | Like takeWhile but takes at least one element otherwise fails. -- -- Pre-release takeWhile1 :: MonadCatch m => (a -> Bool) -> Fold m a b -> Parser m a b -- | Drain the input as long as the predicate succeeds, running the effects -- and discarding the results. -- -- This is also called skipWhile in some parsing libraries. -- -- Pre-release drainWhile :: MonadCatch m => (a -> Bool) -> Parser m a () -- | sliceSepByP cond parser parses a slice of the input using -- parser until cond succeeds or the parser stops. -- -- This is a generalized slicing parser which can be used to implement -- other parsers e.g.: -- --
--   sliceSepByMax cond n p = sliceSepByP cond (take n p)
--   sliceSepByBetween cond m n p = sliceSepByP cond (takeBetween m n p)
--   
-- -- Pre-release sliceSepByP :: MonadCatch m => (a -> Bool) -> Parser m a b -> Parser m a b -- | Collect stream elements until an elements passes the predicate, return -- the last element on which the predicate succeeded back to the input -- stream. If the predicate succeeds on the first element itself then the -- parser does not terminate there. The succeeding element in the leading -- position is treated as a prefix separator which is kept in the output -- segment. -- -- -- -- S.splitWithPrefix pred f = S.parseMany (PR.sliceBeginWith pred f) -- -- Examples: - -- --
--   >>> :{
--    sliceBeginWithOdd ls = Stream.parse prsr (Stream.fromList ls)
--        where prsr = Parser.sliceBeginWith odd Fold.toList
--   :}
--   
-- --
--   >>> sliceBeginWithOdd [2, 4, 6, 3]
--   *** Exception: sliceBeginWith : slice begins with an element which fails the predicate
--   ...
--   
-- --
--   >>> sliceBeginWithOdd [3, 5, 7, 4]
--   [3]
--   
-- --
--   >>> sliceBeginWithOdd [3, 4, 6, 8, 5]
--   [3,4,6,8]
--   
-- --
--   >>> sliceBeginWithOdd []
--   []
--   
-- -- Pre-release sliceBeginWith :: MonadCatch m => (a -> Bool) -> Fold m a b -> Parser m a b -- | Like sliceSepBy but does not drop the separator element, -- instead separator is emitted as a separate element in the output. -- -- Unimplemented sliceSepWith :: (a -> Bool) -> Fold m a b -> Parser m a b -- | Like sliceSepBy but the separator elements can be escaped -- using an escape char determined by the second predicate. -- -- Unimplemented escapedSliceSepBy :: (a -> Bool) -> (a -> Bool) -> Fold m a b -> Parser m a b -- | escapedFrameBy begin end escape parses a string framed using -- begin and end as the frame begin and end marker -- elements and escape as an escaping element to escape the -- occurrence of the framing elements within the frame. Nested frames are -- allowed, but nesting is removed when parsing. -- -- For example, -- --
--   > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== \\) Fold.toList) $ Stream.fromList "{hello}"
--   "hello"
--   
--   > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== \\) Fold.toList) $ Stream.fromList "{hello {world}}"
--   "hello world"
--   
--   > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== \\) Fold.toList) $ Stream.fromList "{hello \{world\}}"
--   "hello {world}"
--   
--   > Stream.parse (Parser.escapedFrameBy (== '{') (== '}') (== \\) Fold.toList) $ Stream.fromList "{hello {world}"
--   ParseError "Unterminated '{'"
--   
-- -- Unimplemented escapedFrameBy :: (a -> Bool) -> (a -> Bool) -> (a -> Bool) -> Fold m a b -> Parser m a b -- | Like splitOn but strips leading, trailing, and repeated -- separators. Therefore, ".a..b." having . as the -- separator would be parsed as ["a","b"]. In other words, its -- like parsing words from whitespace separated text. -- -- -- --
--   S.wordsBy pred f = S.parseMany (PR.wordBy pred f)
--   
wordBy :: MonadCatch m => (a -> Bool) -> Fold m a b -> Parser m a b -- | Given an input stream [a,b,c,...] and a comparison function -- cmp, the parser assigns the element a to the first -- group, then if a `cmp` b is True b is also -- assigned to the same group. If a `cmp` c is True then -- c is also assigned to the same group and so on. When the -- comparison fails the parser is terminated. Each group is folded using -- the Fold f and the result of the fold is the result of -- the parser. -- -- -- --
--   >>> :{
--    runGroupsBy eq =
--        Stream.toList
--            . Stream.parseMany (Parser.groupBy eq Fold.toList)
--            . Stream.fromList
--   :}
--   
-- --
--   >>> runGroupsBy (<) []
--   []
--   
-- --
--   >>> runGroupsBy (<) [1]
--   [[1]]
--   
-- --
--   >>> runGroupsBy (<) [3, 5, 4, 1, 2, 0]
--   [[3,5,4],[1,2],[0]]
--   
-- -- Pre-release groupBy :: MonadCatch m => (a -> a -> Bool) -> Fold m a b -> Parser m a b -- | Unlike groupBy this combinator performs a rolling comparison of -- two successive elements in the input stream. Assuming the input stream -- to the parser is [a,b,c,...] and the comparison function is -- cmp, the parser first assigns the element a to the -- first group, then if a `cmp` b is True b is -- also assigned to the same group. If b `cmp` c is True -- then c is also assigned to the same group and so on. When the -- comparison fails the parser is terminated. Each group is folded using -- the Fold f and the result of the fold is the result of -- the parser. -- -- -- --
--   >>> :{
--    runGroupsByRolling eq =
--        Stream.toList
--            . Stream.parseMany (Parser.groupByRolling eq Fold.toList)
--            . Stream.fromList
--   :}
--   
-- --
--   >>> runGroupsByRolling (<) []
--   []
--   
-- --
--   >>> runGroupsByRolling (<) [1]
--   [[1]]
--   
-- --
--   >>> runGroupsByRolling (<) [3, 5, 4, 1, 2, 0]
--   [[3,5],[4],[1,2],[0]]
--   
-- -- Pre-release groupByRolling :: MonadCatch m => (a -> a -> Bool) -> Fold m a b -> Parser m a b -- | Like groupByRolling, but if the predicate is True then -- collects using the first fold as long as the predicate holds -- True, if the predicate is False collects using the -- second fold as long as it remains False. Returns Left -- for the first case and Right for the second case. -- -- For example, if we want to detect sorted sequences in a stream, both -- ascending and descending cases we can use 'groupByRollingEither -- (<=) Fold.toList Fold.toList'. -- -- Unimplemented groupByRollingEither :: MonadCatch m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Parser m a (Either b c) -- | Match the given sequence of elements using the given comparison -- function. -- --
--   >>> Stream.parse (Parser.eqBy (==) "string") $ Stream.fromList "string"
--   
-- --
--   >>> Stream.parse (Parser.eqBy (==) "mismatch") $ Stream.fromList "match"
--   *** Exception: ParseError "eqBy: failed, yet to match 7 elements"
--   
-- -- Pre-release eqBy :: MonadCatch m => (a -> a -> Bool) -> [a] -> Parser m a () -- | Sequential parser application. Apply two parsers sequentially to an -- input stream. The input is provided to the first parser, when it is -- done the remaining input is provided to the second parser. If both the -- parsers succeed their outputs are combined using the supplied -- function. The operation fails if any of the parsers fail. -- -- Note: This is a parsing dual of appending streams using serial, -- it splits the streams using two parsers and zips the results. -- -- This implementation is strict in the second argument, therefore, the -- following will fail: -- --
--   >>> Stream.parse (Parser.serialWith const (Parser.satisfy (> 0)) undefined) $ Stream.fromList [1]
--   *** Exception: Prelude.undefined
--   ...
--   
-- -- Compare with Applicative instance method <*>. This -- implementation allows stream fusion but has quadratic complexity. This -- can fuse with other operations and can be faster than -- Applicative instance for small number (less than 8) of -- compositions. -- -- Many combinators can be expressed using serialWith and other -- parser primitives. Some common idioms are described below, -- --
--   span :: (a -> Bool) -> Fold m a b -> Fold m a b -> Parser m a b
--   span pred f1 f2 = serialWith (,) (takeWhile pred f1) (fromFold f2)
--   
-- --
--   spanBy :: (a -> a -> Bool) -> Fold m a b -> Fold m a b -> Parser m a b
--   spanBy eq f1 f2 = serialWith (,) (groupBy eq f1) (fromFold f2)
--   
-- --
--   spanByRolling :: (a -> a -> Bool) -> Fold m a b -> Fold m a b -> Parser m a b
--   spanByRolling eq f1 f2 = serialWith (,) (groupByRolling eq f1) (fromFold f2)
--   
-- -- Pre-release serialWith :: MonadCatch m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | Sequential parser application ignoring the output of the first parser. -- Apply two parsers sequentially to an input stream. The input is -- provided to the first parser, when it is done the remaining input is -- provided to the second parser. The output of the parser is the output -- of the second parser. The operation fails if any of the parsers fail. -- -- This implementation is strict in the second argument, therefore, the -- following will fail: -- --
--   >>> Stream.parse (Parser.split_ (Parser.satisfy (> 0)) undefined) $ Stream.fromList [1]
--   *** Exception: Prelude.undefined
--   ...
--   
-- -- Compare with Applicative instance method *>. This -- implementation allows stream fusion but has quadratic complexity. This -- can fuse with other operations, and can be faster than -- Applicative instance for small number (less than 8) of -- compositions. -- -- Pre-release split_ :: MonadCatch m => Parser m x a -> Parser m x b -> Parser m x b -- | teeWith f p1 p2 distributes its input to both p1 and -- p2 until both of them succeed or anyone of them fails and -- combines their output using f. The parser succeeds if both -- the parsers succeed. -- -- Pre-release teeWith :: MonadCatch m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | Like teeWith but ends parsing and zips the results, if -- available, whenever the first parser ends. -- -- Pre-release teeWithFst :: MonadCatch m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | Like teeWith but ends parsing and zips the results, if -- available, whenever any of the parsers ends or fails. -- -- Unimplemented teeWithMin :: MonadCatch m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | Apply two parsers alternately to an input stream. The input stream is -- considered an interleaving of two patterns. The two parsers represent -- the two patterns. -- -- This undoes a "gintercalate" of two streams. -- -- Unimplemented deintercalate :: Fold m a y -> Parser m x a -> Fold m b z -> Parser m x b -> Parser m x (y, z) -- | Sequential alternative. Apply the input to the first parser and return -- the result if the parser succeeds. If the first parser fails then -- backtrack and apply the same input to the second parser and return the -- result. -- -- Note: This implementation is not lazy in the second argument. The -- following will fail: -- --
--   >>> Stream.parse (Parser.satisfy (> 0) `Parser.alt` undefined) $ Stream.fromList [1..10]
--   1
--   
-- -- Compare with Alternative instance method <|>. -- This implementation allows stream fusion but has quadratic complexity. -- This can fuse with other operations and can be much faster than -- Alternative instance for small number (less than 8) of -- alternatives. -- -- Pre-release alt :: MonadCatch m => Parser m x a -> Parser m x a -> Parser m x a -- | Shortest alternative. Apply both parsers in parallel but choose the -- result from the one which consumed least input i.e. take the shortest -- succeeding parse. -- -- Pre-release shortest :: MonadCatch m => Parser m x a -> Parser m x a -> Parser m x a -- | Longest alternative. Apply both parsers in parallel but choose the -- result from the one which consumed more input i.e. take the longest -- succeeding parse. -- -- Pre-release longest :: MonadCatch m => Parser m x a -> Parser m x a -> Parser m x a -- | concatSequence f t collects sequential parses of parsers in -- the container t using the fold f. Fails if the input -- ends or any of the parsers fail. -- -- This is same as sequence but more efficient. -- -- Unimplemented concatSequence :: Fold m b c -> t (Parser m a b) -> Parser m a c -- | Map a Parser returning function on the result of a -- Parser. -- -- Compare with Monad instance method >>=. This -- implementation allows stream fusion but has quadratic complexity. This -- can fuse with other operations and can be much faster than -- Monad instance for small number (less than 8) of compositions. -- -- Pre-release concatMap :: MonadCatch m => (b -> Parser m a c) -> Parser m a b -> Parser m a c -- | count n f p collects exactly n sequential parses of -- parser p using the fold f. Fails if the input ends -- or the parser fails before n results are collected. -- -- Unimplemented count :: Int -> Parser m a b -> Fold m b c -> Parser m a c -- | countBetween m n f p collects between m and -- n sequential parses of parser p using the fold -- f. Stop after collecting n results. Fails if the -- input ends or the parser fails before m results are -- collected. -- -- Unimplemented countBetween :: Int -> Int -> Parser m a b -> Fold m b c -> Parser m a c -- | Like many but uses a Parser instead of a Fold to -- collect the results. Parsing stops or fails if the collecting parser -- stops or fails. -- -- Unimplemented manyP :: Parser m a b -> Parser m b c -> Parser m a c -- | Collect zero or more parses. Apply the supplied parser repeatedly on -- the input stream and push the parse results to a downstream fold. -- -- Stops: when the downstream fold stops or the parser fails. Fails: -- never, produces zero or more results. -- -- Compare with many. -- -- Pre-release many :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c -- | Collect one or more parses. Apply the supplied parser repeatedly on -- the input stream and push the parse results to a downstream fold. -- -- Stops: when the downstream fold stops or the parser fails. Fails: if -- it stops without producing a single result. -- --
--   some fld parser = manyP (takeGE 1 fld) parser
--   
-- -- Compare with some. -- -- Pre-release some :: MonadCatch m => Parser m a b -> Fold m b c -> Parser m a c -- | Like manyTill but uses a Parser to collect the results -- instead of a Fold. Parsing stops or fails if the collecting -- parser stops or fails. -- -- We can implemnent parsers like the following using manyTillP: -- --
--   countBetweenTill m n f p = manyTillP (takeBetween m n f) p
--   
-- -- Unimplemented manyTillP :: Parser m a b -> Parser m a x -> Parser m b c -> Parser m a c -- | manyTill f collect test tries the parser test on the -- input, if test fails it backtracks and tries -- collect, after collect succeeds test is -- tried again and so on. The parser stops when test succeeds. -- The output of test is discarded and the output of -- collect is accumulated by the supplied fold. The parser fails -- if collect fails. -- -- Stops when the fold f stops. -- -- Pre-release manyTill :: MonadCatch m => Parser m a b -> Parser m a x -> Fold m b c -> Parser m a c -- | manyThen f collect recover repeats the parser -- collect on the input and collects the output in the supplied -- fold. If the the parser collect fails, parser -- recover is run until it stops and then we start repeating the -- parser collect again. The parser fails if the recovery parser -- fails. -- -- For example, this can be used to find a key frame in a video stream -- after an error. -- -- Unimplemented manyThen :: Parser m a b -> Parser m a x -> Fold m b c -> Parser m a c -- | Apply a collection of parsers to an input stream in a round robin -- fashion. Each parser is applied until it stops and then we repeat -- starting with the the first parser again. -- -- Unimplemented roundRobin :: t (Parser m a b) -> Fold m b c -> Parser m a c -- | choice parsers applies the parsers in order and -- returns the first successful parse. -- -- This is same as asum but more efficient. -- -- Broken choice :: (Functor t, Foldable t, MonadCatch m) => t (Parser m a b) -> Parser m a b -- | Keep trying a parser up to a maximum of n failures. When the -- parser fails the input consumed till now is dropped and the new -- instance is tried on the fresh input. -- -- Unimplemented retryMaxTotal :: Int -> Parser m a b -> Fold m b c -> Parser m a c -- | Like retryMaxTotal but aborts after n successive -- failures. -- -- Unimplemented retryMaxSuccessive :: Int -> Parser m a b -> Fold m b c -> Parser m a c -- | Keep trying a parser until it succeeds. When the parser fails the -- input consumed till now is dropped and the new instance is tried on -- the fresh input. -- -- Unimplemented retry :: Parser m a b -> Parser m a b -- | A newtype wrapper over the Fold type providing distributing -- Applicative, Semigroup, Monoid, Num, -- Floating and Fractional instances. module Streamly.Internal.Data.Fold.Tee -- | Tee is a newtype wrapper over the Fold type providing -- distributing Applicative, Semigroup, Monoid, -- Num, Floating and Fractional instances. newtype Tee m a b Tee :: Fold m a b -> Tee m a b [toFold] :: Tee m a b -> Fold m a b instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Fold.Tee.Tee m a) instance GHC.Base.Monad m => GHC.Base.Applicative (Streamly.Internal.Data.Fold.Tee.Tee m a) instance (GHC.Base.Semigroup b, GHC.Base.Monad m) => GHC.Base.Semigroup (Streamly.Internal.Data.Fold.Tee.Tee m a b) instance (GHC.Base.Semigroup b, GHC.Base.Monoid b, GHC.Base.Monad m) => GHC.Base.Monoid (Streamly.Internal.Data.Fold.Tee.Tee m a b) instance (GHC.Base.Monad m, GHC.Num.Num b) => GHC.Num.Num (Streamly.Internal.Data.Fold.Tee.Tee m a b) instance (GHC.Base.Monad m, GHC.Real.Fractional b) => GHC.Real.Fractional (Streamly.Internal.Data.Fold.Tee.Tee m a b) instance (GHC.Base.Monad m, GHC.Float.Floating b) => GHC.Float.Floating (Streamly.Internal.Data.Fold.Tee.Tee m a b) -- | The Tee type is a newtype wrapper over the Fold type -- providing distributive Applicative, Semigroup, -- Monoid, Num, Floating and Fractional -- instances. The input received by the composed Tee is replicated -- and distributed to both the constituent Tees. -- -- For example, to compute the average of numbers in a stream without -- going through the stream twice: -- --
--   >>> import Streamly.Data.Fold.Tee (Tee(..))
--   
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import qualified Streamly.Data.Fold as Fold
--   
-- --
--   >>> avg = (/) <$> (Tee Fold.sum) <*> (Tee $ fmap fromIntegral Fold.length)
--   
--   >>> Stream.fold (toFold avg) $ Stream.fromList [1.0..100.0]
--   50.5
--   
-- -- Similarly, the Semigroup and Monoid instances of -- Tee distribute the input to both the folds and combine the -- outputs using Monoid or Semigroup instances of the output types: -- --
--   >>> import Data.Monoid (Sum(..))
--   
--   >>> t = Tee Fold.head <> Tee Fold.last
--   
--   >>> Stream.fold (toFold t) (fmap Sum $ Stream.enumerateFromTo 1.0 100.0)
--   Just (Sum {getSum = 101.0})
--   
-- -- The Num, Floating, and Fractional instances work -- in the same way. module Streamly.Data.Fold.Tee -- | Tee is a newtype wrapper over the Fold type providing -- distributing Applicative, Semigroup, Monoid, -- Num, Floating and Fractional instances. newtype Tee m a b Tee :: Fold m a b -> Tee m a b [toFold] :: Tee m a b -> Fold m a b module Streamly.Internal.Data.Fold.Async -- | takeInterval n fold uses fold to fold the input -- items arriving within a window of first n seconds. -- --
--   >>> input = Stream.delay 0.1 $ Stream.fromList [1..]
--   
--   >>> Stream.fold (Fold.takeInterval 1.0 Fold.toList) input
--   [1,2,3,4,5,6,7,8,9,10,11]
--   
-- -- Stops when fold stops or when the timeout occurs. Note that -- the fold needs an input after the timeout to stop. For example, if no -- input is pushed to the fold until one hour after the timeout had -- occurred, then the fold will be done only after consuming that input. -- -- Pre-release takeInterval :: MonadAsync m => Double -> Fold m a b -> Fold m a b -- | Group the input stream into windows of n second each using the first -- fold and then fold the resulting groups using the second fold. -- --
--   >>> intervals = Fold.intervalsOf 0.5 Fold.toList Fold.toList
--   
--   >>> Stream.fold intervals $ Stream.delay 0.2 $ Stream.fromList [1..10]
--   [[1,2,3,4],[5,6,7],[8,9,10]]
--   
-- --
--   intervalsOf n split = many (takeInterval n split)
--   
-- -- Pre-release intervalsOf :: MonadAsync m => Double -> Fold m a b -> Fold m b c -> Fold m a c -- | To run the examples in this module: -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import qualified Streamly.Data.Fold as Fold
--   
--   >>> import qualified Streamly.Internal.Data.Unfold as Unfold
--   
module Streamly.Internal.Data.Unfold.Type -- | An Unfold m a b is a generator of a stream of values of type -- b from a seed of type a in Monad m. data Unfold m a b -- |
--   Unfold step inject
--   
Unfold :: (s -> m (Step s b)) -> (a -> m s) -> Unfold m a b -- | Make an unfold from step and inject functions. -- -- Pre-release mkUnfoldM :: (s -> m (Step s b)) -> (a -> m s) -> Unfold m a b -- | Make an unfold from a step function. -- -- See also: unfoldrM -- -- Pre-release mkUnfoldrM :: Applicative m => (a -> m (Step a b)) -> Unfold m a b -- | Build a stream by unfolding a monadic step function starting -- from a seed. The step function returns the next element in the stream -- and the next seed value. When it is done it returns Nothing and -- the stream ends. -- -- Since: 0.8.0 unfoldrM :: Applicative m => (a -> m (Maybe (b, a))) -> Unfold m a b -- | Like unfoldrM but uses a pure step function. -- --
--   >>> :{
--    f [] = Nothing
--    f (x:xs) = Just (x, xs)
--   :}
--   
-- --
--   >>> Unfold.fold Fold.toList (Unfold.unfoldr f) [1,2,3]
--   [1,2,3]
--   
-- -- Since: 0.8.0 unfoldr :: Applicative m => (a -> Maybe (b, a)) -> Unfold m a b -- | Lift a monadic function into an unfold. The unfold generates a -- singleton stream. -- -- Since: 0.8.0 functionM :: Applicative m => (a -> m b) -> Unfold m a b -- | Lift a pure function into an unfold. The unfold generates a singleton -- stream. -- --
--   function f = functionM $ return . f
--   
-- -- Since: 0.8.0 function :: Applicative m => (a -> b) -> Unfold m a b -- | Identity unfold. The unfold generates a singleton stream having the -- input as the only element. -- --
--   identity = function Prelude.id
--   
-- -- Pre-release identity :: Applicative m => Unfold m a a -- | The unfold discards its input and generates a function stream using -- the supplied monadic action. -- -- Pre-release fromEffect :: Applicative m => m b -> Unfold m a b -- | Discards the unfold input and always returns the argument of -- fromPure. -- --
--   fromPure = fromEffect . pure
--   
-- -- Pre-release fromPure :: Applicative m => b -> Unfold m a b -- | Map a function on the input argument of the Unfold. -- --
--   >>> u = Unfold.lmap (fmap (+1)) Unfold.fromList
--   
--   >>> Unfold.fold Fold.toList u [1..5]
--   [2,3,4,5,6]
--   
-- --
--   lmap f = Unfold.many (Unfold.function f)
--   
-- -- Since: 0.8.0 lmap :: (a -> c) -> Unfold m c b -> Unfold m a b -- | Map an action on the input argument of the Unfold. -- --
--   lmapM f = Unfold.many (Unfold.functionM f)
--   
-- -- Since: 0.8.0 lmapM :: Monad m => (a -> m c) -> Unfold m c b -> Unfold m a b -- | Map a function on the output of the unfold (the type b). -- -- Pre-release map :: Functor m => (b -> c) -> Unfold m a b -> Unfold m a c -- | Supply the seed to an unfold closing the input end of the unfold. -- --
--   supply a = Unfold.lmap (Prelude.const a)
--   
-- -- Pre-release supply :: a -> Unfold m a b -> Unfold m Void b -- | Supply the first component of the tuple to an unfold that accepts a -- tuple as a seed resulting in a fold that accepts the second component -- of the tuple as a seed. -- --
--   supplyFirst a = Unfold.lmap (a, )
--   
-- -- Pre-release supplyFirst :: a -> Unfold m (a, b) c -> Unfold m b c -- | Supply the second component of the tuple to an unfold that accepts a -- tuple as a seed resulting in a fold that accepts the first component -- of the tuple as a seed. -- --
--   supplySecond b = Unfold.lmap (, b)
--   
-- -- Pre-release supplySecond :: b -> Unfold m (a, b) c -> Unfold m a c takeWhileMWithInput :: Monad m => (a -> b -> m Bool) -> Unfold m a b -> Unfold m a b -- | Same as takeWhile but with a monadic predicate. -- -- Since: 0.8.0 takeWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b -- | End the stream generated by the Unfold as soon as the predicate -- fails on an element. -- -- Since: 0.8.0 takeWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b data ConcatState s1 s2 ConcatOuter :: s1 -> ConcatState s1 s2 ConcatInner :: s1 -> s2 -> ConcatState s1 s2 -- | Apply the second unfold to each output element of the first unfold and -- flatten the output in a single stream. -- -- Since: 0.8.0 many :: Monad m => Unfold m a b -> Unfold m b c -> Unfold m a c -- | unfoldManyInterleave for documentation and notes. -- -- This is almost identical to unfoldManyInterleave in StreamD module. -- -- The many combinator is in fact manyAppend to be more -- explicit in naming. -- -- Internal manyInterleave :: Monad m => Unfold m a b -> Unfold m c a -> Unfold m c b -- | Outer product discarding the first element. -- -- Unimplemented apSequence :: Unfold m a b -> Unfold m a c -> Unfold m a c -- | Outer product discarding the second element. -- -- Unimplemented apDiscardSnd :: Unfold m a b -> Unfold m a c -> Unfold m a b -- | Create a cross product (vector product or cartesian product) of the -- output streams of two unfolds using a monadic combining function. -- -- Pre-release crossWithM :: Monad m => (b -> c -> m d) -> Unfold m a b -> Unfold m a c -> Unfold m a d -- | Like crossWithM but uses a pure combining function. -- --
--   crossWith f = crossWithM (\b c -> return $ f b c)
--   
-- --
--   >>> u1 = Unfold.lmap fst Unfold.fromList
--   
--   >>> u2 = Unfold.lmap snd Unfold.fromList
--   
--   >>> u = Unfold.crossWith (,) u1 u2
--   
--   >>> Unfold.fold Fold.toList u ([1,2,3], [4,5,6])
--   [(1,4),(1,5),(1,6),(2,4),(2,5),(2,6),(3,4),(3,5),(3,6)]
--   
-- -- Since: 0.8.0 crossWith :: Monad m => (b -> c -> d) -> Unfold m a b -> Unfold m a c -> Unfold m a d -- | See crossWith. -- --
--   cross = crossWith (,)
--   
-- -- To cross the streams from a tuple we can write: -- --
--   crossProduct :: Monad m => Unfold m a b -> Unfold m c d -> Unfold m (a, c) (b, d)
--   crossProduct u1 u2 = cross (lmap fst u1) (lmap snd u2)
--   
-- -- Pre-release cross :: Monad m => Unfold m a b -> Unfold m a c -> Unfold m a (b, c) apply :: Monad m => Unfold m a (b -> c) -> Unfold m a b -> Unfold m a c -- | Map an unfold generating action to each element of an unfold and -- flatten the results into a single stream. concatMapM :: Monad m => (b -> m (Unfold m a c)) -> Unfold m a b -> Unfold m a c concatMap :: Monad m => (b -> Unfold m a c) -> Unfold m a b -> Unfold m a c bind :: Monad m => Unfold m a b -> (b -> Unfold m a c) -> Unfold m a c infixl 1 `bind` -- | Distribute the input to two unfolds and then zip the outputs to a -- single stream using a monadic zip function. -- -- Stops as soon as any of the unfolds stops. -- -- Pre-release zipWithM :: Monad m => (b -> c -> m d) -> Unfold m a b -> Unfold m a c -> Unfold m a d -- | Like zipWithM but with a pure zip function. -- --
--   >>> square = fmap (\x -> x * x) Unfold.fromList
--   
--   >>> cube = fmap (\x -> x * x * x) Unfold.fromList
--   
--   >>> u = Unfold.zipWith (,) square cube
--   
--   >>> Unfold.fold Fold.toList u [1..5]
--   [(1,1),(4,8),(9,27),(16,64),(25,125)]
--   
-- --
--   zipWith f = zipWithM (\a b -> return $ f a b)
--   
-- -- Since: 0.8.0 zipWith :: Monad m => (b -> c -> d) -> Unfold m a b -> Unfold m a c -> Unfold m a d instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Unfold.Type.Unfold m a) -- | The functions defined in this module should be rarely needed for -- direct use, try to use the operations from the Enumerable type -- class instances instead. -- -- This module provides an Enumerable type class to enumerate -- Enum types into a stream. The operations in this type class -- correspond to similar operations in the Enum type class, the -- only difference is that they produce a stream instead of a list. These -- operations cannot be defined generically based on the Enum type -- class. We provide instances for commonly used types. If instances for -- other types are needed convenience functions defined in this module -- can be used to define them. Alternatively, these functions can be used -- directly. module Streamly.Internal.Data.Unfold.Enumeration -- | Types that can be enumerated as a stream. The operations in this type -- class are equivalent to those in the Enum type class, except -- that these generate a stream instead of a list. Use the functions in -- Streamly.Internal.Data.Unfold.Enumeration module to define new -- instances. -- -- Pre-release class Enum a => Enumerable a -- | Unfolds from generating a stream starting with the element -- from, enumerating up to maxBound when the type is -- Bounded or generating an infinite stream when the type is not -- Bounded. -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import qualified Streamly.Internal.Data.Unfold as Unfold
--   
-- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFrom (0 :: Int)
--   [0,1,2,3]
--   
-- -- For Fractional types, enumeration is numerically stable. -- However, no overflow or underflow checks are performed. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFrom 1.1
--   [1.1,2.1,3.1,4.1]
--   
-- -- Pre-release enumerateFrom :: (Enumerable a, Monad m) => Unfold m a a -- | Unfolds (from, to) generating a finite stream starting with -- the element from, enumerating the type up to the value -- to. If to is smaller than from then an -- empty stream is returned. -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import qualified Streamly.Internal.Data.Unfold as Unfold
--   
-- --
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromTo (0, 4)
--   [0,1,2,3,4]
--   
-- -- For Fractional types, the last element is equal to the -- specified to value after rounding to the nearest integral -- value. -- --
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromTo (1.1, 4)
--   [1.1,2.1,3.1,4.1]
--   
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromTo (1.1, 4.6)
--   [1.1,2.1,3.1,4.1,5.1]
--   
-- -- Pre-release enumerateFromTo :: (Enumerable a, Monad m) => Unfold m (a, a) a -- | Unfolds (from, then) generating a stream whose first element -- is from and the successive elements are in increments of -- then. Enumeration can occur downwards or upwards depending on -- whether then comes before or after from. For -- Bounded types the stream ends when maxBound is reached, -- for unbounded types it keeps enumerating infinitely. -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import qualified Streamly.Internal.Data.Unfold as Unfold
--   
-- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFromThen (0, 2)
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFromThen (0,(-2))
--   [0,-2,-4,-6]
--   
-- -- Pre-release enumerateFromThen :: (Enumerable a, Monad m) => Unfold m (a, a) a -- | Unfolds (from, then, to) generating a finite stream whose -- first element is from and the successive elements are in -- increments of then up to to. Enumeration can occur -- downwards or upwards depending on whether then comes before -- or after from. -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import qualified Streamly.Internal.Data.Unfold as Unfold
--   
-- --
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromThenTo (0, 2, 6)
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromThenTo (0, (-2), (-6))
--   [0,-2,-4,-6]
--   
-- -- Pre-release enumerateFromThenTo :: (Enumerable a, Monad m) => Unfold m (a, a, a) a -- | Unfolds (from, stride) generating an infinite stream starting -- from from and incrementing every time by stride. For -- Bounded types, after the value overflows it keeps enumerating -- in a cycle: -- --
--   >>> Stream.toList $ Stream.take 10 $ Stream.unfold Unfold.enumerateFromStepNum (255::Word8,1)
--   [255,0,1,2,3,4,5,6,7,8]
--   
-- -- The implementation is numerically stable for floating point values. -- -- Note enumerateFromStepIntegral is faster for integrals. -- -- Internal enumerateFromStepNum :: (Monad m, Num a) => Unfold m (a, a) a -- | Same as enumerateFromStepNum using a stride of 1: -- --
--   >>> enumerateFromNum = lmap (from -> (from, 1)) Unfold.enumerateFromStepNum
--   >>> Stream.toList $ Stream.take 6 $ Stream.unfold enumerateFromNum (0.9)
--   [0.9,1.9,2.9,3.9,4.9,5.9]
--   
-- -- Also, same as enumerateFromThenNum using a stride of 1 but see -- the note in enumerateFromThenNum about the loss of precision: -- --
--   >>> enumerateFromNum = lmap (from -> (from, from + 1)) Unfold.enumerateFromThenNum
--   >>> Stream.toList $ Stream.take 6 $ Stream.unfold enumerateFromNum (0.9)
--   [0.9,1.9,2.9,3.8999999999999995,4.8999999999999995,5.8999999999999995]
--   
-- -- Internal enumerateFromNum :: (Monad m, Num a) => Unfold m a a -- | Same as 'enumerateFromStepNum (from, next)' using a stride of next -- - from: -- --
--   >>> enumerateFromThenNum = lmap ((from, next) -> (from, next - from)) Unfold.enumerateFromStepNum
--   
-- -- Example: @ >>> Stream.toList $ Stream.take 10 $ Stream.unfold -- enumerateFromThenNum (255::Word8,0) [255,0,1,2,3,4,5,6,7,8] -- --
--   The implementation is numerically stable for floating point values.
--   
--   Note that enumerateFromThenIntegral is faster for integrals.
--   
--   Note that in the strange world of floating point numbers, using
--   
-- -- enumerateFromThenNum (from, from + 1) is almost exactly the same -- as enumerateFromStepNum (from, 1) but not precisely the same. -- Because (from + 1) - from is not exactly 1, it may lose some -- precision, the loss may also be aggregated in each step, if you want -- that precision then use enumerateFromStepNum instead. -- -- Internal enumerateFromThenNum :: (Monad m, Num a) => Unfold m (a, a) a -- | Can be used to enumerate unbounded integrals. This does not check for -- overflow or underflow for bounded integrals. -- -- Internal enumerateFromStepIntegral :: (Monad m, Integral a) => Unfold m (a, a) a enumerateFromIntegral :: (Monad m, Integral a) => Unfold m a a enumerateFromThenIntegral :: (Monad m, Integral a) => Unfold m (a, a) a enumerateFromToIntegral :: (Monad m, Integral a) => Unfold m (a, a) a enumerateFromThenToIntegral :: (Monad m, Integral a) => Unfold m (a, a, a) a enumerateFromIntegralBounded :: (Monad m, Integral a, Bounded a) => Unfold m a a enumerateFromThenIntegralBounded :: (Monad m, Integral a, Bounded a) => Unfold m (a, a) a enumerateFromToIntegralBounded :: (Monad m, Integral a, Bounded a) => Unfold m (a, a) a enumerateFromThenToIntegralBounded :: (Monad m, Integral a, Bounded a) => Unfold m (a, a, a) a -- | Enumerate from given starting Enum value from with stride of -- 1 till maxBound -- -- Internal enumerateFromSmallBounded :: (Monad m, Enum a, Bounded a) => Unfold m a a -- | Enumerate from given starting Enum value from and next Enum -- value next with stride of (fromEnum next - fromEnum from) -- till maxBound. -- -- Internal enumerateFromThenSmallBounded :: forall m a. (Monad m, Enum a, Bounded a) => Unfold m (a, a) a -- | Enumerate from given starting Enum value from and to Enum -- value to with stride of 1 till to value. -- -- Internal enumerateFromToSmall :: (Monad m, Enum a) => Unfold m (a, a) a -- | Enumerate from given starting Enum value from and then Enum -- value next and to Enum value to with stride of -- (fromEnum next - fromEnum from) till to value. -- -- Internal enumerateFromThenToSmall :: (Monad m, Enum a) => Unfold m (a, a, a) a enumerateFromFractional :: (Monad m, Fractional a) => Unfold m a a enumerateFromThenFractional :: (Monad m, Fractional a) => Unfold m (a, a) a -- | Same as enumerateFromStepNum with a step of 1 and enumerating -- up to the specified upper limit rounded to the nearest integral value: -- --
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromToFractional (0.1, 6.3)
--   [0.1,1.1,2.1,3.1,4.1,5.1,6.1]
--   
-- -- Internal enumerateFromToFractional :: (Monad m, Fractional a, Ord a) => Unfold m (a, a) a enumerateFromThenToFractional :: (Monad m, Fractional a, Ord a) => Unfold m (a, a, a) a instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable () instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Types.Bool instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Types.Ordering instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Types.Char instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Types.Int instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Int.Int8 instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Int.Int16 instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Int.Int32 instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Int.Int64 instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Types.Word instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Word.Word8 instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Word.Word16 instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Word.Word32 instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Word.Word64 instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Integer.Type.Integer instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Natural.Natural instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Types.Float instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable GHC.Types.Double instance Data.Fixed.HasResolution a => Streamly.Internal.Data.Unfold.Enumeration.Enumerable (Data.Fixed.Fixed a) instance GHC.Real.Integral a => Streamly.Internal.Data.Unfold.Enumeration.Enumerable (GHC.Real.Ratio a) instance Streamly.Internal.Data.Unfold.Enumeration.Enumerable a => Streamly.Internal.Data.Unfold.Enumeration.Enumerable (Data.Functor.Identity.Identity a) module Streamly.Internal.Data.Stream.StreamD.Type -- | A stream is a succession of Steps. A Yield produces a -- single value and the next state of the stream. Stop indicates -- there are no more values in the stream. data Step s a Yield :: a -> s -> Step s a Skip :: s -> Step s a Stop :: Step s a -- | A stream consists of a step function that generates the next step -- given a current state, and the current state. data Stream m a UnStream :: (State Stream m a -> s -> m (Step s a)) -> s -> Stream m a pattern Stream :: (State Stream m a -> s -> m (Step s a)) -> s -> Stream m a -- | An empty Stream with a side effect. nilM :: Applicative m => m b -> Stream m a consM :: Applicative m => m a -> Stream m a -> Stream m a -- | Does not fuse, has the same performance as the StreamK version. uncons :: Monad m => Stream m a -> m (Maybe (a, Stream m a)) -- | Convert an Unfold into a Stream by supplying it a seed. unfold :: Applicative m => Unfold m a b -> a -> Stream m b -- | Create a singleton Stream from a pure value. fromPure :: Applicative m => a -> Stream m a -- | Create a singleton Stream from a monadic action. fromEffect :: Applicative m => m a -> Stream m a -- | Convert a list of pure values to a Stream fromList :: Applicative m => [a] -> Stream m a -- | Convert a CPS encoded StreamK to direct style step encoded StreamD fromStreamK :: Applicative m => Stream m a -> Stream m a -- | Convert a direct style step encoded StreamD to a CPS encoded StreamK toStreamK :: Monad m => Stream m a -> Stream m a fold :: Monad m => Fold m a b -> Stream m a -> m b fold_ :: Monad m => Fold m a b -> Stream m a -> m (b, Stream m a) foldOn :: Monad m => Fold m a b -> Stream m a -> Fold m a b foldrT :: (Monad m, Monad (t m), MonadTrans t) => (a -> t m b -> t m b) -> t m b -> Stream m a -> t m b foldrM :: Monad m => (a -> m b -> m b) -> m b -> Stream m a -> m b foldrMx :: Monad m => (a -> m x -> m x) -> m x -> (m x -> m b) -> Stream m a -> m b foldr :: Monad m => (a -> b -> b) -> b -> Stream m a -> m b foldrS :: Monad m => (a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b foldl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b foldlM' :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> m b foldlx' :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream m a -> m b foldlMx' :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream m a -> m b -- | Run a streaming composition, discard the results. drain :: Monad m => Stream m a -> m () toList :: Monad m => Stream m a -> m [a] eqBy :: Monad m => (a -> b -> Bool) -> Stream m a -> Stream m b -> m Bool -- | Compare two streams lexicographically cmpBy :: Monad m => (a -> b -> Ordering) -> Stream m a -> Stream m b -> m Ordering map :: Monad m => (a -> b) -> Stream m a -> Stream m b -- | Map a monadic function over a Stream mapM :: Monad m => (a -> m b) -> Stream m a -> Stream m b take :: Applicative m => Int -> Stream m a -> Stream m a takeWhile :: Monad m => (a -> Bool) -> Stream m a -> Stream m a takeWhileM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m a data ConcatMapUState o i ConcatMapUOuter :: o -> ConcatMapUState o i ConcatMapUInner :: o -> i -> ConcatMapUState o i -- | unfoldMany unfold stream uses unfold to map the -- input stream elements to streams and then flattens the generated -- streams into a single output stream. unfoldMany :: Monad m => Unfold m a b -> Stream m a -> Stream m b concatMap :: Monad m => (a -> Stream m b) -> Stream m a -> Stream m b concatMapM :: Monad m => (a -> m (Stream m b)) -> Stream m a -> Stream m b data FoldMany s fs b a FoldManyStart :: s -> FoldMany s fs b a FoldManyFirst :: fs -> s -> FoldMany s fs b a FoldManyLoop :: s -> fs -> FoldMany s fs b a FoldManyYield :: b -> FoldMany s fs b a -> FoldMany s fs b a FoldManyDone :: FoldMany s fs b a data FoldManyPost s fs b a FoldManyPostStart :: s -> FoldManyPost s fs b a FoldManyPostLoop :: s -> fs -> FoldManyPost s fs b a FoldManyPostYield :: b -> FoldManyPost s fs b a -> FoldManyPost s fs b a FoldManyPostDone :: FoldManyPost s fs b a -- | Apply a fold multiple times until the stream ends. If the stream is -- empty the output would be empty. -- --
--   foldMany f = parseMany (fromFold f)
--   
-- -- A terminating fold may terminate even without accepting a single -- input. So we run the fold's initial action before evaluating the -- stream. However, this means that if later the stream does not yield -- anything we have to discard the fold's initial result which could have -- generated an effect. foldMany :: Monad m => Fold m a b -> Stream m a -> Stream m b -- | Like foldMany but with the following differences: -- -- foldManyPost :: Monad m => Fold m a b -> Stream m a -> Stream m b -- | Like foldMany but for the Refold type. The supplied -- action is used as the initial value for each refold. -- -- Internal refoldMany :: Monad m => Refold m x a b -> m x -> Stream m a -> Stream m b chunksOf :: Monad m => Int -> Fold m a b -> Stream m a -> Stream m b instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Stream.StreamD.Type.Stream m) instance GHC.Base.Applicative f => GHC.Base.Applicative (Streamly.Internal.Data.Stream.StreamD.Type.Stream f) instance GHC.Base.Monad m => GHC.Base.Monad (Streamly.Internal.Data.Stream.StreamD.Type.Stream m) instance Control.Monad.Trans.Class.MonadTrans Streamly.Internal.Data.Stream.StreamD.Type.Stream instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.StreamD.Type.Stream m) -- | Transform the underlying monad of a stream. module Streamly.Internal.Data.Stream.StreamD.Lift hoist :: Monad n => (forall x. m x -> n x) -> Stream m a -> Stream n a generally :: Monad m => Stream Identity a -> Stream m a liftInner :: (Monad m, MonadTrans t, Monad (t m)) => Stream m a -> Stream (t m) a runReaderT :: Monad m => m s -> Stream (ReaderT s m) a -> Stream m a evalStateT :: Monad m => m s -> Stream (StateT s m) a -> Stream m a runStateT :: Monad m => m s -> Stream (StateT s m) a -> Stream m (s, a) module Streamly.Internal.Data.Stream.StreamD.Exception -- | Like gbracket but with following differences: -- -- -- -- Inhibits stream fusion -- -- Pre-release gbracket_ :: Monad m => m c -> (forall s. m s -> m (Either e s)) -> (c -> m d) -> (c -> e -> Stream m b -> Stream m b) -> (c -> Stream m b) -> Stream m b -- | Run the alloc action m c with async exceptions disabled but -- keeping blocking operations interruptible (see mask). Use the -- output c as input to c -> Stream m b to generate -- an output stream. When generating the stream use the supplied -- try operation forall s. m s -> m (Either e s) to -- catch synchronous exceptions. If an exception occurs run the exception -- handler c -> e -> Stream m b -> m (Stream m b). Note -- that gbracket does not rethrow the exception, it has to be done -- by the exception handler if desired. -- -- The cleanup action c -> m d, runs whenever the stream ends -- normally, due to a sync or async exception or if it gets garbage -- collected after a partial lazy evaluation. See bracket for -- the semantics of the cleanup action. -- -- gbracket can express all other exception handling combinators. -- -- Inhibits stream fusion -- -- Pre-release gbracket :: (MonadIO m, MonadBaseControl IO m) => m c -> (forall s. m s -> m (Either e s)) -> (c -> m d1) -> (c -> m d2) -> (c -> e -> Stream m b -> m (Stream m b)) -> (c -> Stream m b) -> Stream m b -- | See before. before :: Monad m => m b -> Stream m a -> Stream m a -- | See after_. after_ :: Monad m => m b -> Stream m a -> Stream m a -- | See after. after :: (MonadIO m, MonadBaseControl IO m) => m b -> Stream m a -> Stream m a -- | See bracket_. bracket_ :: MonadCatch m => m b -> (b -> m c) -> (b -> Stream m a) -> Stream m a -- | See bracket. bracket' :: (MonadAsync m, MonadCatch m) => m b -> (b -> m c) -> (b -> m d) -> (b -> m e) -> (b -> Stream m a) -> Stream m a -- | See onException. onException :: MonadCatch m => m b -> Stream m a -> Stream m a -- | See finally_. finally_ :: MonadCatch m => m b -> Stream m a -> Stream m a -- | See finally. -- -- finally action xs = after action $ onException action xs finally :: (MonadAsync m, MonadCatch m) => m b -> Stream m a -> Stream m a -- | See ghandle. ghandle :: (MonadCatch m, Exception e) => (e -> Stream m a -> Stream m a) -> Stream m a -> Stream m a -- | See handle. handle :: (MonadCatch m, Exception e) => (e -> Stream m a) -> Stream m a -> Stream m a -- | See retry retry :: forall e m a. (Exception e, Ord e, MonadCatch m) => Map e Int -> (e -> Stream m a) -> Stream m a -> Stream m a -- | Low level functions using StreamK as the intermediate stream type. -- These functions are used in SerialTAsyncTAheadT/ParallelT -- stream modules to implement their instances.. module Streamly.Internal.Data.Stream.Prelude drain :: Monad m => Stream m a -> m () -- |
--   fromList = foldr cons nil
--   
-- -- Construct a stream from a list of pure values. This is more efficient -- than fromFoldable for serial streams. fromList :: Monad m => [a] -> Stream m a -- | Convert a stream into a list in the underlying monad. toList :: Monad m => Stream m a -> m [a] foldrM :: Monad m => (a -> m b -> m b) -> m b -> Stream m a -> m b foldrMx :: Monad m => (a -> m x -> m x) -> m x -> (m x -> m b) -> Stream m a -> m b foldr :: Monad m => (a -> b -> b) -> b -> Stream m a -> m b -- | Strict left fold with an extraction function. Like the standard strict -- left fold, but applies a user supplied extraction function (the third -- argument) to the folded value at the end. This is designed to work -- with the foldl library. The suffix x is a mnemonic -- for extraction. foldlx' :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream m a -> m b -- | Like foldlx', but with a monadic step function. foldlMx' :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream m a -> m b -- | Strict left associative fold. foldl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b fold :: Monad m => Fold m a b -> Stream m a -> m b -- | Compare two streams for equality eqBy :: Monad m => (a -> b -> Bool) -> Stream m a -> Stream m b -> m Bool -- | Compare two streams cmpBy :: Monad m => (a -> b -> Ordering) -> Stream m a -> Stream m b -> m Ordering -- | A mutable variable in a mutation capable monad (IO) holding a -- Prim value. This allows fast modification because of unboxed -- storage. -- --

Multithread Consistency Notes

-- -- In general, any value that straddles a machine word cannot be -- guaranteed to be consistently read from another thread without a lock. -- GHC heap objects are always machine word aligned, therefore, a -- IORef is also word aligned. On a 64-bit platform, writing a -- 64-bit aligned type from one thread and reading it from another thread -- should give consistent old or new value. The same holds true for -- 32-bit values on a 32-bit platform. module Streamly.Internal.Data.IORef.Prim -- | An IORef holds a single Prim value. data IORef a -- | Class of types supporting primitive array operations. This includes -- interfacing with GC-managed memory (functions suffixed with -- ByteArray#) and interfacing with unmanaged memory (functions -- suffixed with Addr#). Endianness is platform-dependent. class Prim a -- | Create a new IORef. -- -- Pre-release newIORef :: forall a. Prim a => a -> IO (IORef a) -- | Write a value to an IORef. -- -- Pre-release writeIORef :: Prim a => IORef a -> a -> IO () -- | Modify the value of an IORef using a function with strict -- application. -- -- Pre-release modifyIORef' :: Prim a => IORef a -> (a -> a) -> IO () -- | Read a value from an IORef. -- -- Pre-release readIORef :: Prim a => IORef a -> IO a -- | Generate a stream by continuously reading the IORef. -- -- Pre-release toStreamD :: (MonadIO m, Prim a) => IORef a -> Stream m a module Streamly.Internal.Data.Time.Clock -- | Clock types. A clock may be system-wide (that is, visible to all -- processes) or per-process (measuring time that is meaningful only -- within a process). All implementations shall support CLOCK_REALTIME. -- (The only suspend-aware monotonic is CLOCK_BOOTTIME on Linux.) data Clock -- | The identifier for the system-wide monotonic clock, which is defined -- as a clock measuring real time, whose value cannot be set via -- clock_settime and which cannot have negative clock jumps. The -- maximum possible clock jump shall be implementation defined. For this -- clock, the value returned by getTime represents the amount of -- time (in seconds and nanoseconds) since an unspecified point in the -- past (for example, system start-up time, or the Epoch). This point -- does not change after system start-up time. Note that the absolute -- value of the monotonic clock is meaningless (because its origin is -- arbitrary), and thus there is no need to set it. Furthermore, realtime -- applications can rely on the fact that the value of this clock is -- never set. Monotonic :: Clock -- | The identifier of the system-wide clock measuring real time. For this -- clock, the value returned by getTime represents the amount of -- time (in seconds and nanoseconds) since the Epoch. Realtime :: Clock -- | The identifier of the CPU-time clock associated with the calling -- process. For this clock, the value returned by getTime -- represents the amount of execution time of the current process. ProcessCPUTime :: Clock -- | The identifier of the CPU-time clock associated with the calling OS -- thread. For this clock, the value returned by getTime -- represents the amount of execution time of the current OS thread. ThreadCPUTime :: Clock -- | (since Linux 2.6.28; Linux and Mac OSX) Similar to CLOCK_MONOTONIC, -- but provides access to a raw hardware-based time that is not subject -- to NTP adjustments or the incremental adjustments performed by -- adjtime(3). MonotonicRaw :: Clock -- | (since Linux 2.6.32; Linux and Mac OSX) A faster but less precise -- version of CLOCK_MONOTONIC. Use when you need very fast, but not -- fine-grained timestamps. MonotonicCoarse :: Clock -- | (since Linux 2.6.39; Linux and Mac OSX) Identical to CLOCK_MONOTONIC, -- except it also includes any time that the system is suspended. This -- allows applications to get a suspend-aware monotonic clock without -- having to deal with the complications of CLOCK_REALTIME, which may -- have discontinuities if the time is changed using settimeofday(2). Uptime :: Clock -- | (since Linux 2.6.32; Linux-specific) A faster but less precise version -- of CLOCK_REALTIME. Use when you need very fast, but not fine-grained -- timestamps. RealtimeCoarse :: Clock getTime :: Clock -> IO AbsTime -- | asyncClock g starts a clock thread that updates an IORef with -- current time as a 64-bit value in microseconds, every g -- seconds. The IORef can be read asynchronously. The thread exits -- automatically when the reference to the returned ThreadId is -- lost. -- -- Minimum granularity of clock update is 1 ms. Higher is better for -- performance. -- -- CAUTION! This is safe only on a 64-bit machine. On a 32-bit machine a -- 64-bit Var cannot be read consistently without a lock while -- another thread is writing to it. asyncClock :: Clock -> Double -> IO (ThreadId, IORef MicroSecond64) readClock :: (ThreadId, IORef MicroSecond64) -> IO MicroSecond64 -- | Prefer unfolds (Streamly.Internal.Data.Unfold) over the -- combinators in this module. They are more powerful and efficient as -- they can be transformed and composed on the input side efficiently and -- they can fuse in nested operations (e.g. unfoldMany). All the -- combinators in this module can be expressed using unfolds with the -- same efficiency. -- -- Operations in this module that are not in -- Streamly.Internal.Data.Unfold: generate, times, fromPrimIORef. -- -- We should plan to replace this module with -- Streamly.Internal.Data.Unfold in future. module Streamly.Internal.Data.Stream.StreamD.Generate -- | An empty Stream. nil :: Monad m => Stream m a -- | An empty Stream with a side effect. nilM :: Applicative m => m b -> Stream m a -- | Can fuse but has O(n^2) complexity. cons :: Monad m => a -> Stream m a -> Stream m a consM :: Applicative m => m a -> Stream m a -> Stream m a -- | Convert an Unfold into a Stream by supplying it a seed. unfold :: Applicative m => Unfold m a b -> a -> Stream m b unfoldr :: Monad m => (s -> Maybe (a, s)) -> s -> Stream m a unfoldrM :: Monad m => (s -> m (Maybe (a, s))) -> s -> Stream m a -- | Create a singleton Stream from a pure value. fromPure :: Applicative m => a -> Stream m a -- | Create a singleton Stream from a monadic action. fromEffect :: Applicative m => m a -> Stream m a repeat :: Monad m => a -> Stream m a repeatM :: Monad m => m a -> Stream m a replicate :: Monad m => Int -> a -> Stream m a replicateM :: forall m a. Monad m => Int -> m a -> Stream m a -- | Can be used to enumerate unbounded integrals. This does not check for -- overflow or underflow for bounded integrals. enumerateFromStepIntegral :: (Integral a, Monad m) => a -> a -> Stream m a enumerateFromIntegral :: (Monad m, Integral a, Bounded a) => a -> Stream m a enumerateFromThenIntegral :: (Monad m, Integral a, Bounded a) => a -> a -> Stream m a -- | Enumerate upwards from from to to. We are assuming -- that "to" is constrained by the type to be within max/min bounds. enumerateFromToIntegral :: (Monad m, Integral a) => a -> a -> Stream m a enumerateFromThenToIntegral :: (Monad m, Integral a) => a -> a -> a -> Stream m a -- | For floating point numbers if the increment is less than the precision -- then it just gets lost. Therefore we cannot always increment it -- correctly by just repeated addition. 9007199254740992 + 1 + 1 :: -- Double => 9.007199254740992e15 9007199254740992 + 2 :: Double => -- 9.007199254740994e15 -- -- Instead we accumulate the increment counter and compute the increment -- every time before adding it to the starting number. -- -- This works for Integrals as well as floating point numbers, but -- enumerateFromStepIntegral is faster for integrals. enumerateFromStepNum :: (Monad m, Num a) => a -> a -> Stream m a enumerateFromNum :: (Monad m, Num a) => a -> Stream m a enumerateFromThenNum :: (Monad m, Num a) => a -> a -> Stream m a -- | We cannot write a general function for Num. The only way to write code -- portable between the two is to use a Real constraint and -- convert between Fractional and Integral using fromRational which is -- horribly slow. enumerateFromToFractional :: (Monad m, Fractional a, Ord a) => a -> a -> Stream m a enumerateFromThenToFractional :: (Monad m, Fractional a, Ord a) => a -> a -> a -> Stream m a times :: MonadAsync m => Double -> Stream m (AbsTime, RelTime64) fromIndices :: Monad m => (Int -> a) -> Stream m a fromIndicesM :: Monad m => (Int -> m a) -> Stream m a generate :: Monad m => Int -> (Int -> a) -> Stream m a generateM :: Monad m => Int -> (Int -> m a) -> Stream m a iterate :: Monad m => (a -> a) -> a -> Stream m a iterateM :: Monad m => (a -> m a) -> m a -> Stream m a -- | Convert a list of pure values to a Stream fromList :: Applicative m => [a] -> Stream m a -- | Convert a list of monadic actions to a Stream fromListM :: MonadAsync m => [m a] -> Stream m a -- | Convert a CPS encoded StreamK to direct style step encoded StreamD fromStreamK :: Applicative m => Stream m a -> Stream m a -- | Convert a direct style step encoded StreamD to a CPS encoded StreamK toStreamK :: Monad m => Stream m a -> Stream m a -- | To run examples in this module: -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
module Streamly.Internal.Data.Stream.Serial -- | For SerialT streams: -- --
--   (<>) = serial                       -- Semigroup
--   (>>=) = flip . concatMapWith serial -- Monad
--   
-- -- A single Monad bind behaves like a for loop: -- --
--   >>> :{
--   Stream.toList $ do
--        x <- Stream.fromList [1,2] -- foreach x in stream
--        return x
--   :}
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops: -- --
--   >>> :{
--   Stream.toList $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [3,4] -- foreach y in stream
--       return (x, y)
--   :}
--   [(1,3),(1,4),(2,3),(2,4)]
--   
-- -- Since: 0.2.0 (Streamly) newtype SerialT m a SerialT :: Stream m a -> SerialT m a [getSerialT] :: SerialT m a -> Stream m a -- | A serial IO stream of elements of type a. See SerialT -- documentation for more details. -- -- Since: 0.2.0 (Streamly) type Serial = SerialT IO serial :: SerialT m a -> SerialT m a -> SerialT m a -- | For WSerialT streams: -- --
--   (<>) = wSerial                       -- Semigroup
--   (>>=) = flip . concatMapWith wSerial -- Monad
--   
-- -- Note that <> is associative only if we disregard the -- ordering of elements in the resulting stream. -- -- A single Monad bind behaves like a for loop: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWSerial $ do
--        x <- Stream.fromList [1,2] -- foreach x in stream
--        return x
--   :}
--   [1,2]
--   
-- -- Nested monad binds behave like interleaved nested for loops: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWSerial $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [3,4] -- foreach y in stream
--       return (x, y)
--   :}
--   [(1,3),(2,3),(1,4),(2,4)]
--   
-- -- It is a result of interleaving all the nested iterations corresponding -- to element 1 in the first stream with all the nested -- iterations of element 2: -- --
--   >>> import Streamly.Prelude (wSerial)
--   
--   >>> Stream.toList $ Stream.fromList [(1,3),(1,4)] `Stream.wSerial` Stream.fromList [(2,3),(2,4)]
--   [(1,3),(2,3),(1,4),(2,4)]
--   
-- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- SerialT. -- -- Since: 0.2.0 (Streamly) newtype WSerialT m a WSerialT :: Stream m a -> WSerialT m a [getWSerialT] :: WSerialT m a -> Stream m a -- | An interleaving serial IO stream of elements of type a. See -- WSerialT documentation for more details. -- -- Since: 0.2.0 (Streamly) type WSerial = WSerialT IO wSerialK :: Stream m a -> Stream m a -> Stream m a -- | Interleaves two streams, yielding one element from each stream -- alternately. When one stream stops the rest of the other stream is -- used in the output stream. wSerial :: WSerialT m a -> WSerialT m a -> WSerialT m a infixr 6 `wSerial` wSerialFst :: WSerialT m a -> WSerialT m a -> WSerialT m a wSerialMin :: WSerialT m a -> WSerialT m a -> WSerialT m a consMWSerial :: Monad m => m a -> WSerialT m a -> WSerialT m a cons :: a -> SerialT m a -> SerialT m a consM :: Monad m => m a -> SerialT m a -> SerialT m a -- | Generate an infinite stream by repeating a pure value. repeat :: Monad m => a -> SerialT m a -- | Build a stream by unfolding a monadic step function starting -- from a seed. The step function returns the next element in the stream -- and the next seed value. When it is done it returns Nothing and -- the stream ends. For example, -- --
--   let f b =
--           if b > 3
--           then return Nothing
--           else print b >> return (Just (b, b + 1))
--   in drain $ unfoldrM f 0
--   
-- --
--   0
--   1
--   2
--   3
--   
-- -- Pre-release unfoldrM :: Monad m => (b -> m (Maybe (a, b))) -> b -> SerialT m a -- | The fromList function constructs the structure l from -- the given list of Item l fromList :: IsList l => [Item l] -> l -- | The toList function extracts a list of Item l from the -- structure l. It should satisfy fromList . toList = id. toList :: IsList l => l -> [Item l] -- |
--   map = fmap
--   
-- -- Same as fmap. -- --
--   > S.toList $ S.map (+1) $ S.fromList [1,2,3]
--   [2,3,4]
--   
map :: Monad m => (a -> b) -> SerialT m a -> SerialT m b mapM :: Monad m => (a -> m b) -> SerialT m a -> SerialT m b -- | Deprecated: Please use SerialT instead. type StreamT = SerialT -- | Deprecated: Please use WSerialT instead. type InterleavedT = WSerialT instance Control.Monad.Trans.Class.MonadTrans Streamly.Internal.Data.Stream.Serial.SerialT instance GHC.Base.Monoid (Streamly.Internal.Data.Stream.Serial.SerialT m a) instance GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Serial.SerialT m a) instance Control.Monad.Trans.Class.MonadTrans Streamly.Internal.Data.Stream.Serial.WSerialT instance GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Serial.WSerialT m a) instance GHC.Base.Monoid (Streamly.Internal.Data.Stream.Serial.WSerialT m a) instance GHC.Base.Monad m => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Serial.WSerialT m) instance GHC.Base.Monad m => GHC.Base.Monad (Streamly.Internal.Data.Stream.Serial.WSerialT m) instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Stream.Serial.WSerialT m) instance (Control.Monad.Base.MonadBase b m, GHC.Base.Monad m) => Control.Monad.Base.MonadBase b (Streamly.Internal.Data.Stream.Serial.WSerialT m) instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Stream.Serial.WSerialT m) instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.Serial.WSerialT m) instance Control.Monad.Reader.Class.MonadReader r m => Control.Monad.Reader.Class.MonadReader r (Streamly.Internal.Data.Stream.Serial.WSerialT m) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Stream.Serial.WSerialT m) instance GHC.Exts.IsList (Streamly.Internal.Data.Stream.Serial.WSerialT Data.Functor.Identity.Identity a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Streamly.Internal.Data.Stream.Serial.WSerialT Data.Functor.Identity.Identity a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Streamly.Internal.Data.Stream.Serial.WSerialT Data.Functor.Identity.Identity a) instance GHC.Show.Show a => GHC.Show.Show (Streamly.Internal.Data.Stream.Serial.WSerialT Data.Functor.Identity.Identity a) instance GHC.Read.Read a => GHC.Read.Read (Streamly.Internal.Data.Stream.Serial.WSerialT Data.Functor.Identity.Identity a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString (Streamly.Internal.Data.Stream.Serial.WSerialT Data.Functor.Identity.Identity a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Streamly.Internal.Data.Stream.Serial.WSerialT Data.Functor.Identity.Identity a) instance Control.DeepSeq.NFData1 (Streamly.Internal.Data.Stream.Serial.WSerialT Data.Functor.Identity.Identity) instance (Data.Foldable.Foldable m, GHC.Base.Monad m) => Data.Foldable.Foldable (Streamly.Internal.Data.Stream.Serial.WSerialT m) instance Data.Traversable.Traversable (Streamly.Internal.Data.Stream.Serial.WSerialT Data.Functor.Identity.Identity) instance GHC.Base.Monad m => GHC.Base.Monad (Streamly.Internal.Data.Stream.Serial.SerialT m) instance GHC.Base.Monad m => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Serial.SerialT m) instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Stream.Serial.SerialT m) instance (Control.Monad.Base.MonadBase b m, GHC.Base.Monad m) => Control.Monad.Base.MonadBase b (Streamly.Internal.Data.Stream.Serial.SerialT m) instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Stream.Serial.SerialT m) instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.Serial.SerialT m) instance Control.Monad.Reader.Class.MonadReader r m => Control.Monad.Reader.Class.MonadReader r (Streamly.Internal.Data.Stream.Serial.SerialT m) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Stream.Serial.SerialT m) instance GHC.Exts.IsList (Streamly.Internal.Data.Stream.Serial.SerialT Data.Functor.Identity.Identity a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Streamly.Internal.Data.Stream.Serial.SerialT Data.Functor.Identity.Identity a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Streamly.Internal.Data.Stream.Serial.SerialT Data.Functor.Identity.Identity a) instance GHC.Show.Show a => GHC.Show.Show (Streamly.Internal.Data.Stream.Serial.SerialT Data.Functor.Identity.Identity a) instance GHC.Read.Read a => GHC.Read.Read (Streamly.Internal.Data.Stream.Serial.SerialT Data.Functor.Identity.Identity a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString (Streamly.Internal.Data.Stream.Serial.SerialT Data.Functor.Identity.Identity a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Streamly.Internal.Data.Stream.Serial.SerialT Data.Functor.Identity.Identity a) instance Control.DeepSeq.NFData1 (Streamly.Internal.Data.Stream.Serial.SerialT Data.Functor.Identity.Identity) instance (Data.Foldable.Foldable m, GHC.Base.Monad m) => Data.Foldable.Foldable (Streamly.Internal.Data.Stream.Serial.SerialT m) instance Data.Traversable.Traversable (Streamly.Internal.Data.Stream.Serial.SerialT Data.Functor.Identity.Identity) -- | See Streamly.Data.Fold for an overview and -- Streamly.Internal.Data.Fold.Types for design notes. -- -- IMPORTANT: keep the signatures consistent with the folds in -- Streamly.Prelude module Streamly.Internal.Data.Fold -- | Represents the result of the step of a Fold. -- Partial returns an intermediate state of the fold, the fold -- step can be called again with the state or the driver can use -- extract on the state to get the result out. Done -- returns the final result and the fold cannot be driven further. -- -- Pre-release data Step s b Partial :: !s -> Step s b Done :: !b -> Step s b -- | The type Fold m a b having constructor Fold step initial -- extract represents a fold over an input stream of values of type -- a to a final value of type b in Monad -- m. -- -- The fold uses an intermediate state s as accumulator, the -- type s is internal to the specific fold definition. The -- initial value of the fold state s is returned by -- initial. The step function consumes an input and -- either returns the final result b if the fold is done or the -- next intermediate state (see Step). At any point the fold -- driver can extract the result from the intermediate state using the -- extract function. -- -- NOTE: The constructor is not yet exposed via exposed modules, smart -- constructors are provided to create folds. If you think you need the -- constructor of this type please consider using the smart constructors -- in Streamly.Internal.Data.Fold instead. -- -- since 0.8.0 (type changed) data Fold m a b -- | Fold step initial extract Fold :: (s -> a -> m (Step s b)) -> m (Step s b) -> (s -> m b) -> Fold m a b -- | Make a fold from a left fold style pure step function and initial -- value of the accumulator. -- -- If your Fold returns only Partial (i.e. never returns a -- Done) then you can use foldl'* constructors. -- -- A fold with an extract function can be expressed using fmap: -- --
--   mkfoldlx :: Monad m => (s -> a -> s) -> s -> (s -> b) -> Fold m a b
--   mkfoldlx step initial extract = fmap extract (foldl' step initial)
--   
-- -- See also: Streamly.Prelude.foldl' foldl' :: Monad m => (b -> a -> b) -> b -> Fold m a b -- | Make a fold from a left fold style monadic step function and initial -- value of the accumulator. -- -- A fold with an extract function can be expressed using rmapM: -- --
--   mkFoldlxM :: Functor m => (s -> a -> m s) -> m s -> (s -> m b) -> Fold m a b
--   mkFoldlxM step initial extract = rmapM extract (foldlM' step initial)
--   
-- -- See also: Streamly.Prelude.foldlM' foldlM' :: Monad m => (b -> a -> m b) -> m b -> Fold m a b -- | Make a strict left fold, for non-empty streams, using first element as -- the starting value. Returns Nothing if the stream is empty. -- -- See also: Streamly.Prelude.foldl1' -- -- Pre-release foldl1' :: Monad m => (a -> a -> a) -> Fold m a (Maybe a) -- | Make a fold using a right fold style step function and a terminal -- value. It performs a strict right fold via a left fold using function -- composition. Note that this is strict fold, it can only be useful for -- constructing strict structures in memory. For reductions this will be -- very inefficient. -- -- For example, -- --
--   toList = foldr (:) []
--   
-- -- See also: foldr foldr :: Monad m => (a -> b -> b) -> b -> Fold m a b -- | Like foldr but with a monadic step function. -- -- For example, -- --
--   toList = foldrM (\a xs -> return $ a : xs) (return [])
--   
-- -- See also: foldrM -- -- Pre-release foldrM :: Monad m => (a -> b -> m b) -> m b -> Fold m a b -- | Make a terminating fold using a pure step function, a pure initial -- state and a pure state extraction function. -- -- Pre-release mkFold :: Monad m => (s -> a -> Step s b) -> Step s b -> (s -> b) -> Fold m a b -- | Similar to mkFold but the final state extracted is identical to -- the intermediate state. -- --
--   mkFold_ step initial = mkFold step initial id
--   
-- -- Pre-release mkFold_ :: Monad m => (b -> a -> Step b b) -> Step b b -> Fold m a b -- | Make a terminating fold with an effectful step function and initial -- state, and a state extraction function. -- --
--   mkFoldM = Fold
--   
-- -- We can just use Fold but it is provided for completeness. -- -- Pre-release mkFoldM :: (s -> a -> m (Step s b)) -> m (Step s b) -> (s -> m b) -> Fold m a b -- | Similar to mkFoldM but the final state extracted is identical -- to the intermediate state. -- --
--   mkFoldM_ step initial = mkFoldM step initial return
--   
-- -- Pre-release mkFoldM_ :: Monad m => (b -> a -> m (Step b b)) -> m (Step b b) -> Fold m a b -- | A fold that always yields a pure value without consuming any input. -- -- Pre-release fromPure :: Applicative m => b -> Fold m a b -- | A fold that always yields the result of an effectful action without -- consuming any input. -- -- Pre-release fromEffect :: Applicative m => m b -> Fold m a b -- | Append the elements of an input stream to a provided starting value. -- --
--   >>> Stream.fold (Fold.sconcat 10) (Stream.map Data.Monoid.Sum $ Stream.enumerateFromTo 1 10)
--   Sum {getSum = 65}
--   
-- --
--   sconcat = Fold.foldl' (<>)
--   
sconcat :: (Monad m, Semigroup a) => a -> Fold m a a -- | Fold an input stream consisting of monoidal elements using -- mappend and mempty. -- --
--   >>> Stream.fold Fold.mconcat (Stream.map Data.Monoid.Sum $ Stream.enumerateFromTo 1 10)
--   Sum {getSum = 55}
--   
-- --
--   mconcat = Fold.sconcat mempty
--   
mconcat :: (Monad m, Monoid a) => Fold m a a -- |
--   foldMap f = Fold.lmap f Fold.mconcat
--   
-- -- Make a fold from a pure function that folds the output of the function -- using mappend and mempty. -- --
--   >>> Stream.fold (Fold.foldMap Data.Monoid.Sum) $ Stream.enumerateFromTo 1 10
--   Sum {getSum = 55}
--   
foldMap :: (Monad m, Monoid b) => (a -> b) -> Fold m a b -- |
--   foldMapM f = Fold.lmapM f Fold.mconcat
--   
-- -- Make a fold from a monadic function that folds the output of the -- function using mappend and mempty. -- --
--   >>> Stream.fold (Fold.foldMapM (return . Data.Monoid.Sum)) $ Stream.enumerateFromTo 1 10
--   Sum {getSum = 55}
--   
foldMapM :: (Monad m, Monoid b) => (a -> m b) -> Fold m a b -- | A fold that drains all its input, running the effects and discarding -- the results. -- --
--   drain = drainBy (const (return ()))
--   
drain :: Monad m => Fold m a () -- |
--   drainBy f = lmapM f drain
--   drainBy = Fold.foldMapM (void . f)
--   
-- -- Drain all input after passing it through a monadic function. This is -- the dual of mapM_ on stream producers. -- -- See also: mapM_ drainBy :: Monad m => (a -> m b) -> Fold m a () -- | Extract the last element of the input stream, if any. -- --
--   last = fmap getLast $ Fold.foldMap (Last . Just)
--   
last :: Monad m => Fold m a (Maybe a) -- | Determine the length of the input stream. -- --
--   length = fmap getSum $ Fold.foldMap (Sum . const  1)
--   
length :: Monad m => Fold m a Int -- | Compute a numerically stable arithmetic mean of all elements in the -- input stream. mean :: (Monad m, Fractional a) => Fold m a a -- | Compute a numerically stable (population) variance over all elements -- in the input stream. variance :: (Monad m, Fractional a) => Fold m a a -- | Compute a numerically stable (population) standard deviation over all -- elements in the input stream. stdDev :: (Monad m, Floating a) => Fold m a a -- | Compute an Int sized polynomial rolling hash of a stream. -- --
--   rollingHash = Fold.rollingHashWithSalt defaultSalt
--   
rollingHash :: (Monad m, Enum a) => Fold m a Int64 -- | Compute an Int sized polynomial rolling hash -- --
--   H = salt * k ^ n + c1 * k ^ (n - 1) + c2 * k ^ (n - 2) + ... + cn * k ^ 0
--   
-- -- Where c1, c2, cn are the elements in the -- input stream and k is a constant. -- -- This hash is often used in Rabin-Karp string search algorithm. -- -- See https://en.wikipedia.org/wiki/Rolling_hash rollingHashWithSalt :: (Monad m, Enum a) => Int64 -> Fold m a Int64 -- | Compute an Int sized polynomial rolling hash of the first n -- elements of a stream. -- --
--   rollingHashFirstN = Fold.take n Fold.rollingHash
--   
-- -- Pre-release rollingHashFirstN :: (Monad m, Enum a) => Int -> Fold m a Int64 -- | Determine the sum of all elements of a stream of numbers. Returns -- additive identity (0) when the stream is empty. Note that -- this is not numerically stable for floating point numbers. -- --
--   sum = fmap getSum $ Fold.foldMap Sum
--   
sum :: (Monad m, Num a) => Fold m a a -- | Determine the product of all elements of a stream of numbers. Returns -- multiplicative identity (1) when the stream is empty. The -- fold terminates when it encounters (0) in its input. -- -- Compare with Fold.foldMap Product. -- -- Since 0.8.0 (Added Eq constraint) product :: (Monad m, Num a, Eq a) => Fold m a a -- | Determine the maximum element in a stream using the supplied -- comparison function. maximumBy :: Monad m => (a -> a -> Ordering) -> Fold m a (Maybe a) -- |
--   maximum = Fold.maximumBy compare
--   
-- -- Determine the maximum element in a stream. -- -- Compare with Fold.foldMap Max. maximum :: (Monad m, Ord a) => Fold m a (Maybe a) -- | Computes the minimum element with respect to the given comparison -- function minimumBy :: Monad m => (a -> a -> Ordering) -> Fold m a (Maybe a) -- | Determine the minimum element in a stream using the supplied -- comparison function. -- --
--   minimum = minimumBy compare
--   
-- -- Compare with Fold.foldMap Min. minimum :: (Monad m, Ord a) => Fold m a (Maybe a) -- | Folds the input stream to a list. -- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using -- Streamly.Data.Array.Foreign instead. -- --
--   toList = foldr (:) []
--   
toList :: Monad m => Fold m a [a] -- | Buffers the input stream to a list in the reverse order of the input. -- --
--   toListRev = Fold.foldl' (flip (:)) []
--   
-- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using Streamly.Array -- instead. toListRev :: Monad m => Fold m a [a] -- | A fold that buffers its input to a pure stream. -- -- Warning! working on large streams accumulated as buffers in -- memory could be very inefficient, consider using -- Streamly.Data.Array instead. -- --
--   >>> toStream = fmap SerialT Fold.toStreamK
--   
-- -- Pre-release toStream :: Monad m => Fold m a (SerialT n a) -- | Buffers the input stream to a pure stream in the reverse order of the -- input. -- --
--   >>> toStreamRev = fmap SerialT Fold.toStreamKRev
--   
-- -- Warning! working on large streams accumulated as buffers in -- memory could be very inefficient, consider using -- Streamly.Data.Array instead. -- -- Pre-release toStreamRev :: Monad m => Fold m a (SerialT n a) -- | A fold that drains the first n elements of its input, running the -- effects and discarding the results. -- --
--   drainN n = Fold.take n Fold.drain
--   
-- -- Pre-release drainN :: Monad m => Int -> Fold m a () -- | Like index, except with a more general Integral argument -- -- Pre-release genericIndex :: (Integral i, Monad m) => i -> Fold m a (Maybe a) -- | Lookup the element at the given index. -- -- See also: !! index :: Monad m => Int -> Fold m a (Maybe a) -- | Extract the first element of the stream, if any. head :: Monad m => Fold m a (Maybe a) -- | Returns the first element that satisfies the given predicate. find :: Monad m => (a -> Bool) -> Fold m a (Maybe a) -- | In a stream of (key-value) pairs (a, b), return the value -- b of the first pair where the key equals the given value -- a. -- --
--   lookup = snd <$> Fold.find ((==) . fst)
--   
lookup :: (Eq a, Monad m) => a -> Fold m (a, b) (Maybe b) -- | Returns the first index that satisfies the given predicate. findIndex :: Monad m => (a -> Bool) -> Fold m a (Maybe Int) -- | Returns the first index where a given value is found in the stream. -- --
--   elemIndex a = Fold.findIndex (== a)
--   
elemIndex :: (Eq a, Monad m) => a -> Fold m a (Maybe Int) -- | Return True if the input stream is empty. -- --
--   null = fmap isJust Fold.head
--   
null :: Monad m => Fold m a Bool -- | Return True if the given element is present in the stream. -- --
--   elem a = Fold.any (== a)
--   
elem :: (Eq a, Monad m) => a -> Fold m a Bool -- | Returns True if the given element is not present in the stream. -- --
--   notElem a = Fold.all (/= a)
--   
notElem :: (Eq a, Monad m) => a -> Fold m a Bool -- | Returns True if all elements of a stream satisfy a predicate. -- --
--   >>> Stream.fold (Fold.all (== 0)) $ Stream.fromList [1,0,1]
--   False
--   
-- --
--   all p = Fold.lmap p Fold.and
--   
all :: Monad m => (a -> Bool) -> Fold m a Bool -- | Returns True if any of the elements of a stream satisfies a -- predicate. -- --
--   >>> Stream.fold (Fold.any (== 0)) $ Stream.fromList [1,0,1]
--   True
--   
-- --
--   any p = Fold.lmap p Fold.or
--   
any :: Monad m => (a -> Bool) -> Fold m a Bool -- | Returns True if all elements are True, False -- otherwise -- --
--   and = Fold.all (== True)
--   
and :: Monad m => Fold m Bool Bool -- | Returns True if any element is True, False -- otherwise -- --
--   or = Fold.any (== True)
--   
or :: Monad m => Fold m Bool Bool -- | Change the predicate function of a Fold from a -> b to -- accept an additional state input (s, a) -> b. Convenient -- to filter with an addiitonal index or time input. -- --
--   filterWithIndex = with indexed filter
--   filterWithAbsTime = with timestamped filter
--   filterWithRelTime = with timeIndexed filter
--   
-- -- Pre-release with :: (Fold m (s, a) b -> Fold m a b) -> (((s, a) -> c) -> Fold m (s, a) b -> Fold m (s, a) b) -> ((s, a) -> c) -> Fold m a b -> Fold m a b -- | Change the underlying monad of a fold -- -- Pre-release hoist :: (forall x. m x -> n x) -> Fold m a b -> Fold n a b -- | Adapt a pure fold to any monad -- --
--   generally = Fold.hoist (return . runIdentity)
--   
-- -- Pre-release generally :: Monad m => Fold Identity a b -> Fold m a b -- | Map a monadic function on the output of a fold. rmapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c -- | Apply a transformation on a Fold using a Pipe. -- -- Pre-release transform :: Monad m => Pipe m a b -> Fold m b c -> Fold m a c -- | lmap f fold maps the function f on the input of the -- fold. -- --
--   >>> Stream.fold (Fold.lmap (\x -> x * x) Fold.sum) (Stream.enumerateFromTo 1 100)
--   338350
--   
-- --
--   lmap = Fold.lmapM return
--   
lmap :: (a -> b) -> Fold m b r -> Fold m a r -- | lmapM f fold maps the monadic function f on the -- input of the fold. lmapM :: Monad m => (a -> m b) -> Fold m b r -> Fold m a r -- | Scan the input of a Fold to change it in a stateful manner -- using another Fold. Pre-release scan :: Monad m => Fold m a b -> Fold m b c -> Fold m a c -- | Pair each element of a fold input with its index, starting from index -- 0. -- -- Unimplemented indexed :: Fold m (Int, a) b -> Fold m a b -- | Include only those elements that pass a predicate. -- --
--   >>> Stream.fold (Fold.filter (> 5) Fold.sum) $ Stream.fromList [1..10]
--   40
--   
-- --
--   filter f = Fold.filterM (return . f)
--   
filter :: Monad m => (a -> Bool) -> Fold m a r -> Fold m a r -- | Like filter but with a monadic predicate. filterM :: Monad m => (a -> m Bool) -> Fold m a r -> Fold m a r -- | sampleFromthen offset stride samples the element at -- offset index and then every element at strides of -- stride. -- -- Unimplemented sampleFromthen :: Monad m => Int -> Int -> Fold m a b -> Fold m a b -- | Modify a fold to receive a Maybe input, the Just values -- are unwrapped and sent to the original fold, Nothing values are -- discarded. catMaybes :: Monad m => Fold m a b -> Fold m (Maybe a) b -- | mapMaybe f fold maps a Maybe returning function -- f on the input of the fold, filters out Nothing -- elements, and return the values extracted from Just. -- --
--   >>> f x = if even x then Just x else Nothing
--   
--   >>> fld = Fold.mapMaybe f Fold.toList
--   
--   >>> Stream.fold fld (Stream.enumerateFromTo 1 10)
--   [2,4,6,8,10]
--   
mapMaybe :: Monad m => (a -> Maybe b) -> Fold m b r -> Fold m a r -- | Take at most n input elements and fold them using the -- supplied fold. A negative count is treated as 0. -- --
--   >>> Stream.fold (Fold.take 2 Fold.toList) $ Stream.fromList [1..10]
--   [1,2]
--   
take :: Monad m => Int -> Fold m a b -> Fold m a b -- | Take the input, stop when the predicate succeeds taking the succeeding -- element as well. -- --
--   >>> Stream.fold (Fold.takeEndBy (== '\n') Fold.toList) $ Stream.fromList "hello\nthere\n"
--   "hello\n"
--   
-- --
--   >>> Stream.toList $ Stream.foldMany (Fold.takeEndBy (== '\n') Fold.toList) $ Stream.fromList "hello\nthere\n"
--   ["hello\n","there\n"]
--   
-- --
--   Stream.splitWithSuffix p f = Stream.foldMany (Fold.takeEndBy p f)
--   
-- -- See splitWithSuffix for more details on splitting a stream -- using takeEndBy. takeEndBy :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a b -- | Like takeEndBy but drops the element on which the predicate -- succeeds. -- --
--   >>> Stream.fold (Fold.takeEndBy_ (== '\n') Fold.toList) $ Stream.fromList "hello\nthere\n"
--   "hello"
--   
-- --
--   >>> Stream.toList $ Stream.foldMany (Fold.takeEndBy_ (== '\n') Fold.toList) $ Stream.fromList "hello\nthere\n"
--   ["hello","there"]
--   
-- --
--   Stream.splitOnSuffix p f = Stream.foldMany (Fold.takeEndBy_ p f)
--   
-- -- See splitOnSuffix for more details on splitting a stream using -- takeEndBy_. takeEndBy_ :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a b -- | Sequential fold application. Apply two folds sequentially to an input -- stream. The input is provided to the first fold, when it is done - the -- remaining input is provided to the second fold. When the second fold -- is done or if the input stream is over, the outputs of the two folds -- are combined using the supplied function. -- --
--   >>> f = Fold.serialWith (,) (Fold.take 8 Fold.toList) (Fold.takeEndBy (== '\n') Fold.toList)
--   
--   >>> Stream.fold f $ Stream.fromList "header: hello\n"
--   ("header: ","hello\n")
--   
-- -- Note: This is dual to appending streams using serial. -- -- Note: this implementation allows for stream fusion but has quadratic -- time complexity, because each composition adds a new branch that each -- subsequent fold's input element has to traverse, therefore, it cannot -- scale to a large number of compositions. After around 100 compositions -- the performance starts dipping rapidly compared to a CPS style -- implementation. -- -- Time: O(n^2) where n is the number of compositions. serialWith :: Monad m => (a -> b -> c) -> Fold m x a -> Fold m x b -> Fold m x c -- | Same as applicative *>. Run two folds serially one after the -- other discarding the result of the first. -- -- This was written in the hope that it might be faster than implementing -- it using serialWith, but the current benchmarks show that it has the -- same performance. So do not expose it unless some benchmark shows -- benefit. serial_ :: Monad m => Fold m x a -> Fold m x b -> Fold m x b -- | splitAt n f1 f2 composes folds f1 and f2 -- such that first n elements of its input are consumed by fold -- f1 and the rest of the stream is consumed by fold -- f2. -- --
--   >>> let splitAt_ n xs = Stream.fold (Fold.splitAt n Fold.toList Fold.toList) $ Stream.fromList xs
--   
-- --
--   >>> splitAt_ 6 "Hello World!"
--   ("Hello ","World!")
--   
-- --
--   >>> splitAt_ (-1) [1,2,3]
--   ([],[1,2,3])
--   
-- --
--   >>> splitAt_ 0 [1,2,3]
--   ([],[1,2,3])
--   
-- --
--   >>> splitAt_ 1 [1,2,3]
--   ([1],[2,3])
--   
-- --
--   >>> splitAt_ 3 [1,2,3]
--   ([1,2,3],[])
--   
-- --
--   >>> splitAt_ 4 [1,2,3]
--   ([1,2,3],[])
--   
-- --
--   splitAt n f1 f2 = Fold.serialWith (,) (Fold.take n f1) f2
--   
-- -- Internal splitAt :: Monad m => Int -> Fold m a b -> Fold m a c -> Fold m a (b, c) -- | teeWith k f1 f2 distributes its input to both f1 and -- f2 until both of them terminate and combines their output -- using k. -- --
--   >>> avg = Fold.teeWith (/) Fold.sum (fmap fromIntegral Fold.length)
--   
--   >>> Stream.fold avg $ Stream.fromList [1.0..100.0]
--   50.5
--   
-- --
--   teeWith k f1 f2 = fmap (uncurry k) ((Fold.tee f1 f2)
--   
-- -- For applicative composition using this combinator see -- Streamly.Internal.Data.Fold.Tee. -- -- See also: Streamly.Internal.Data.Fold.Tee teeWith :: Monad m => (a -> b -> c) -> Fold m x a -> Fold m x b -> Fold m x c -- | Distribute one copy of the stream to each fold and zip the results. -- --
--                   |-------Fold m a b--------|
--   ---stream m a---|                         |---m (b,c)
--                   |-------Fold m a c--------|
--   
-- --
--   >>> Stream.fold (Fold.tee Fold.sum Fold.length) (Stream.enumerateFromTo 1.0 100.0)
--   (5050.0,100)
--   
-- --
--   tee = teeWith (,)
--   
tee :: Monad m => Fold m a b -> Fold m a c -> Fold m a (b, c) -- | Like teeWith but terminates as soon as the first fold -- terminates. -- -- Pre-release teeWithFst :: Monad m => (b -> c -> d) -> Fold m a b -> Fold m a c -> Fold m a d -- | Like teeWith but terminates as soon as any one of the two folds -- terminates. -- -- Pre-release teeWithMin :: Monad m => (b -> c -> d) -> Fold m a b -> Fold m a c -> Fold m a d -- | Distribute one copy of the stream to each fold and collect the results -- in a container. -- --
--                   |-------Fold m a b--------|
--   ---stream m a---|                         |---m [b]
--                   |-------Fold m a b--------|
--                   |                         |
--                              ...
--   
-- --
--   >>> Stream.fold (Fold.distribute [Fold.sum, Fold.length]) (Stream.enumerateFromTo 1 5)
--   [15,5]
--   
-- --
--   distribute = Prelude.foldr (Fold.teeWith (:)) (Fold.fromPure [])
--   
-- -- This is the consumer side dual of the producer side sequence -- operation. -- -- Stops when all the folds stop. distribute :: Monad m => [Fold m a b] -> Fold m a [b] -- | Shortest alternative. Apply both folds in parallel but choose the -- result from the one which consumed least input i.e. take the shortest -- succeeding fold. -- -- If both the folds finish at the same time or if the result is -- extracted before any of the folds could finish then the left one is -- taken. -- -- Pre-release shortest :: Monad m => Fold m x a -> Fold m x b -> Fold m x (Either a b) -- | Longest alternative. Apply both folds in parallel but choose the -- result from the one which consumed more input i.e. take the longest -- succeeding fold. -- -- If both the folds finish at the same time or if the result is -- extracted before any of the folds could finish then the left one is -- taken. -- -- Pre-release longest :: Monad m => Fold m x a -> Fold m x b -> Fold m x (Either a b) -- | Partition the input over two folds using an Either partitioning -- predicate. -- --
--                                       |-------Fold b x--------|
--   -----stream m a --> (Either b c)----|                       |----(x,y)
--                                       |-------Fold c y--------|
--   
-- -- Send input to either fold randomly: -- --
--   > import System.Random (randomIO)
--   > randomly a = randomIO >>= \x -> return $ if x then Left a else Right a
--   > Stream.fold (Fold.partitionByM randomly Fold.length Fold.length) (Stream.enumerateFromTo 1 100)
--   (59,41)
--   
-- -- Send input to the two folds in a proportion of 2:1: -- --
--   >>> :{
--   proportionately m n = do
--    ref <- newIORef $ cycle $ concat [replicate m Left, replicate n Right]
--    return $ \a -> do
--        r <- readIORef ref
--        writeIORef ref $ tail r
--        return $ Prelude.head r a
--   :}
--   
-- --
--   >>> :{
--   main = do
--    f <- proportionately 2 1
--    r <- Stream.fold (Fold.partitionByM f Fold.length Fold.length) (Stream.enumerateFromTo (1 :: Int) 100)
--    print r
--   :}
--   
-- --
--   >>> main
--   (67,33)
--   
-- -- This is the consumer side dual of the producer side mergeBy -- operation. -- -- When one fold is done, any input meant for it is ignored until the -- other fold is also done. -- -- Stops when both the folds stop. -- -- See also: partitionByFstM and partitionByMinM. -- -- Pre-release partitionByM :: Monad m => (a -> m (Either b c)) -> Fold m b x -> Fold m c y -> Fold m a (x, y) -- | Similar to partitionByM but terminates when the first fold -- terminates. partitionByFstM :: Monad m => (a -> m (Either b c)) -> Fold m b x -> Fold m c y -> Fold m a (x, y) -- | Similar to partitionByM but terminates when any fold -- terminates. partitionByMinM :: Monad m => (a -> m (Either b c)) -> Fold m b x -> Fold m c y -> Fold m a (x, y) -- | Same as partitionByM but with a pure partition function. -- -- Count even and odd numbers in a stream: -- --
--   >>> :{
--    let f = Fold.partitionBy (\n -> if even n then Left n else Right n)
--                        (fmap (("Even " ++) . show) Fold.length)
--                        (fmap (("Odd "  ++) . show) Fold.length)
--     in Stream.fold f (Stream.enumerateFromTo 1 100)
--   :}
--   ("Even 50","Odd 50")
--   
-- -- Pre-release partitionBy :: Monad m => (a -> Either b c) -> Fold m b x -> Fold m c y -> Fold m a (x, y) -- | Compose two folds such that the combined fold accepts a stream of -- Either and routes the Left values to the first fold and -- Right values to the second fold. -- --
--   partition = partitionBy id
--   
partition :: Monad m => Fold m b x -> Fold m c y -> Fold m (Either b c) (x, y) -- | Fold a stream of key value pairs using a map of specific folds for -- each key into a map from keys to the results of fold outputs of the -- corresponding values. -- --
--   >>> import qualified Data.Map
--   
--   >>> :{
--    let table = Data.Map.fromList [("SUM", Fold.sum), ("PRODUCT", Fold.product)]
--        input = Stream.fromList [("SUM",1),("PRODUCT",2),("SUM",3),("PRODUCT",4)]
--     in Stream.fold (Fold.demux table) input
--   :}
--   fromList [("PRODUCT",8),("SUM",4)]
--   
-- --
--   demux = demuxWith id
--   
-- -- Pre-release demux :: (Monad m, Ord k) => Map k (Fold m a b) -> Fold m (k, a) (Map k b) -- | Split the input stream based on a key field and fold each split using -- a specific fold collecting the results in a map from the keys to the -- results. Useful for cases like protocol handlers to handle different -- type of packets using different handlers. -- --
--                               |-------Fold m a b
--   -----stream m a-----Map-----|
--                               |-------Fold m a b
--                               |
--                                         ...
--   
-- -- Any input that does not map to a fold in the input Map is silently -- ignored. -- --
--   demuxWith f kv = fmap fst $ demuxDefaultWith f kv drain
--   
-- -- Pre-release demuxWith :: (Monad m, Ord k) => (a -> (k, a')) -> Map k (Fold m a' b) -> Fold m a (Map k b) -- |
--   demuxDefault = demuxDefaultWith id
--   
-- -- Pre-release demuxDefault :: (Monad m, Ord k) => Map k (Fold m a b) -> Fold m (k, a) b -> Fold m (k, a) (Map k b, b) -- | Like demuxWith but uses a default catchall fold to handle -- inputs which do not have a specific fold in the map to handle them. -- -- If any fold in the map stops, inputs meant for that fold are sent to -- the catchall fold. If the catchall fold stops then inputs that do not -- match any fold are ignored. -- -- Stops when all the folds, including the catchall fold, stop. -- -- Pre-release demuxDefaultWith :: (Monad m, Ord k) => (a -> (k, a')) -> Map k (Fold m a' b) -> Fold m (k, a') c -> Fold m a (Map k b, c) -- | Given an input stream of key value pairs and a fold for values, fold -- all the values belonging to each key. Useful for map/reduce, -- bucketizing the input in different bins or for generating histograms. -- --
--   >>> :{
--    let input = Stream.fromList [("ONE",1),("ONE",1.1),("TWO",2), ("TWO",2.2)]
--     in Stream.fold (Fold.classify Fold.toList) input
--   :}
--   fromList [("ONE",[1.0,1.1]),("TWO",[2.0,2.2])]
--   
-- -- Same as: -- --
--   classify fld = Fold.classifyWith fst (lmap snd fld)
--   
-- -- Pre-release classify :: (Monad m, Ord k) => Fold m a b -> Fold m (k, a) (Map k b) -- | Split the input stream based on a key field and fold each split using -- the given fold. Useful for map/reduce, bucketizing the input in -- different bins or for generating histograms. -- --
--   >>> :{
--    let input = Stream.fromList [("ONE",1),("ONE",1.1),("TWO",2), ("TWO",2.2)]
--     in Stream.fold (Fold.classifyWith fst (Fold.map snd Fold.toList)) input
--   :}
--   fromList [("ONE",[1.0,1.1]),("TWO",[2.0,2.2])]
--   
-- -- If the classifier fold stops for a particular key any further inputs -- in that bucket are ignored. -- -- Stops: never -- -- Pre-release classifyWith :: (Monad m, Ord k) => (a -> k) -> Fold m a b -> Fold m a (Map k b) -- | Send the elements of tuples in a stream of tuples through two -- different folds. -- --
--                             |-------Fold m a x--------|
--   ---------stream of (a,b)--|                         |----m (x,y)
--                             |-------Fold m b y--------|
--   
-- --
--   unzip = Fold.unzipWith id
--   
-- -- This is the consumer side dual of the producer side zip -- operation. unzip :: Monad m => Fold m a x -> Fold m b y -> Fold m (a, b) (x, y) -- | Split elements in the input stream into two parts using a pure -- splitter function, direct each part to a different fold and zip the -- results. -- --
--   unzipWith f fld1 fld2 = Fold.lmap f (Fold.unzip fld1 fld2)
--   
-- -- This fold terminates when both the input folds terminate. -- -- Pre-release unzipWith :: Monad m => (a -> (b, c)) -> Fold m b x -> Fold m c y -> Fold m a (x, y) -- | Like unzipWith but with a monadic splitter function. -- --
--   unzipWithM k f1 f2 = lmapM k (unzip f1 f2)
--   
-- -- Pre-release unzipWithM :: Monad m => (a -> m (b, c)) -> Fold m b x -> Fold m c y -> Fold m a (x, y) -- | Similar to unzipWithM but terminates when the first fold -- terminates. unzipWithFstM :: Monad m => (a -> m (b, c)) -> Fold m b x -> Fold m c y -> Fold m a (x, y) -- | Similar to unzipWithM but terminates when any fold terminates. unzipWithMinM :: Monad m => (a -> m (b, c)) -> Fold m b x -> Fold m c y -> Fold m a (x, y) -- | Zip a stream with the input of a fold using the supplied function. -- -- Unimplemented zipWithM :: (a -> b -> m c) -> t m a -> Fold m c x -> Fold m b x -- | Zip a stream with the input of a fold. -- -- Unimplemented zip :: Monad m => t m a -> Fold m (a, b) x -> Fold m b x -- | Collect zero or more applications of a fold. many split -- collect applies the split fold repeatedly on the input -- stream and accumulates zero or more fold results using -- collect. -- --
--   >>> two = Fold.take 2 Fold.toList
--   
--   >>> twos = Fold.many two Fold.toList
--   
--   >>> Stream.fold twos $ Stream.fromList [1..10]
--   [[1,2],[3,4],[5,6],[7,8],[9,10]]
--   
-- -- Stops when collect stops. -- -- See also: concatMap, foldMany many :: Monad m => Fold m a b -> Fold m b c -> Fold m a c -- | chunksOf n split collect repeatedly applies the -- split fold to chunks of n items in the input stream -- and supplies the result to the collect fold. -- --
--   >>> twos = Fold.chunksOf 2 Fold.toList Fold.toList
--   
--   >>> Stream.fold twos $ Stream.fromList [1..10]
--   [[1,2],[3,4],[5,6],[7,8],[9,10]]
--   
-- --
--   chunksOf n split = many (take n split)
--   
-- -- Stops when collect stops. chunksOf :: Monad m => Int -> Fold m a b -> Fold m b c -> Fold m a c -- | Group the input stream into groups of elements between low -- and high. Collection starts in chunks of low and -- then keeps doubling until we reach high. Each chunk is folded -- using the provided fold function. -- -- This could be useful, for example, when we are folding a stream of -- unknown size to a stream of arrays and we want to minimize the number -- of allocations. -- -- NOTE: this would be an application of "many" using a terminating fold. -- -- Unimplemented chunksBetween :: Int -> Int -> Fold m a b -> Fold m b c -> Fold m a c -- | concatSequence f t applies folds from stream t -- sequentially and collects the results using the fold f. -- -- Unimplemented concatSequence :: Fold m b c -> t (Fold m a b) -> Fold m a c -- | Map a Fold returning function on the result of a Fold -- and run the returned fold. This operation can be used to express data -- dependencies between fold operations. -- -- Let's say the first element in the stream is a count of the following -- elements that we have to add, then: -- --
--   >>> import Data.Maybe (fromJust)
--   
--   >>> count = fmap fromJust Fold.head
--   
--   >>> total n = Fold.take n Fold.sum
--   
--   >>> Stream.fold (Fold.concatMap total count) $ Stream.fromList [10,9..1]
--   45
--   
-- -- Time: O(n^2) where n is the number of compositions. -- -- See also: foldIterateM concatMap :: Monad m => (b -> Fold m a c) -> Fold m a b -> Fold m a c -- | Run the initialization effect of a fold. The returned fold would use -- the value returned by this effect as its initial value. -- -- Pre-release initialize :: Monad m => Fold m a b -> m (Fold m a b) -- | Append a singleton value to the fold. -- --
--   >>> import qualified Data.Foldable as Foldable
--   
--   >>> Foldable.foldlM Fold.snoc Fold.toList [1..3] >>= Fold.finish
--   [1,2,3]
--   
-- -- Compare with duplicate which allows appending a stream to the -- fold. -- -- Pre-release snoc :: Monad m => Fold m a b -> a -> m (Fold m a b) -- | duplicate provides the ability to run a fold in parts. The -- duplicated fold consumes the input and returns the same fold as output -- instead of returning the final result, the returned fold can be run -- later to consume more input. -- -- We can append a stream to a fold as follows: -- --
--   >>> :{
--   foldAppend :: Monad m => Fold m a b -> SerialT m a -> m (Fold m a b)
--   foldAppend f = Stream.fold (Fold.duplicate f)
--   :}
--   
-- --
--   >>> :{
--   do
--    sum1 <- foldAppend Fold.sum (Stream.enumerateFromTo 1 10)
--    sum2 <- foldAppend sum1 (Stream.enumerateFromTo 11 20)
--    Stream.fold sum2 (Stream.enumerateFromTo 21 30)
--   :}
--   465
--   
-- -- duplicate essentially appends a stream to the fold without -- finishing the fold. Compare with snoc which appends a singleton -- value to the fold. -- -- Pre-release duplicate :: Monad m => Fold m a b -> Fold m a (Fold m a b) -- | Finish the fold to extract the current value of the fold. -- --
--   >>> Fold.finish Fold.toList
--   []
--   
-- -- Pre-release finish :: Monad m => Fold m a b -> m b -- | Flatten the monadic output of a fold to pure output. -- | Deprecated: Use "rmapM id" instead sequence :: Monad m => Fold m a (m b) -> Fold m a b -- | Map a monadic function on the output of a fold. -- | Deprecated: Use rmapM instead mapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c -- | A Fold is a sink or a consumer of a stream of values. The -- Fold type consists of an accumulator and an effectful action -- that absorbs a value into the accumulator. -- --
--   >>> import Data.Function ((&))
--   
--   >>> import qualified Streamly.Data.Fold as Fold
--   
--   >>> import qualified Streamly.Prelude as Stream
--   
-- -- For example, a sum Fold represents adding the input to the -- accumulated sum. A fold driver e.g. fold pushes values from a -- stream to the Fold one at a time, reducing the stream to a -- single value. -- --
--   >>> Stream.fold Fold.sum $ Stream.fromList [1..100]
--   5050
--   
-- -- Conceptually, a Fold is a data type that can mimic a strict -- left fold (foldl) as well as lazy right fold (foldr). -- The above example is similar to a left fold using (+) as the -- step and 0 as the initial value of the accumulator: -- --
--   >>> Data.List.foldl' (+) 0 [1..100]
--   5050
--   
-- -- Folds have an early termination capability e.g. the head -- fold would terminate on an infinite stream: -- --
--   >>> Stream.fold Fold.head $ Stream.fromList [1..]
--   Just 1
--   
-- -- The above example is similar to the following right fold: -- --
--   >>> Prelude.foldr (\x _ -> Just x) Nothing [1..]
--   Just 1
--   
-- -- Folds can be combined together using combinators. For example, -- to create a fold that sums first two elements in a stream: -- --
--   >>> sumTwo = Fold.take 2 Fold.sum
--   
--   >>> Stream.fold sumTwo $ Stream.fromList [1..100]
--   3
--   
-- -- Folds can be combined to run in parallel on the same input. For -- example, to compute the average of numbers in a stream without going -- through the stream twice: -- --
--   >>> avg = Fold.teeWith (/) Fold.sum (fmap fromIntegral Fold.length)
--   
--   >>> Stream.fold avg $ Stream.fromList [1.0..100.0]
--   50.5
--   
-- -- Folds can be combined so as to partition the input stream over -- multiple folds. For example, to count even and odd numbers in a -- stream: -- --
--   >>> split n = if even n then Left n else Right n
--   
--   >>> stream = Stream.map split $ Stream.fromList [1..100]
--   
--   >>> countEven = fmap (("Even " ++) . show) Fold.length
--   
--   >>> countOdd = fmap (("Odd "  ++) . show) Fold.length
--   
--   >>> f = Fold.partition countEven countOdd
--   
--   >>> Stream.fold f stream
--   ("Even 50","Odd 50")
--   
-- -- Terminating folds can be combined to parse the stream serially such -- that the first fold consumes the input until it terminates and the -- second fold consumes the rest of the input until it terminates: -- --
--   >>> f = Fold.serialWith (,) (Fold.take 8 Fold.toList) (Fold.takeEndBy (== '\n') Fold.toList)
--   
--   >>> Stream.fold f $ Stream.fromList "header: hello\n"
--   ("header: ","hello\n")
--   
-- -- A Fold can be applied repeatedly on a stream to transform it to -- a stream of fold results. To split a stream on newlines: -- --
--   >>> f = Fold.takeEndBy (== '\n') Fold.toList
--   
--   >>> Stream.toList $ Stream.foldMany f $ Stream.fromList "Hello there!\nHow are you\n"
--   ["Hello there!\n","How are you\n"]
--   
-- -- Similarly, we can split the input of a fold too: -- --
--   >>> Stream.fold (Fold.many f Fold.toList) $ Stream.fromList "Hello there!\nHow are you\n"
--   ["Hello there!\n","How are you\n"]
--   
-- -- Please see Streamly.Internal.Data.Fold for additional -- Pre-release functions. -- --

Folds vs. Streams

-- -- We can often use streams or folds to achieve the same goal. However, -- streams are more efficient in composition of producers (e.g. -- serial or mergeBy) whereas folds are more efficient in -- composition of consumers (e.g. serialWith, partition or -- teeWith). -- -- Streams are producers, transformations on streams happen on the output -- side: -- --
--   >>> :{
--    f stream =
--          Stream.filter odd stream
--        & Stream.map (+1)
--        & Stream.sum
--   :}
--   
-- --
--   >>> f $ Stream.fromList [1..100 :: Int]
--   2550
--   
-- -- Folds are stream consumers with an input stream and an output value, -- stream transformations on folds happen on the input side: -- --
--   >>> :{
--   f =
--          Fold.filter odd
--        $ Fold.lmap (+1)
--        $ Fold.sum
--   :}
--   
-- --
--   >>> Stream.fold f $ Stream.fromList [1..100 :: Int]
--   2550
--   
-- -- Notice the similiarity in the definition of f in both cases, -- the only difference is the composition by & vs $ -- and the use lmap vs map, the difference is due to -- output vs input side transformations. module Streamly.Data.Fold -- | The type Fold m a b having constructor Fold step initial -- extract represents a fold over an input stream of values of type -- a to a final value of type b in Monad -- m. -- -- The fold uses an intermediate state s as accumulator, the -- type s is internal to the specific fold definition. The -- initial value of the fold state s is returned by -- initial. The step function consumes an input and -- either returns the final result b if the fold is done or the -- next intermediate state (see Step). At any point the fold -- driver can extract the result from the intermediate state using the -- extract function. -- -- NOTE: The constructor is not yet exposed via exposed modules, smart -- constructors are provided to create folds. If you think you need the -- constructor of this type please consider using the smart constructors -- in Streamly.Internal.Data.Fold instead. -- -- since 0.8.0 (type changed) data Fold m a b -- | Make a fold from a left fold style pure step function and initial -- value of the accumulator. -- -- If your Fold returns only Partial (i.e. never returns a -- Done) then you can use foldl'* constructors. -- -- A fold with an extract function can be expressed using fmap: -- --
--   mkfoldlx :: Monad m => (s -> a -> s) -> s -> (s -> b) -> Fold m a b
--   mkfoldlx step initial extract = fmap extract (foldl' step initial)
--   
-- -- See also: Streamly.Prelude.foldl' foldl' :: Monad m => (b -> a -> b) -> b -> Fold m a b -- | Make a fold from a left fold style monadic step function and initial -- value of the accumulator. -- -- A fold with an extract function can be expressed using rmapM: -- --
--   mkFoldlxM :: Functor m => (s -> a -> m s) -> m s -> (s -> m b) -> Fold m a b
--   mkFoldlxM step initial extract = rmapM extract (foldlM' step initial)
--   
-- -- See also: Streamly.Prelude.foldlM' foldlM' :: Monad m => (b -> a -> m b) -> m b -> Fold m a b -- | Make a fold using a right fold style step function and a terminal -- value. It performs a strict right fold via a left fold using function -- composition. Note that this is strict fold, it can only be useful for -- constructing strict structures in memory. For reductions this will be -- very inefficient. -- -- For example, -- --
--   toList = foldr (:) []
--   
-- -- See also: foldr foldr :: Monad m => (a -> b -> b) -> b -> Fold m a b -- | Append the elements of an input stream to a provided starting value. -- --
--   >>> Stream.fold (Fold.sconcat 10) (Stream.map Data.Monoid.Sum $ Stream.enumerateFromTo 1 10)
--   Sum {getSum = 65}
--   
-- --
--   sconcat = Fold.foldl' (<>)
--   
sconcat :: (Monad m, Semigroup a) => a -> Fold m a a -- | Fold an input stream consisting of monoidal elements using -- mappend and mempty. -- --
--   >>> Stream.fold Fold.mconcat (Stream.map Data.Monoid.Sum $ Stream.enumerateFromTo 1 10)
--   Sum {getSum = 55}
--   
-- --
--   mconcat = Fold.sconcat mempty
--   
mconcat :: (Monad m, Monoid a) => Fold m a a -- |
--   foldMap f = Fold.lmap f Fold.mconcat
--   
-- -- Make a fold from a pure function that folds the output of the function -- using mappend and mempty. -- --
--   >>> Stream.fold (Fold.foldMap Data.Monoid.Sum) $ Stream.enumerateFromTo 1 10
--   Sum {getSum = 55}
--   
foldMap :: (Monad m, Monoid b) => (a -> b) -> Fold m a b -- |
--   foldMapM f = Fold.lmapM f Fold.mconcat
--   
-- -- Make a fold from a monadic function that folds the output of the -- function using mappend and mempty. -- --
--   >>> Stream.fold (Fold.foldMapM (return . Data.Monoid.Sum)) $ Stream.enumerateFromTo 1 10
--   Sum {getSum = 55}
--   
foldMapM :: (Monad m, Monoid b) => (a -> m b) -> Fold m a b -- | A fold that drains all its input, running the effects and discarding -- the results. -- --
--   drain = drainBy (const (return ()))
--   
drain :: Monad m => Fold m a () -- |
--   drainBy f = lmapM f drain
--   drainBy = Fold.foldMapM (void . f)
--   
-- -- Drain all input after passing it through a monadic function. This is -- the dual of mapM_ on stream producers. -- -- See also: mapM_ drainBy :: Monad m => (a -> m b) -> Fold m a () -- | Extract the last element of the input stream, if any. -- --
--   last = fmap getLast $ Fold.foldMap (Last . Just)
--   
last :: Monad m => Fold m a (Maybe a) -- | Determine the length of the input stream. -- --
--   length = fmap getSum $ Fold.foldMap (Sum . const  1)
--   
length :: Monad m => Fold m a Int -- | Determine the sum of all elements of a stream of numbers. Returns -- additive identity (0) when the stream is empty. Note that -- this is not numerically stable for floating point numbers. -- --
--   sum = fmap getSum $ Fold.foldMap Sum
--   
sum :: (Monad m, Num a) => Fold m a a -- | Determine the product of all elements of a stream of numbers. Returns -- multiplicative identity (1) when the stream is empty. The -- fold terminates when it encounters (0) in its input. -- -- Compare with Fold.foldMap Product. -- -- Since 0.8.0 (Added Eq constraint) product :: (Monad m, Num a, Eq a) => Fold m a a -- | Determine the maximum element in a stream using the supplied -- comparison function. maximumBy :: Monad m => (a -> a -> Ordering) -> Fold m a (Maybe a) -- |
--   maximum = Fold.maximumBy compare
--   
-- -- Determine the maximum element in a stream. -- -- Compare with Fold.foldMap Max. maximum :: (Monad m, Ord a) => Fold m a (Maybe a) -- | Computes the minimum element with respect to the given comparison -- function minimumBy :: Monad m => (a -> a -> Ordering) -> Fold m a (Maybe a) -- | Determine the minimum element in a stream using the supplied -- comparison function. -- --
--   minimum = minimumBy compare
--   
-- -- Compare with Fold.foldMap Min. minimum :: (Monad m, Ord a) => Fold m a (Maybe a) -- | Compute a numerically stable arithmetic mean of all elements in the -- input stream. mean :: (Monad m, Fractional a) => Fold m a a -- | Compute a numerically stable (population) variance over all elements -- in the input stream. variance :: (Monad m, Fractional a) => Fold m a a -- | Compute a numerically stable (population) standard deviation over all -- elements in the input stream. stdDev :: (Monad m, Floating a) => Fold m a a -- | Compute an Int sized polynomial rolling hash of a stream. -- --
--   rollingHash = Fold.rollingHashWithSalt defaultSalt
--   
rollingHash :: (Monad m, Enum a) => Fold m a Int64 -- | Compute an Int sized polynomial rolling hash -- --
--   H = salt * k ^ n + c1 * k ^ (n - 1) + c2 * k ^ (n - 2) + ... + cn * k ^ 0
--   
-- -- Where c1, c2, cn are the elements in the -- input stream and k is a constant. -- -- This hash is often used in Rabin-Karp string search algorithm. -- -- See https://en.wikipedia.org/wiki/Rolling_hash rollingHashWithSalt :: (Monad m, Enum a) => Int64 -> Fold m a Int64 -- | Folds the input stream to a list. -- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using -- Streamly.Data.Array.Foreign instead. -- --
--   toList = foldr (:) []
--   
toList :: Monad m => Fold m a [a] -- | Buffers the input stream to a list in the reverse order of the input. -- --
--   toListRev = Fold.foldl' (flip (:)) []
--   
-- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using Streamly.Array -- instead. toListRev :: Monad m => Fold m a [a] -- | Lookup the element at the given index. -- -- See also: !! index :: Monad m => Int -> Fold m a (Maybe a) -- | Extract the first element of the stream, if any. head :: Monad m => Fold m a (Maybe a) -- | Returns the first element that satisfies the given predicate. find :: Monad m => (a -> Bool) -> Fold m a (Maybe a) -- | In a stream of (key-value) pairs (a, b), return the value -- b of the first pair where the key equals the given value -- a. -- --
--   lookup = snd <$> Fold.find ((==) . fst)
--   
lookup :: (Eq a, Monad m) => a -> Fold m (a, b) (Maybe b) -- | Returns the first index that satisfies the given predicate. findIndex :: Monad m => (a -> Bool) -> Fold m a (Maybe Int) -- | Returns the first index where a given value is found in the stream. -- --
--   elemIndex a = Fold.findIndex (== a)
--   
elemIndex :: (Eq a, Monad m) => a -> Fold m a (Maybe Int) -- | Return True if the input stream is empty. -- --
--   null = fmap isJust Fold.head
--   
null :: Monad m => Fold m a Bool -- | Return True if the given element is present in the stream. -- --
--   elem a = Fold.any (== a)
--   
elem :: (Eq a, Monad m) => a -> Fold m a Bool -- | Returns True if the given element is not present in the stream. -- --
--   notElem a = Fold.all (/= a)
--   
notElem :: (Eq a, Monad m) => a -> Fold m a Bool -- | Returns True if all elements of a stream satisfy a predicate. -- --
--   >>> Stream.fold (Fold.all (== 0)) $ Stream.fromList [1,0,1]
--   False
--   
-- --
--   all p = Fold.lmap p Fold.and
--   
all :: Monad m => (a -> Bool) -> Fold m a Bool -- | Returns True if any of the elements of a stream satisfies a -- predicate. -- --
--   >>> Stream.fold (Fold.any (== 0)) $ Stream.fromList [1,0,1]
--   True
--   
-- --
--   any p = Fold.lmap p Fold.or
--   
any :: Monad m => (a -> Bool) -> Fold m a Bool -- | Returns True if all elements are True, False -- otherwise -- --
--   and = Fold.all (== True)
--   
and :: Monad m => Fold m Bool Bool -- | Returns True if any element is True, False -- otherwise -- --
--   or = Fold.any (== True)
--   
or :: Monad m => Fold m Bool Bool -- | Map a monadic function on the output of a fold. rmapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c -- | lmap f fold maps the function f on the input of the -- fold. -- --
--   >>> Stream.fold (Fold.lmap (\x -> x * x) Fold.sum) (Stream.enumerateFromTo 1 100)
--   338350
--   
-- --
--   lmap = Fold.lmapM return
--   
lmap :: (a -> b) -> Fold m b r -> Fold m a r -- | lmapM f fold maps the monadic function f on the -- input of the fold. lmapM :: Monad m => (a -> m b) -> Fold m b r -> Fold m a r -- | Include only those elements that pass a predicate. -- --
--   >>> Stream.fold (Fold.filter (> 5) Fold.sum) $ Stream.fromList [1..10]
--   40
--   
-- --
--   filter f = Fold.filterM (return . f)
--   
filter :: Monad m => (a -> Bool) -> Fold m a r -> Fold m a r -- | Like filter but with a monadic predicate. filterM :: Monad m => (a -> m Bool) -> Fold m a r -> Fold m a r -- | Modify a fold to receive a Maybe input, the Just values -- are unwrapped and sent to the original fold, Nothing values are -- discarded. catMaybes :: Monad m => Fold m a b -> Fold m (Maybe a) b -- | mapMaybe f fold maps a Maybe returning function -- f on the input of the fold, filters out Nothing -- elements, and return the values extracted from Just. -- --
--   >>> f x = if even x then Just x else Nothing
--   
--   >>> fld = Fold.mapMaybe f Fold.toList
--   
--   >>> Stream.fold fld (Stream.enumerateFromTo 1 10)
--   [2,4,6,8,10]
--   
mapMaybe :: Monad m => (a -> Maybe b) -> Fold m b r -> Fold m a r -- | Take at most n input elements and fold them using the -- supplied fold. A negative count is treated as 0. -- --
--   >>> Stream.fold (Fold.take 2 Fold.toList) $ Stream.fromList [1..10]
--   [1,2]
--   
take :: Monad m => Int -> Fold m a b -> Fold m a b -- | Like takeEndBy but drops the element on which the predicate -- succeeds. -- --
--   >>> Stream.fold (Fold.takeEndBy_ (== '\n') Fold.toList) $ Stream.fromList "hello\nthere\n"
--   "hello"
--   
-- --
--   >>> Stream.toList $ Stream.foldMany (Fold.takeEndBy_ (== '\n') Fold.toList) $ Stream.fromList "hello\nthere\n"
--   ["hello","there"]
--   
-- --
--   Stream.splitOnSuffix p f = Stream.foldMany (Fold.takeEndBy_ p f)
--   
-- -- See splitOnSuffix for more details on splitting a stream using -- takeEndBy_. takeEndBy_ :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a b -- | Take the input, stop when the predicate succeeds taking the succeeding -- element as well. -- --
--   >>> Stream.fold (Fold.takeEndBy (== '\n') Fold.toList) $ Stream.fromList "hello\nthere\n"
--   "hello\n"
--   
-- --
--   >>> Stream.toList $ Stream.foldMany (Fold.takeEndBy (== '\n') Fold.toList) $ Stream.fromList "hello\nthere\n"
--   ["hello\n","there\n"]
--   
-- --
--   Stream.splitWithSuffix p f = Stream.foldMany (Fold.takeEndBy p f)
--   
-- -- See splitWithSuffix for more details on splitting a stream -- using takeEndBy. takeEndBy :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a b -- | Sequential fold application. Apply two folds sequentially to an input -- stream. The input is provided to the first fold, when it is done - the -- remaining input is provided to the second fold. When the second fold -- is done or if the input stream is over, the outputs of the two folds -- are combined using the supplied function. -- --
--   >>> f = Fold.serialWith (,) (Fold.take 8 Fold.toList) (Fold.takeEndBy (== '\n') Fold.toList)
--   
--   >>> Stream.fold f $ Stream.fromList "header: hello\n"
--   ("header: ","hello\n")
--   
-- -- Note: This is dual to appending streams using serial. -- -- Note: this implementation allows for stream fusion but has quadratic -- time complexity, because each composition adds a new branch that each -- subsequent fold's input element has to traverse, therefore, it cannot -- scale to a large number of compositions. After around 100 compositions -- the performance starts dipping rapidly compared to a CPS style -- implementation. -- -- Time: O(n^2) where n is the number of compositions. serialWith :: Monad m => (a -> b -> c) -> Fold m x a -> Fold m x b -> Fold m x c -- | teeWith k f1 f2 distributes its input to both f1 and -- f2 until both of them terminate and combines their output -- using k. -- --
--   >>> avg = Fold.teeWith (/) Fold.sum (fmap fromIntegral Fold.length)
--   
--   >>> Stream.fold avg $ Stream.fromList [1.0..100.0]
--   50.5
--   
-- --
--   teeWith k f1 f2 = fmap (uncurry k) ((Fold.tee f1 f2)
--   
-- -- For applicative composition using this combinator see -- Streamly.Internal.Data.Fold.Tee. -- -- See also: Streamly.Internal.Data.Fold.Tee teeWith :: Monad m => (a -> b -> c) -> Fold m x a -> Fold m x b -> Fold m x c -- | Distribute one copy of the stream to each fold and zip the results. -- --
--                   |-------Fold m a b--------|
--   ---stream m a---|                         |---m (b,c)
--                   |-------Fold m a c--------|
--   
-- --
--   >>> Stream.fold (Fold.tee Fold.sum Fold.length) (Stream.enumerateFromTo 1.0 100.0)
--   (5050.0,100)
--   
-- --
--   tee = teeWith (,)
--   
tee :: Monad m => Fold m a b -> Fold m a c -> Fold m a (b, c) -- | Distribute one copy of the stream to each fold and collect the results -- in a container. -- --
--                   |-------Fold m a b--------|
--   ---stream m a---|                         |---m [b]
--                   |-------Fold m a b--------|
--                   |                         |
--                              ...
--   
-- --
--   >>> Stream.fold (Fold.distribute [Fold.sum, Fold.length]) (Stream.enumerateFromTo 1 5)
--   [15,5]
--   
-- --
--   distribute = Prelude.foldr (Fold.teeWith (:)) (Fold.fromPure [])
--   
-- -- This is the consumer side dual of the producer side sequence -- operation. -- -- Stops when all the folds stop. distribute :: Monad m => [Fold m a b] -> Fold m a [b] -- | Compose two folds such that the combined fold accepts a stream of -- Either and routes the Left values to the first fold and -- Right values to the second fold. -- --
--   partition = partitionBy id
--   
partition :: Monad m => Fold m b x -> Fold m c y -> Fold m (Either b c) (x, y) -- | Send the elements of tuples in a stream of tuples through two -- different folds. -- --
--                             |-------Fold m a x--------|
--   ---------stream of (a,b)--|                         |----m (x,y)
--                             |-------Fold m b y--------|
--   
-- --
--   unzip = Fold.unzipWith id
--   
-- -- This is the consumer side dual of the producer side zip -- operation. unzip :: Monad m => Fold m a x -> Fold m b y -> Fold m (a, b) (x, y) -- | Collect zero or more applications of a fold. many split -- collect applies the split fold repeatedly on the input -- stream and accumulates zero or more fold results using -- collect. -- --
--   >>> two = Fold.take 2 Fold.toList
--   
--   >>> twos = Fold.many two Fold.toList
--   
--   >>> Stream.fold twos $ Stream.fromList [1..10]
--   [[1,2],[3,4],[5,6],[7,8],[9,10]]
--   
-- -- Stops when collect stops. -- -- See also: concatMap, foldMany many :: Monad m => Fold m a b -> Fold m b c -> Fold m a c -- | chunksOf n split collect repeatedly applies the -- split fold to chunks of n items in the input stream -- and supplies the result to the collect fold. -- --
--   >>> twos = Fold.chunksOf 2 Fold.toList Fold.toList
--   
--   >>> Stream.fold twos $ Stream.fromList [1..10]
--   [[1,2],[3,4],[5,6],[7,8],[9,10]]
--   
-- --
--   chunksOf n split = many (take n split)
--   
-- -- Stops when collect stops. chunksOf :: Monad m => Int -> Fold m a b -> Fold m b c -> Fold m a c -- | Map a Fold returning function on the result of a Fold -- and run the returned fold. This operation can be used to express data -- dependencies between fold operations. -- -- Let's say the first element in the stream is a count of the following -- elements that we have to add, then: -- --
--   >>> import Data.Maybe (fromJust)
--   
--   >>> count = fmap fromJust Fold.head
--   
--   >>> total n = Fold.take n Fold.sum
--   
--   >>> Stream.fold (Fold.concatMap total count) $ Stream.fromList [10,9..1]
--   45
--   
-- -- Time: O(n^2) where n is the number of compositions. -- -- See also: foldIterateM concatMap :: Monad m => (b -> Fold m a c) -> Fold m a b -> Fold m a c -- | Flatten the monadic output of a fold to pure output. -- | Deprecated: Use "rmapM id" instead sequence :: Monad m => Fold m a (m b) -> Fold m a b -- | Map a monadic function on the output of a fold. -- | Deprecated: Use rmapM instead mapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c module Streamly.Internal.Data.SVar.Worker decrementYieldLimit :: SVar t m a -> IO Bool incrementYieldLimit :: SVar t m a -> IO () decrementBufferLimit :: SVar t m a -> IO () incrementBufferLimit :: SVar t m a -> IO () resetBufferLimit :: SVar t m a -> IO () data Work BlockWait :: NanoSecond64 -> Work PartialWorker :: Count -> Work ManyWorkers :: Int -> Count -> Work isBeyondMaxRate :: SVar t m a -> YieldRateInfo -> IO Bool estimateWorkers :: Limit -> Count -> Count -> NanoSecond64 -> NanoSecond64 -> NanoSecond64 -> LatencyRange -> Work updateYieldCount :: WorkerInfo -> IO Count -- | This is a magic number and it is overloaded, and used at several -- places to achieve batching: -- --
    --
  1. If we have to sleep to slowdown this is the minimum period that we -- accumulate before we sleep. Also, workers do not stop until this much -- sleep time is accumulated.
  2. --
  3. Collected latencies are computed and transferred to measured -- latency after a minimum of this period.
  4. --
minThreadDelay :: NanoSecond64 workerRateControl :: SVar t m a -> YieldRateInfo -> WorkerInfo -> IO Bool workerUpdateLatency :: YieldRateInfo -> WorkerInfo -> IO () -- | This function is used by the producer threads to queue output for the -- consumer thread to consume. Returns whether the queue has more space. send :: SVar t m a -> ChildEvent a -> IO Int ringDoorBell :: SVar t m a -> IO () sendYield :: SVar t m a -> Maybe WorkerInfo -> ChildEvent a -> IO Bool sendToProducer :: SVar t m a -> ChildEvent a -> IO Int sendStop :: SVar t m a -> Maybe WorkerInfo -> IO () sendStopToProducer :: MonadIO m => SVar t m a -> m () handleChildException :: SVar t m a -> SomeException -> IO () handleFoldException :: SVar t m a -> SomeException -> IO () instance GHC.Show.Show Streamly.Internal.Data.SVar.Worker.Work module Streamly.Internal.Data.SVar.Dispatch collectLatency :: SVar t m a -> YieldRateInfo -> Bool -> IO (Count, AbsTime, NanoSecond64) withDiagMVar :: SVar t m a -> String -> IO () -> IO () dumpSVar :: SVar t m a -> IO String printSVar :: SVar t m a -> String -> IO () delThread :: MonadIO m => SVar t m a -> ThreadId -> m () modifyThread :: MonadIO m => SVar t m a -> ThreadId -> m () -- | This is safe even if we are adding more threads concurrently because -- if a child thread is adding another thread then anyway -- workerThreads will not be empty. allThreadsDone :: MonadIO m => SVar t m a -> m Bool recordMaxWorkers :: MonadIO m => SVar t m a -> m () pushWorker :: MonadAsync m => Count -> SVar t m a -> m () -- | In contrast to pushWorker which always happens only from the consumer -- thread, a pushWorkerPar can happen concurrently from multiple threads -- on the producer side. So we need to use a thread safe modification of -- workerThreads. Alternatively, we can use a CreateThread event to avoid -- using a CAS based modification. pushWorkerPar :: MonadAsync m => SVar t m a -> (Maybe WorkerInfo -> m ()) -> m () dispatchWorker :: MonadAsync m => Count -> SVar t m a -> m Bool dispatchWorkerPaced :: MonadAsync m => SVar t m a -> m Bool sendWorkerWait :: MonadAsync m => (SVar t m a -> IO ()) -> (SVar t m a -> m Bool) -> SVar t m a -> m () sendFirstWorker :: MonadAsync m => SVar t m a -> t m a -> m (SVar t m a) sendWorkerDelay :: SVar t m a -> IO () sendWorkerDelayPaced :: SVar t m a -> IO () module Streamly.Internal.Data.SVar.Pull readOutputQBasic :: IORef ([ChildEvent a], Int) -> IO ([ChildEvent a], Int) readOutputQRaw :: SVar t m a -> IO ([ChildEvent a], Int) readOutputQPaced :: MonadAsync m => SVar t m a -> m [ChildEvent a] readOutputQBounded :: MonadAsync m => SVar t m a -> m [ChildEvent a] postProcessPaced :: MonadAsync m => SVar t m a -> m Bool postProcessBounded :: MonadAsync m => SVar t m a -> m Bool cleanupSVar :: SVar t m a -> IO () cleanupSVarFromWorker :: SVar t m a -> IO () module Streamly.Internal.Data.SVar getYieldRateInfo :: State t m a -> IO (Maybe YieldRateInfo) newSVarStats :: IO SVarStats newParallelVar :: MonadAsync m => SVarStopStyle -> State t m a -> m (SVar t m a) enqueueAhead :: SVar t m a -> IORef ([t m a], Int) -> (RunInIO m, t m a) -> IO () reEnqueueAhead :: SVar t m a -> IORef ([t m a], Int) -> t m a -> IO () queueEmptyAhead :: MonadIO m => IORef ([t m a], Int) -> m Bool dequeueAhead :: MonadIO m => IORef ([t m a], Int) -> m (Maybe (t m a, Int)) data HeapDequeueResult t m a Clearing :: HeapDequeueResult t m a Waiting :: Int -> HeapDequeueResult t m a Ready :: Entry Int (AheadHeapEntry t m a) -> HeapDequeueResult t m a dequeueFromHeap :: IORef (Heap (Entry Int (AheadHeapEntry t m a)), Maybe Int) -> IO (HeapDequeueResult t m a) dequeueFromHeapSeq :: IORef (Heap (Entry Int (AheadHeapEntry t m a)), Maybe Int) -> Int -> IO (HeapDequeueResult t m a) requeueOnHeapTop :: IORef (Heap (Entry Int (AheadHeapEntry t m a)), Maybe Int) -> Entry Int (AheadHeapEntry t m a) -> Int -> IO () updateHeapSeq :: IORef (Heap (Entry Int (AheadHeapEntry t m a)), Maybe Int) -> Int -> IO () withIORef :: IORef a -> (a -> IO b) -> IO b heapIsSane :: Maybe Int -> Int -> Bool newAheadVar :: MonadAsync m => State t m a -> t m a -> (IORef ([t m a], Int) -> IORef (Heap (Entry Int (AheadHeapEntry t m a)), Maybe Int) -> State t m a -> SVar t m a -> Maybe WorkerInfo -> m ()) -> m (SVar t m a) module Streamly.Internal.Data.Unfold.SVar -- | Internal fromSVar :: MonadAsync m => Unfold m (SVar t m a) a -- | Internal fromProducer :: MonadAsync m => Unfold m (SVar t m a) a module Streamly.Internal.Data.Stream.SVar.Generate -- | Write a stream to an SVar in a non-blocking manner. The stream -- can then be read back from the SVar using fromSVar. toSVar :: MonadAsync m => SVar SerialT m a -> SerialT m a -> m () -- | Generate a stream from an SVar. An unevaluated stream can be pushed to -- an SVar using toSVar. As we pull a stream from the SVar the -- input stream gets evaluated concurrently. The evaluation depends on -- the SVar style and the configuration parameters e.g. using the -- maxBuffer/maxThreads combinators. fromSVar :: MonadAsync m => SVar Stream m a -> SerialT m a -- | Like fromSVar but generates a StreamD style stream instead of -- CPS. fromSVarD :: MonadAsync m => SVar t m a -> Stream m a -- | To run examples in this module: -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import Control.Concurrent (threadDelay)
--   
--   >>> :{
--    delay n = do
--        threadDelay (n * 1000000)   -- sleep for n seconds
--        putStrLn (show n ++ " sec") -- print "n sec"
--        return n                    -- IO Int
--   :}
--   
module Streamly.Internal.Data.Stream.Async -- | For AsyncT streams: -- --
--   (<>) = async
--   (>>=) = flip . concatMapWith async
--   
-- -- A single Monad bind behaves like a for loop with -- iterations of the loop executed concurrently a la the async -- combinator, producing results and side effects of iterations out of -- order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAsync $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, a la the async combinator: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAsync $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,4,5,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one output stream and all the iterations corresponding to 2 -- constitute another output stream and these two output streams are -- merged using async. -- -- Since: 0.1.0 (Streamly) newtype AsyncT m a AsyncT :: Stream m a -> AsyncT m a [getAsyncT] :: AsyncT m a -> Stream m a -- | A demand driven left biased parallely composing IO stream of elements -- of type a. See AsyncT documentation for more details. -- -- Since: 0.2.0 (Streamly) type Async = AsyncT IO -- | XXX we can implement it more efficienty by directly implementing -- instead of combining streams using async. consMAsync :: MonadAsync m => m a -> AsyncT m a -> AsyncT m a asyncK :: MonadAsync m => Stream m a -> Stream m a -> Stream m a -- | Generate a stream asynchronously to keep it buffered, lazily consume -- from the buffer. -- -- Pre-release mkAsyncK :: MonadAsync m => Stream m a -> Stream m a mkAsyncD :: MonadAsync m => Stream m a -> Stream m a -- | For WAsyncT streams: -- --
--   (<>) = wAsync
--   (>>=) = flip . concatMapWith wAsync
--   
-- -- A single Monad bind behaves like a for loop with -- iterations of the loop executed concurrently a la the wAsync -- combinator, producing results and side effects of iterations out of -- order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWAsync $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, a la the wAsync combinator: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWAsync $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,4,5,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one WAsyncT output stream and all the iterations corresponding -- to 2 constitute another WAsyncT output stream and -- these two output streams are merged using wAsync. -- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- AsyncT. -- -- Since: 0.2.0 (Streamly) newtype WAsyncT m a WAsyncT :: Stream m a -> WAsyncT m a [getWAsyncT] :: WAsyncT m a -> Stream m a -- | A round robin parallely composing IO stream of elements of type -- a. See WAsyncT documentation for more details. -- -- Since: 0.2.0 (Streamly) type WAsync = WAsyncT IO -- | XXX we can implement it more efficienty by directly implementing -- instead of combining streams using wAsync. consMWAsync :: MonadAsync m => m a -> WAsyncT m a -> WAsyncT m a wAsyncK :: MonadAsync m => Stream m a -> Stream m a -> Stream m a instance Control.Monad.Trans.Class.MonadTrans Streamly.Internal.Data.Stream.Async.AsyncT instance Control.Monad.Trans.Class.MonadTrans Streamly.Internal.Data.Stream.Async.WAsyncT instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Async.WAsyncT m a) instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Monoid (Streamly.Internal.Data.Stream.Async.WAsyncT m a) instance (GHC.Base.Monad m, Streamly.Internal.Control.Concurrent.MonadAsync m) => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Monad (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance (Control.Monad.Base.MonadBase b m, GHC.Base.Monad m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Base.MonadBase b (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance (Control.Monad.IO.Class.MonadIO m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance (Control.Monad.Catch.MonadThrow m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance (Control.Monad.Reader.Class.MonadReader r m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Reader.Class.MonadReader r (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance (Control.Monad.State.Class.MonadState s m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Async.AsyncT m a) instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Monoid (Streamly.Internal.Data.Stream.Async.AsyncT m a) instance (GHC.Base.Monad m, Streamly.Internal.Control.Concurrent.MonadAsync m) => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Async.AsyncT m) instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Monad (Streamly.Internal.Data.Stream.Async.AsyncT m) instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Stream.Async.AsyncT m) instance (Control.Monad.Base.MonadBase b m, GHC.Base.Monad m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Base.MonadBase b (Streamly.Internal.Data.Stream.Async.AsyncT m) instance (Control.Monad.IO.Class.MonadIO m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Stream.Async.AsyncT m) instance (Control.Monad.Catch.MonadThrow m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.Async.AsyncT m) instance (Control.Monad.Reader.Class.MonadReader r m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Reader.Class.MonadReader r (Streamly.Internal.Data.Stream.Async.AsyncT m) instance (Control.Monad.State.Class.MonadState s m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Stream.Async.AsyncT m) -- | To run examples in this module: -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import Control.Concurrent (threadDelay)
--   
--   >>> :{
--    delay n = do
--        threadDelay (n * 1000000)   -- sleep for n seconds
--        putStrLn (show n ++ " sec") -- print "n sec"
--        return n                    -- IO Int
--   :}
--   
module Streamly.Internal.Data.Stream.Ahead -- | For AheadT streams: -- --
--   (<>) = ahead
--   (>>=) = flip . concatMapWith ahead
--   
-- -- A single Monad bind behaves like a for loop with -- iterations executed concurrently, ahead of time, producing side -- effects of iterations out of order, but results in order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAhead $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [2,1]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, ahead of time: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAhead $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,5,4,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one output stream and all the iterations corresponding to 2 -- constitute another output stream and these two output streams are -- merged using ahead. -- -- Since: 0.3.0 (Streamly) newtype AheadT m a AheadT :: Stream m a -> AheadT m a [getAheadT] :: AheadT m a -> Stream m a -- | A serial IO stream of elements of type a with concurrent -- lookahead. See AheadT documentation for more details. -- -- Since: 0.3.0 (Streamly) type Ahead = AheadT IO aheadK :: MonadAsync m => Stream m a -> Stream m a -> Stream m a -- | XXX we can implement it more efficienty by directly implementing -- instead of combining streams using ahead. consM :: MonadAsync m => m a -> AheadT m a -> AheadT m a instance Control.Monad.Trans.Class.MonadTrans Streamly.Internal.Data.Stream.Ahead.AheadT instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Ahead.AheadT m a) instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Monoid (Streamly.Internal.Data.Stream.Ahead.AheadT m a) instance (GHC.Base.Monad m, Streamly.Internal.Control.Concurrent.MonadAsync m) => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Monad (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance (Control.Monad.Base.MonadBase b m, GHC.Base.Monad m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Base.MonadBase b (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance (Control.Monad.IO.Class.MonadIO m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance (Control.Monad.Catch.MonadThrow m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance (Control.Monad.Reader.Class.MonadReader r m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Reader.Class.MonadReader r (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance (Control.Monad.State.Class.MonadState s m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Stream.Ahead.AheadT m) module Streamly.Internal.Data.Fold.SVar -- | A fold to write a stream to an SVar. Unlike toSVar this does -- not allow for concurrent evaluation of the stream, as the fold -- receives the input one element at a time, it just forwards the -- elements to the SVar. However, we can safely execute the fold in an -- independent thread, the SVar can act as a buffer decoupling the sender -- from the receiver. Also, we can have multiple folds running -- concurrently pusing the streams to the SVar. write :: MonadIO m => SVar t m a -> Maybe WorkerInfo -> Fold m a () -- | Like write, but applies a yield limit. writeLimited :: MonadIO m => SVar t m a -> Maybe WorkerInfo -> Fold m a () -- | Eliminate a stream by distributing it to multiple SVars concurrently. module Streamly.Internal.Data.Stream.SVar.Eliminate -- | Fold the supplied stream to the SVar asynchronously using Parallel -- concurrency style. {--} toSVarParallel :: MonadAsync m => State t m a -> SVar t m a -> Stream m a -> m () -- | Create a Fold style SVar that runs a supplied fold function as the -- consumer. Any elements sent to the SVar are consumed by the supplied -- fold function. newFoldSVar :: MonadAsync m => State Stream m a -> (SerialT m a -> m b) -> m (SVar Stream m a) -- | Like newFoldSVar except that it uses a Fold instead of a -- fold function. newFoldSVarF :: MonadAsync m => State t m a -> Fold m a b -> m (SVar t m a) -- | Poll for events sent by the fold consumer to the stream pusher. The -- fold consumer can send a Stop event or an exception. When a -- Stop is received this function returns True. If an -- exception is recieved then it throws the exception. fromConsumer :: MonadAsync m => SVar Stream m a -> m Bool -- | Push values from a stream to a fold worker via an SVar. Before pushing -- a value to the SVar it polls for events received from the fold -- consumer. If a stop event is received then it returns True -- otherwise false. Propagates exceptions received from the fold -- consumer. pushToFold :: MonadAsync m => SVar Stream m a -> a -> m Bool -- | Tap a stream and send the elements to the specified SVar in addition -- to yielding them again. The SVar runs a fold consumer. Elements are -- tapped and sent to the SVar until the fold finishes. Any exceptions -- from the fold evaluation are propagated in the current thread. -- --
--   ------input stream---------output stream----->
--                      /|\   |
--           exceptions  |    |  input
--                       |   \|/
--                       ----SVar
--                            |
--                           Fold
--   
teeToSVar :: MonadAsync m => SVar Stream m a -> SerialT m a -> SerialT m a -- | To run examples in this module: -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import Control.Concurrent (threadDelay)
--   
--   >>> :{
--    delay n = do
--        threadDelay (n * 1000000)   -- sleep for n seconds
--        putStrLn (show n ++ " sec") -- print "n sec"
--        return n                    -- IO Int
--   :}
--   
module Streamly.Internal.Data.Stream.Parallel -- | For ParallelT streams: -- --
--   (<>) = parallel
--   (>>=) = flip . concatMapWith parallel
--   
-- -- See AsyncT, ParallelT is similar except that all -- iterations are strictly concurrent while in AsyncT it depends -- on the consumer demand and available threads. See parallel -- for more details. -- -- Since: 0.1.0 (Streamly) -- -- Since: 0.7.0 (maxBuffer applies to ParallelT streams) newtype ParallelT m a ParallelT :: Stream m a -> ParallelT m a [getParallelT] :: ParallelT m a -> Stream m a -- | A parallely composing IO stream of elements of type a. See -- ParallelT documentation for more details. -- -- Since: 0.2.0 (Streamly) type Parallel = ParallelT IO -- | XXX we can implement it more efficienty by directly implementing -- instead of combining streams using parallel. consM :: MonadAsync m => m a -> ParallelT m a -> ParallelT m a parallelK :: MonadAsync m => Stream m a -> Stream m a -> Stream m a -- | Like parallel but stops the output as soon as the first -- stream stops. -- -- Pre-release parallelFstK :: MonadAsync m => Stream m a -> Stream m a -> Stream m a -- | Like parallel but stops the output as soon as any of the two -- streams stops. -- -- Pre-release parallelMinK :: MonadAsync m => Stream m a -> Stream m a -> Stream m a -- | Same as mkParallel but for StreamD stream. mkParallelD :: MonadAsync m => Stream m a -> Stream m a -- | Like mkParallel but uses StreamK internally. -- -- Pre-release mkParallelK :: MonadAsync m => Stream m a -> Stream m a -- | Redirect a copy of the stream to a supplied fold and run it -- concurrently in an independent thread. The fold may buffer some -- elements. The buffer size is determined by the prevailing -- maxBuffer setting. -- --
--                 Stream m a -> m b
--                         |
--   -----stream m a ---------------stream m a-----
--   
-- --
--   > S.drain $ S.tapAsync (S.mapM_ print) (S.enumerateFromTo 1 2)
--   1
--   2
--   
-- -- Exceptions from the concurrently running fold are propagated to the -- current computation. Note that, because of buffering in the fold, -- exceptions may be delayed and may not correspond to the current -- element being processed in the parent stream, but we guarantee that -- before the parent stream stops the tap finishes and all exceptions -- from it are drained. -- -- Compare with tap. -- -- Pre-release tapAsyncK :: MonadAsync m => (Stream m a -> m b) -> Stream m a -> Stream m a -- | Like tapAsync but uses a Fold instead of a fold -- function. tapAsyncF :: MonadAsync m => Fold m a b -> Stream m a -> Stream m a -- | Generates a callback and a stream pair. The callback returned is used -- to queue values to the stream. The stream is infinite, there is no way -- for the callback to indicate that it is done now. -- -- Pre-release newCallbackStream :: MonadAsync m => m (a -> m (), Stream m a) instance Control.Monad.Trans.Class.MonadTrans Streamly.Internal.Data.Stream.Parallel.ParallelT instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Parallel.ParallelT m a) instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Monoid (Streamly.Internal.Data.Stream.Parallel.ParallelT m a) instance (GHC.Base.Monad m, Streamly.Internal.Control.Concurrent.MonadAsync m) => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Monad (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance (Control.Monad.Base.MonadBase b m, GHC.Base.Monad m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Base.MonadBase b (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance (Control.Monad.IO.Class.MonadIO m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance (Control.Monad.Catch.MonadThrow m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance (Control.Monad.Reader.Class.MonadReader r m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.Reader.Class.MonadReader r (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance (Control.Monad.State.Class.MonadState s m, Streamly.Internal.Control.Concurrent.MonadAsync m) => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Stream.Parallel.ParallelT m) -- | Streamly.Internal.Data.Pipe might ultimately replace this -- module. module Streamly.Internal.Data.Stream.StreamD.Transform transform :: Monad m => Pipe m a b -> Stream m a -> Stream m b map :: Monad m => (a -> b) -> Stream m a -> Stream m b -- | Map a monadic function over a Stream mapM :: Monad m => (a -> m b) -> Stream m a -> Stream m b sequence :: Monad m => Stream m (m a) -> Stream m a tap :: Monad m => Fold m a b -> Stream m a -> Stream m a tapOffsetEvery :: Monad m => Int -> Int -> Fold m a b -> Stream m a -> Stream m a tapRate :: (MonadAsync m, MonadCatch m) => Double -> (Int -> m b) -> Stream m a -> Stream m a pollCounts :: MonadAsync m => (a -> Bool) -> (Stream m Int -> Stream m Int) -> Fold m Int b -> Stream m a -> Stream m a foldrS :: Monad m => (a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b foldrT :: (Monad m, Monad (t m), MonadTrans t) => (a -> t m b -> t m b) -> t m b -> Stream m a -> t m b foldlS :: Monad m => (Stream m b -> a -> Stream m b) -> Stream m b -> Stream m a -> Stream m b foldlT :: (Monad m, Monad (s m), MonadTrans s) => (s m b -> a -> s m b) -> s m b -> Stream m a -> s m b postscanOnce :: Monad m => Fold m a b -> Stream m a -> Stream m b scanOnce :: Monad m => Fold m a b -> Stream m a -> Stream m b scanlM' :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> Stream m b scanlMAfter' :: Monad m => (b -> a -> m b) -> m b -> (b -> m b) -> Stream m a -> Stream m b scanl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> Stream m b scanlM :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> Stream m b scanl :: Monad m => (b -> a -> b) -> b -> Stream m a -> Stream m b scanl1M' :: Monad m => (a -> a -> m a) -> Stream m a -> Stream m a scanl1' :: Monad m => (a -> a -> a) -> Stream m a -> Stream m a scanl1M :: Monad m => (a -> a -> m a) -> Stream m a -> Stream m a scanl1 :: Monad m => (a -> a -> a) -> Stream m a -> Stream m a prescanl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> Stream m b prescanlM' :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> Stream m b postscanl :: Monad m => (a -> b -> a) -> a -> Stream m b -> Stream m a postscanlM :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> Stream m b postscanl' :: Monad m => (a -> b -> a) -> a -> Stream m b -> Stream m a postscanlM' :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> Stream m b postscanlMAfter' :: Monad m => (b -> a -> m b) -> m b -> (b -> m b) -> Stream m a -> Stream m b postscanlx' :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream m a -> Stream m b postscanlMx' :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream m a -> Stream m b scanlMx' :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream m a -> Stream m b scanlx' :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream m a -> Stream m b filter :: Monad m => (a -> Bool) -> Stream m a -> Stream m a filterM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m a deleteBy :: Monad m => (a -> a -> Bool) -> a -> Stream m a -> Stream m a uniq :: (Eq a, Monad m) => Stream m a -> Stream m a take :: Applicative m => Int -> Stream m a -> Stream m a takeByTime :: (MonadIO m, TimeUnit64 t) => t -> Stream m a -> Stream m a takeWhile :: Monad m => (a -> Bool) -> Stream m a -> Stream m a takeWhileM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m a drop :: Monad m => Int -> Stream m a -> Stream m a dropByTime :: (MonadIO m, TimeUnit64 t) => t -> Stream m a -> Stream m a dropWhile :: Monad m => (a -> Bool) -> Stream m a -> Stream m a dropWhileM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m a insertBy :: Monad m => (a -> a -> Ordering) -> a -> Stream m a -> Stream m a intersperse :: Monad m => a -> Stream m a -> Stream m a intersperseM :: Monad m => m a -> Stream m a -> Stream m a intersperseSuffix :: forall m a. Monad m => m a -> Stream m a -> Stream m a -- | intersperse after every n items intersperseSuffixBySpan :: forall m a. Monad m => Int -> m a -> Stream m a -> Stream m a intersperseM_ :: Monad m => m b -> Stream m a -> Stream m a intersperseSuffix_ :: Monad m => m b -> Stream m a -> Stream m a reverse :: Monad m => Stream m a -> Stream m a indexed :: Monad m => Stream m a -> Stream m (Int, a) indexedR :: Monad m => Int -> Stream m a -> Stream m (Int, a) findIndices :: Monad m => (a -> Bool) -> Stream m a -> Stream m Int slicesBy :: Monad m => (a -> Bool) -> Stream m a -> Stream m (Int, Int) rollingMap :: Monad m => (a -> a -> b) -> Stream m a -> Stream m b rollingMapM :: Monad m => (a -> a -> m b) -> Stream m a -> Stream m b mapMaybe :: Monad m => (a -> Maybe b) -> Stream m a -> Stream m b mapMaybeM :: Monad m => (a -> m (Maybe b)) -> Stream m a -> Stream m b -- | A Producer is an Unfold with an extract -- function added to extract the state. It is more powerful but less -- general than an Unfold. -- -- A Producer represents steps of a loop generating a sequence of -- elements. While unfolds are closed representation of imperative loops -- with some opaque internal state, producers are open loops with the -- state being accessible to the user. -- -- Unlike an unfold, which runs a loop till completion, a producer can be -- stopped in the middle, its state can be extracted, examined, changed, -- and then it can be resumed later from the stopped state. -- -- A producer can be used in places where a CPS stream would otherwise be -- needed, because the state of the loop can be passed around. However, -- it can be much more efficient than CPS because it allows stream fusion -- and unecessary function calls can be avoided. module Streamly.Internal.Data.Producer -- | A Producer m a b is a generator of a stream of values of type -- b from a seed of type a in Monad m. -- -- Pre-release data Producer m a b -- |
--   Producer step inject extract
--   
Producer :: (s -> m (Step s b)) -> (a -> m s) -> (s -> m a) -> Producer m a b -- | Simplify a producer to an unfold. -- -- Pre-release simplify :: Producer m a b -> Unfold m a b nil :: Monad m => Producer m a b nilM :: Monad m => (a -> m c) -> Producer m a b unfoldrM :: Monad m => (a -> m (Maybe (b, a))) -> Producer m a b -- | Convert a StreamD stream into a producer. -- -- Pre-release fromStreamD :: Monad m => Producer m (Stream m a) a -- | Convert a list of pure values to a Stream -- -- Pre-release fromList :: Monad m => Producer m [a] a -- | State representing a nested loop. data NestedLoop s1 s2 OuterLoop :: s1 -> NestedLoop s1 s2 InnerLoop :: s1 -> s2 -> NestedLoop s1 s2 -- | Apply the second unfold to each output element of the first unfold and -- flatten the output in a single stream. -- -- Pre-release concat :: Monad m => Producer m a b -> Producer m b c -> Producer m (NestedLoop a b) c module Streamly.Internal.Foreign.Malloc mallocForeignPtrAlignedBytes :: Int -> Int -> IO (ForeignPtr a) mallocForeignPtrAlignedUnmanagedBytes :: Int -> Int -> IO (ForeignPtr a) module Streamly.Internal.System.IO -- | Default maximum buffer size in bytes, for reading from and writing to -- IO devices, the value is 32KB minus GHC allocation overhead, which is -- a few bytes, so that the actual allocation is 32KB. defaultChunkSize :: Int -- | When we allocate a byte array of size k the allocator -- actually allocates memory of size k + byteArrayOverhead. -- arrayPayloadSize n returns the size of the array in bytes -- that would result in an allocation of n bytes. arrayPayloadSize :: Int -> Int unsafeInlineIO :: IO a -> a -- | Mutable arrays and file system files are quite similar, they can grow -- and their content is mutable. Therefore, both have similar APIs as -- well. We strive to keep the API consistent for both. Ideally, you -- should be able to replace one with another with little changes to the -- code. module Streamly.Internal.Data.Array.Foreign.Mut.Type -- | An unboxed, pinned mutable array. An array is created with a given -- length and capacity. Length is the number of valid elements in the -- array. Capacity is the maximum number of elements that the array can -- be expanded to without having to reallocate the memory. -- -- The elements in the array can be mutated in-place without changing the -- reference (constructor). However, the length of the array cannot be -- mutated in-place. A new array reference is generated when the length -- changes. When the length is increased (upto the maximum reserved -- capacity of the array), the array is not reallocated and the new -- reference uses the same underlying memory as the old one. -- -- Several routines in this module allow the programmer to control the -- capacity of the array. The programmer can control the trade-off -- between memory usage and performance impact due to reallocations when -- growing or shrinking the array. data Array a Array :: {-# UNPACK #-} !ArrayContents -> {-# UNPACK #-} !Ptr a -> {-# UNPACK #-} !Ptr a -> {-# UNPACK #-} !Ptr a -> Array a [arrContents] :: Array a -> {-# UNPACK #-} !ArrayContents -- | first address [arrStart] :: Array a -> {-# UNPACK #-} !Ptr a -- | first unused address [aEnd] :: Array a -> {-# UNPACK #-} !Ptr a -- | first address beyond allocated memory [aBound] :: Array a -> {-# UNPACK #-} !Ptr a data ArrayContents arrayToFptrContents :: ArrayContents -> ForeignPtrContents fptrToArrayContents :: ForeignPtrContents -> ArrayContents -- | Similar to unsafeWithForeignPtr. unsafeWithArrayContents :: MonadIO m => ArrayContents -> Ptr a -> (Ptr a -> m b) -> m b nilArrayContents :: ArrayContents touch :: ArrayContents -> IO () -- | Allocates an empty array that can hold count items. The -- memory of the array is uninitialized and the allocation is aligned as -- per the Storable instance of the type. -- -- Pre-release newArray :: forall m a. (MonadIO m, Storable a) => Int -> m (Array a) -- | Like newArrayWith but using an allocator that aligns the memory -- to the alignment dictated by the Storable instance of the type. -- -- Internal newArrayAligned :: (MonadIO m, Storable a) => Int -> Int -> m (Array a) -- | Like newArrayWith but using an allocator that allocates -- unmanaged pinned memory. The memory will never be freed by GHC. This -- could be useful in allocate-once global data structures. Use carefully -- as incorrect use can lead to memory leak. -- -- Internal newArrayAlignedUnmanaged :: forall m a. (MonadIO m, Storable a) => Int -> Int -> m (Array a) -- | newArrayWith allocator alignment count allocates a new array -- of zero length and with a capacity to hold count elements, -- using allocator size alignment as the memory allocator -- function. -- -- Alignment must be greater than or equal to machine word size and a -- power of 2. -- -- Pre-release newArrayWith :: forall m a. (MonadIO m, Storable a) => (Int -> Int -> m (ArrayContents, Ptr a)) -> Int -> Int -> m (Array a) -- | Allocate an Array of the given size and run an IO action passing the -- array start pointer. -- -- Internal withNewArrayUnsafe :: (MonadIO m, Storable a) => Int -> (Ptr a -> m ()) -> m (Array a) data ArrayUnsafe a ArrayUnsafe :: {-# UNPACK #-} !ArrayContents -> {-# UNPACK #-} !Ptr a -> {-# UNPACK #-} !Ptr a -> ArrayUnsafe a -- | Like writeNUnsafe but takes a new array allocator alloc -- size function as argument. -- --
--   >>> writeNWithUnsafe alloc n = Array.appendNUnsafe (alloc n) n
--   
-- -- Pre-release writeNWithUnsafe :: forall m a. (MonadIO m, Storable a) => (Int -> m (Array a)) -> Int -> Fold m a (Array a) -- | writeNWith alloc n folds a maximum of n elements -- into an array allocated using the alloc function. -- --
--   >>> writeNWith alloc n = Fold.take n (Array.writeNWithUnsafe alloc n)
--   
--   >>> writeNWith alloc n = Array.appendN (alloc n) n
--   
writeNWith :: forall m a. (MonadIO m, Storable a) => (Int -> m (Array a)) -> Int -> Fold m a (Array a) -- | Like writeN but does not check the array bounds when writing. -- The fold driver must not call the step function more than n -- times otherwise it will corrupt the memory and crash. This function -- exists mainly because any conditional in the step function blocks -- fusion causing 10x performance slowdown. -- --
--   >>> writeNUnsafe = Array.writeNWithUnsafe Array.newArray
--   
writeNUnsafe :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- --
--   >>> writeN = Array.writeNWith Array.newArray
--   
--   >>> writeN n = Fold.take n (Array.writeNUnsafe n)
--   
--   >>> writeN n = Array.appendN (Array.newArray n) n
--   
writeN :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) -- | writeNAligned align n folds a maximum of n elements -- from the input stream to an Array aligned to the given size. -- --
--   >>> writeNAligned align = Array.writeNWith (Array.newArrayAligned align)
--   
--   >>> writeNAligned align n = Array.appendN (Array.newArrayAligned align n) n
--   
-- -- Pre-release writeNAligned :: forall m a. (MonadIO m, Storable a) => Int -> Int -> Fold m a (Array a) -- | writeNAlignedUnmanaged align n folds a maximum of n -- elements from the input stream to an Array whose starting -- address is aligned to align bytes and is allocated using -- unmanaged memory (never freed). This could be useful to allocate -- memory that we need to allocate only once in the lifetime of the -- program. -- --
--   >>> f = Array.newArrayAlignedUnmanaged
--   
--   >>> writeNAlignedUnmanaged a = Array.writeNWith (f a)
--   
--   >>> writeNAlignedUnmanaged a n = Array.appendN (f a n) n
--   
-- -- Pre-release writeNAlignedUnmanaged :: forall m a. (MonadIO m, Storable a) => Int -> Int -> Fold m a (Array a) -- | writeWith minCount folds the whole input to a single array. -- The array starts at a size big enough to hold minCount elements, the -- size is doubled every time the array needs to be grown. -- -- Caution! Do not use this on infinite streams. -- --
--   >>> f n = Array.appendWith (* 2) (Array.newArray n)
--   
--   >>> writeWith n = Fold.rmapM Array.rightSize (f n)
--   
--   >>> writeWith n = Fold.rmapM Array.fromArrayStreamK (Array.writeChunks n)
--   
-- -- Pre-release writeWith :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Same as writeWith using an initial array size of -- arrayChunkBytes bytes rounded up to the element size. -- -- Caution! Do not use this on infinite streams. write :: forall m a. (MonadIO m, Storable a) => Fold m a (Array a) -- | fromForeignPtrUnsafe foreignPtr end bound creates an -- Array that starts at the memory pointed by the -- foreignPtr, end is the first unused address, and -- bound is the first address beyond the allocated memory. -- -- Unsafe: Make sure that foreignPtr <= end <= bound and (end - -- start) is an integral multiple of the element size. Only PlainPtr type -- ForeignPtr is supported. -- -- Pre-release fromForeignPtrUnsafe :: ForeignPtr a -> Ptr a -> Ptr a -> Array a -- | Create an Array from the first N elements of a list. The array -- is allocated to size N, if the list terminates before N elements then -- the array may hold less than N elements. fromListN :: (MonadIO m, Storable a) => Int -> [a] -> m (Array a) -- | Create an Array from a list. The list must be of finite size. fromList :: (MonadIO m, Storable a) => [a] -> m (Array a) -- | Use the writeN fold instead. -- --
--   >>> fromStreamDN n = StreamD.fold (Array.writeN n)
--   
fromStreamDN :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> m (Array a) -- | We could take the approach of doubling the memory allocation on each -- overflow. This would result in more or less the same amount of copying -- as in the chunking approach. However, if we have to shrink in the end -- then it may result in an extra copy of the entire data. -- --
--   >>> fromStreamD = StreamD.fold Array.write
--   
fromStreamD :: (MonadIO m, Storable a) => Stream m a -> m (Array a) -- | O(1) Write the given element at the given index in the array. -- Performs in-place mutation of the array. -- --
--   >>> putIndex arr ix val = Array.modifyIndex arr ix (const (val, ()))
--   
--   >>> f = Array.putIndices
--   
--   >>> putIndex arr ix val = Stream.fold (f arr) (Stream.fromPure (ix, val))
--   
-- -- Pre-release putIndex :: (MonadIO m, Storable a) => Array a -> Int -> a -> m () -- | Write the given element to the given index of the array. Does not -- check if the index is out of bounds of the array. -- -- Pre-release putIndexUnsafe :: forall m a. (MonadIO m, Storable a) => Array a -> Int -> a -> m () -- | Write an input stream of (index, value) pairs to an array. Throws an -- error if any index is out of bounds. -- -- Unimplemented putIndices :: Array a -> Fold m (Int, a) () -- | Modify a given index of an array using a modifier function. -- -- Pre-release modifyIndexUnsafe :: forall m a b. (MonadIO m, Storable a) => Array a -> Int -> (a -> (a, b)) -> m b -- | Modify a given index of an array using a modifier function. -- -- Pre-release modifyIndex :: forall m a b. (MonadIO m, Storable a) => Array a -> Int -> (a -> (a, b)) -> m b -- | Modify the array indices generated by the supplied unfold. -- -- Pre-release modifyIndices :: Unfold m (Array a) Int -> Array a -> (a -> a) -> m () -- | Modify each element of an array using the supplied modifier function. -- -- Unimplemented modify :: Array a -> (a -> a) -> m () -- | Swap the elements at two indices. -- -- Pre-release swapIndices :: Array a -> Int -> Int -> m () -- | snocWith sizer arr elem mutates arr to append -- elem. The length of the array increases by 1. -- -- If there is no reserved space available in arr it is -- reallocated to a size in bytes determined by the sizer -- oldSizeBytes function, where oldSizeBytes is the -- original size of the array in bytes. -- -- If the new array size is more than largeObjectThreshold we -- automatically round it up to blockSize. -- -- Note that the returned array may be a mutated version of the original -- array. -- -- Pre-release snocWith :: forall m a. (MonadIO m, Storable a) => (Int -> Int) -> Array a -> a -> m (Array a) -- | The array is mutated to append an additional element to it. If there -- is no reserved space available in the array then it is reallocated to -- double the original size. -- -- This is useful to reduce allocations when appending unknown number of -- elements. -- -- Note that the returned array may be a mutated version of the original -- array. -- --
--   >>> snoc = Array.snocWith (* 2)
--   
-- -- Performs O(n * log n) copies to grow, but is liberal with memory -- allocation. -- -- Pre-release snoc :: forall m a. (MonadIO m, Storable a) => Array a -> a -> m (Array a) -- | The array is mutated to append an additional element to it. If there -- is no reserved space available in the array then it is reallocated to -- grow it by arrayChunkBytes rounded up to blockSize when -- the size becomes more than largeObjectThreshold. -- -- Note that the returned array may be a mutated version of the original -- array. -- -- Performs O(n^2) copies to grow but is thrifty on memory. -- -- Pre-release snocLinear :: forall m a. (MonadIO m, Storable a) => Array a -> a -> m (Array a) -- | Like snoc but does not reallocate when pre-allocated array -- capacity becomes full. -- -- Internal snocMay :: forall m a. (MonadIO m, Storable a) => Array a -> a -> m (Maybe (Array a)) -- | Really really unsafe, appends the element into the first array, may -- cause silent data corruption or if you are lucky a segfault if the -- first array does not have enough space to append the element. -- -- Internal snocUnsafe :: forall m a. (MonadIO m, Storable a) => Array a -> a -> m (Array a) -- | Append up to n input items to the supplied array. -- -- Unsafe: Do not drive the fold beyond n elements, it will lead -- to memory corruption or segfault. -- -- Any free space left in the array after appending n elements -- is lost. -- -- Internal appendNUnsafe :: forall m a. (MonadIO m, Storable a) => m (Array a) -> Int -> Fold m a (Array a) -- | Append n elements to an existing array. Any free space left -- in the array after appending n elements is lost. -- --
--   >>> appendN initial n = Fold.take n (Array.appendNUnsafe initial n)
--   
-- -- Pre-release appendN :: forall m a. (MonadIO m, Storable a) => m (Array a) -> Int -> Fold m a (Array a) -- | appendWith realloc action mutates the array generated by -- action to append the input stream. If there is no reserved -- space available in the array it is reallocated to a size in bytes -- determined by realloc oldSize, where oldSize is the -- current size of the array in bytes. -- -- Note that the returned array may be a mutated version of original -- array. -- --
--   >>> appendWith sizer = Fold.foldlM' (Array.snocWith sizer)
--   
-- -- Pre-release appendWith :: forall m a. (MonadIO m, Storable a) => (Int -> Int) -> m (Array a) -> Fold m a (Array a) -- | append action mutates the array generated by action -- to append the input stream. If there is no reserved space available in -- the array it is reallocated to double the size. -- -- Note that the returned array may be a mutated version of original -- array. -- --
--   >>> append = Array.appendWith (* 2)
--   
-- -- Pre-release append :: forall m a. (MonadIO m, Storable a) => m (Array a) -> Fold m a (Array a) -- | Drop the last n elements of the array to reduce the length by n. The -- capacity is reallocated using the user supplied function. -- -- Unimplemented truncateWith :: Int -> (Int -> Int) -> Array a -> m (Array a) -- | Drop the last n elements of the array to reduce the length by n. -- -- The capacity is rounded to 1K or 4K if the length is more than the GHC -- large block threshold. -- -- Unimplemented truncate :: Int -> Array a -> m (Array a) -- | Like truncate but the capacity is rounded to the closest power -- of 2. -- -- Unimplemented truncateExp :: Int -> Array a -> m (Array a) data ReadUState a ReadUState :: {-# UNPACK #-} !ArrayContents -> !Ptr a -> !Ptr a -> ReadUState a -- | Unfold an array into a stream. read :: forall m a. (MonadIO m, Storable a) => Unfold m (Array a) a -- | Unfold an array into a stream in reverse order. -- -- Pre-release readRev :: forall m a. (MonadIO m, Storable a) => Unfold m (Array a) a -- | Use the read unfold instead. -- --
--   toStreamD = D.unfold read
--   
-- -- We can try this if the unfold has any performance issues. toStreamD :: forall m a. (MonadIO m, Storable a) => Array a -> Stream m a -- | Use the readRev unfold instead. -- --
--   toStreamDRev = D.unfold readRev
--   
-- -- We can try this if the unfold has any perf issues. toStreamDRev :: forall m a. (MonadIO m, Storable a) => Array a -> Stream m a toStreamK :: forall m a. (MonadIO m, Storable a) => Array a -> Stream m a toStreamKRev :: forall m a. (MonadIO m, Storable a) => Array a -> Stream m a -- | Convert an Array into a list. toList :: forall m a. (MonadIO m, Storable a) => Array a -> m [a] -- | Resumable unfold of an array. producer :: forall m a. (MonadIO m, Storable a) => Producer m (Array a) a -- | O(1) Lookup the element at the given index. Index starts from -- 0. getIndex :: (MonadIO m, Storable a) => Array a -> Int -> m a -- | Return the element at the specified index without checking the bounds. -- -- Unsafe because it does not check the bounds of the array. getIndexUnsafe :: forall m a. (MonadIO m, Storable a) => Array a -> Int -> m a -- | Given an unfold that generates array indices, read the elements on -- those indices from the supplied Array. An error is thrown if an index -- is out of bounds. -- -- Pre-release getIndices :: (MonadIO m, Storable a) => Unfold m (Array a) Int -> Unfold m (Array a) a -- | O(1) Lookup the element at the given index from the end of the -- array. Index starts from 0. -- -- Slightly faster than computing the forward index and using getIndex. getIndexRev :: (MonadIO m, Storable a) => Array a -> Int -> m a -- | The page or block size used by the GHC allocator. Allocator allocates -- at least a block and then allocates smaller allocations from within a -- block. blockSize :: Int -- | The default chunk size by which the array creation routines increase -- the size of the array when the array is grown linearly. arrayChunkBytes :: Int -- | Given a Storable type (unused first arg) and real allocation -- size (including overhead), return how many elements of that type will -- completely fit in it, returns at least 1. allocBytesToElemCount :: Storable a => a -> Int -> Int realloc :: forall m a. (MonadIO m, Storable a) => Int -> Array a -> m (Array a) -- | Change the reserved memory of the array so that it is enough to hold -- the specified number of elements. Nothing is done if the specified -- capacity is less than the length of the array. -- -- If the capacity is more than largeObjectThreshold then it is -- rounded up to the block size (4K). -- -- Unimplemented resize :: Int -> Array a -> m (Array a) -- | Like resize but if the capacity is more than -- largeObjectThreshold then it is rounded up to the closest power -- of 2. -- -- Unimplemented resizeExp :: Int -> Array a -> m (Array a) -- | Resize the allocated memory to drop any reserved free space at the end -- of the array and reallocate it to reduce wastage. -- -- Up to 25% wastage is allowed to avoid reallocations. If the capacity -- is more than largeObjectThreshold then free space up to the -- blockSize is retained. -- -- Pre-release rightSize :: forall m a. (MonadIO m, Storable a) => Array a -> m (Array a) -- | O(1) Get the length of the array i.e. the number of elements in -- the array. -- -- Note that byteLength is less expensive than this operation, as -- length involves a costly division operation. length :: forall a. Storable a => Array a -> Int -- | O(1) Get the byte length of the array. byteLength :: Array a -> Int -- | Get the total capacity of an array. An array may have space reserved -- beyond the current used length of the array. -- -- Pre-release byteCapacity :: Array a -> Int -- | The remaining capacity in the array for appending more elements -- without reallocation. -- -- Pre-release bytesFree :: Array a -> Int -- | You may not need to reverse an array because you can consume it in -- reverse using readRev. To reverse large arrays you can read in -- reverse and write to another array. However, in-place reverse can be -- useful to take adavantage of cache locality and when you do not want -- to allocate additional memory. -- -- Unimplemented reverse :: Array a -> m Bool -- | Generate the next permutation of the sequence, returns False if this -- is the last permutation. -- -- Unimplemented permute :: Array a -> m Bool -- | Partition an array into two halves using a partitioning predicate. The -- first half retains values where the predicate is False and the -- second half retains values where the predicate is True. -- -- Unimplemented partitionBy :: (a -> Bool) -> Array a -> m (Array a, Array a) -- | Shuffle corresponding elements from two arrays using a shuffle -- function. If the shuffle function returns False then do nothing -- otherwise swap the elements. This can be used in a bottom up fold to -- shuffle or reorder the elements. -- -- Unimplemented shuffleBy :: (a -> a -> m Bool) -> Array a -> Array a -> m (Array a) -- | divideBy level partition array performs a top down -- hierarchical recursive partitioning fold of items in the container -- using the given function as the partition function. Level indicates -- the level in the tree where the fold would stop. -- -- This performs a quick sort if the partition function is 'partitionBy -- (< pivot)'. -- -- Unimplemented divideBy :: Int -> (Array a -> Array a -> m (Array a)) -> Array a -> m (Array a) -- | mergeBy level merge array performs a pairwise bottom up fold -- recursively merging the pairs using the supplied merge function. Level -- indicates the level in the tree where the fold would stop. -- -- This performs a random shuffle if the shuffle function is random. If -- we stop at level 0 and repeatedly apply the function then we can do a -- bubble sort. -- -- Unimplemented mergeBy :: Int -> (Array a -> Array a -> m (Array a)) -> Array a -> m (Array a) -- | Cast an array having elements of type a into an array having -- elements of type b. The length of the array should be a -- multiple of the size of the target element otherwise Nothing is -- returned. -- -- Pre-release cast :: forall a b. Storable b => Array a -> Maybe (Array b) -- | Cast an array having elements of type a into an array having -- elements of type b. The array size must be a multiple of the -- size of type b otherwise accessing the last element of the -- array may result into a crash or a random value. -- -- Pre-release castUnsafe :: Array a -> Array b -- | Cast an Array a into an Array Word8. -- -- Pre-release asBytes :: Array a -> Array Word8 -- | Use an Array a as Ptr b. -- -- Unsafe -- -- Pre-release asPtrUnsafe :: Array a -> (Ptr b -> IO c) -> IO c -- | Strict left fold of an array. foldl' :: (MonadIO m, Storable a) => (b -> a -> b) -> b -> Array a -> m b -- | Right fold of an array. foldr :: (MonadIO m, Storable a) => (a -> b -> b) -> b -> Array a -> m b -- | Compare if two arrays are equal. -- -- Pre-release cmp :: MonadIO m => Array a -> Array a -> m Bool -- | arraysOf n stream groups the input stream into a stream of -- arrays of size n. -- --
--   arraysOf n = StreamD.foldMany (Array.writeN n)
--   
-- -- Pre-release arraysOf :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> Stream m (Array a) -- | Buffer the stream into arrays in memory. arrayStreamKFromStreamD :: forall m a. (MonadIO m, Storable a) => Stream m a -> m (Stream m (Array a)) -- | Buffer a stream into a stream of arrays. -- --
--   >>> writeChunks n = Fold.many (Array.writeN n) Fold.toStreamK
--   
-- -- Breaking an array into an array stream can be useful to consume a -- large array sequentially such that memory of the array is released -- incrementatlly. -- -- See also: arrayStreamKFromStreamD. -- -- Unimplemented writeChunks :: (MonadIO m, Storable a) => Int -> Fold m a (Stream n (Array a)) -- | Use the "read" unfold instead. -- --
--   flattenArrays = unfoldMany read
--   
-- -- We can try this if there are any fusion issues in the unfold. flattenArrays :: forall m a. (MonadIO m, Storable a) => Stream m (Array a) -> Stream m a -- | Use the "readRev" unfold instead. -- --
--   flattenArrays = unfoldMany readRev
--   
-- -- We can try this if there are any fusion issues in the unfold. flattenArraysRev :: forall m a. (MonadIO m, Storable a) => Stream m (Array a) -> Stream m a -- | Convert an array stream to an array. Note that this requires peak -- memory that is double the size of the array stream. fromArrayStreamK :: (Storable a, MonadIO m) => Stream m (Array a) -> m (Array a) -- | O(1) Slice an array in constant time. -- -- Unsafe: The bounds of the slice are not checked. -- -- Unsafe -- -- Pre-release getSliceUnsafe :: forall a. Storable a => Int -> Int -> Array a -> Array a -- | O(1) Slice an array in constant time. Throws an error if the -- slice extends out of the array bounds. -- -- Pre-release getSlice :: forall a. Storable a => Int -> Int -> Array a -> Array a -- | Create two slices of an array without copying the original array. The -- specified index i is the first index of the second slice. splitAt :: forall a. Storable a => Int -> Array a -> (Array a, Array a) -- | Drops the separator byte breakOn :: MonadIO m => Word8 -> Array Word8 -> m (Array Word8, Maybe (Array Word8)) -- | Copy two arrays into a newly allocated array. spliceCopy :: (MonadIO m, Storable a) => Array a -> Array a -> m (Array a) -- | spliceWith sizer dst src mutates dst to append -- src. If there is no reserved space available in dst -- it is reallocated to a size determined by the sizer dstBytesn -- srcBytes function, where dstBytes is the size of the -- first array and srcBytes is the size of the second array, in -- bytes. -- -- Note that the returned array may be a mutated version of first array. -- -- Pre-release spliceWith :: forall m a. (MonadIO m, Storable a) => (Int -> Int -> Int) -> Array a -> Array a -> m (Array a) -- | The first array is mutated to append the second array. If there is no -- reserved space available in the first array a new allocation of exact -- required size is done. -- -- Note that the returned array may be a mutated version of first array. -- --
--   >>> splice = Array.spliceWith (+)
--   
-- -- Pre-release splice :: (MonadIO m, Storable a) => Array a -> Array a -> m (Array a) -- | Like append but the growth of the array is exponential. -- Whenever a new allocation is required the previous array size is at -- least doubled. -- -- This is useful to reduce allocations when folding many arrays -- together. -- -- Note that the returned array may be a mutated version of first array. -- --
--   >>> spliceExp = Array.spliceWith (\l1 l2 -> max (l1 * 2) (l1 + l2))
--   
-- -- Pre-release spliceExp :: (MonadIO m, Storable a) => Array a -> Array a -> m (Array a) memcpy :: Ptr Word8 -> Ptr Word8 -> Int -> IO () memcmp :: Ptr Word8 -> Ptr Word8 -> Int -> IO Bool c_memchr :: Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8) instance Control.DeepSeq.NFData (Streamly.Internal.Data.Array.Foreign.Mut.Type.Array a) -- | See notes in Streamly.Internal.Data.Array.Foreign.Mut.Type module Streamly.Internal.Data.Array.Foreign.Type data Array a Array :: {-# UNPACK #-} !ArrayContents -> {-# UNPACK #-} !Ptr a -> {-# UNPACK #-} !Ptr a -> Array a -- | first address [arrContents] :: Array a -> {-# UNPACK #-} !ArrayContents [arrStart] :: Array a -> {-# UNPACK #-} !Ptr a [aEnd] :: Array a -> {-# UNPACK #-} !Ptr a -- | Makes an immutable array using the underlying memory of the mutable -- array. -- -- Please make sure that there are no other references to the mutable -- array lying around, so that it is never used after freezing it using -- unsafeFreeze. If the underlying array is mutated, the immutable -- promise is lost. -- -- Pre-release unsafeFreeze :: Array a -> Array a -- | Similar to unsafeFreeze but uses rightSize on the -- mutable array first. unsafeFreezeWithShrink :: Storable a => Array a -> Array a -- | Makes a mutable array using the underlying memory of the immutable -- array. -- -- Please make sure that there are no other references to the immutable -- array lying around, so that it is never used after thawing it using -- unsafeThaw. If the resulting array is mutated, any references -- to the older immutable array are mutated as well. -- -- Pre-release unsafeThaw :: Array a -> Array a splice :: (MonadIO m, Storable a) => Array a -> Array a -> m (Array a) -- | Create an Array of the given number of elements of type -- a from a read only pointer Ptr a. The pointer is not -- freed when the array is garbage collected. This API is unsafe for the -- following reasons: -- --
    --
  1. The pointer must point to static pinned memory or foreign memory -- that does not require freeing..
  2. --
  3. The pointer must be legally accessible upto the given length.
  4. --
  5. To guarantee that the array is immutable, the contents of the -- address must be guaranteed to not change.
  6. --
-- -- Unsafe -- -- Pre-release fromPtr :: Int -> Ptr a -> Array a -- | Create an Array Word8 of the given length from a static, read -- only machine address Addr#. See fromPtr for safety -- caveats. -- -- A common use case for this API is to create an array from a static -- unboxed string literal. GHC string literals are of type Addr#, -- and must contain characters that can be encoded in a byte i.e. -- characters or literal bytes in the range from 0-255. -- --
--   >>> import Data.Word (Word8)
--   
--   >>> Array.fromAddr# 5 "hello world!"# :: Array Word8
--   [104,101,108,108,111]
--   
-- --
--   >>> Array.fromAddr# 3 "\255\NUL\255"# :: Array Word8
--   [255,0,255]
--   
-- -- See also: fromString# -- -- Unsafe -- -- Time complexity: O(1) -- -- Pre-release fromAddr# :: Int -> Addr# -> Array a -- | Generate a byte array from an Addr# that contains a sequence of -- NUL (0) terminated bytes. The array would not include the NUL -- byte. The address must be in static read-only memory and must be -- legally accessible up to and including the first NUL byte. -- -- An unboxed string literal (e.g. "hello"#) is a common example -- of an Addr# in static read only memory. It represents the UTF8 -- encoded sequence of bytes terminated by a NUL byte (a CString) -- corresponding to the given unicode string. -- --
--   >>> Array.fromCString# "hello world!"#
--   [104,101,108,108,111,32,119,111,114,108,100,33]
--   
-- --
--   >>> Array.fromCString# "\255\NUL\255"#
--   [255]
--   
-- -- See also: fromAddr# -- -- Unsafe -- -- Time complexity: O(n) (computes the length of the string) -- -- Pre-release fromCString# :: Addr# -> Array Word8 -- | Create an Array from a list. The list must be of finite size. -- -- Since 0.7.0 (Streamly.Memory.Array) fromList :: Storable a => [a] -> Array a -- | Create an Array from the first N elements of a list. The array -- is allocated to size N, if the list terminates before N elements then -- the array may hold less than N elements. -- -- Since 0.7.0 (Streamly.Memory.Array) fromListN :: Storable a => Int -> [a] -> Array a -- | Create an Array from a list in reverse order. The list must be -- of finite size. -- -- Unimplemented fromListRev :: [a] -> Array a -- | Create an Array from the first N elements of a list in reverse -- order. The array is allocated to size N, if the list terminates before -- N elements then the array may hold less than N elements. -- -- Unimplemented fromListRevN :: Int -> [a] -> Array a fromStreamDN :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> m (Array a) fromStreamD :: forall m a. (MonadIO m, Storable a) => Stream m a -> m (Array a) breakOn :: MonadIO m => Word8 -> Array Word8 -> m (Array Word8, Maybe (Array Word8)) -- | Return element at the specified index without checking the bounds. -- -- Unsafe because it does not check the bounds of the array. unsafeIndexIO :: forall a. Storable a => Array a -> Int -> IO a -- | Return element at the specified index without checking the bounds. unsafeIndex :: forall a. Storable a => Array a -> Int -> a -- | O(1) Get the byte length of the array. byteLength :: Array a -> Int -- | O(1) Get the length of the array i.e. the number of elements in -- the array. -- -- Since 0.7.0 (Streamly.Memory.Array) length :: forall a. Storable a => Array a -> Int foldl' :: forall a b. Storable a => (b -> a -> b) -> b -> Array a -> b foldr :: Storable a => (a -> b -> b) -> b -> Array a -> b -- | Create two slices of an array without copying the original array. The -- specified index i is the first index of the second slice. splitAt :: forall a. Storable a => Int -> Array a -> (Array a, Array a) -- | Unfold an array into a stream in reverse order. readRev :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a toStreamD :: forall m a. (Monad m, Storable a) => Array a -> Stream m a toStreamDRev :: forall m a. (Monad m, Storable a) => Array a -> Stream m a toStreamK :: forall m a. Storable a => Array a -> Stream m a toStreamKRev :: forall m a. Storable a => Array a -> Stream m a -- | Convert an Array into a stream. -- -- Pre-release toStream :: (Monad m, Storable a) => Array a -> SerialT m a -- | Convert an Array into a stream in reverse order. -- -- Pre-release toStreamRev :: (Monad m, Storable a) => Array a -> SerialT m a -- | Convert an Array into a list. -- -- Since 0.7.0 (Streamly.Memory.Array) toList :: Storable a => Array a -> [a] writeWith :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- -- Since 0.7.0 (Streamly.Memory.Array) writeN :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) -- | Like writeN but does not check the array bounds when writing. -- The fold driver must not call the step function more than n -- times otherwise it will corrupt the memory and crash. This function -- exists mainly because any conditional in the step function blocks -- fusion causing 10x performance slowdown. writeNUnsafe :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) data ArrayUnsafe a ArrayUnsafe :: {-# UNPACK #-} !ArrayContents -> {-# UNPACK #-} !Ptr a -> {-# UNPACK #-} !Ptr a -> ArrayUnsafe a -- | writeNAligned alignment n folds a maximum of n -- elements from the input stream to an Array aligned to the given -- size. -- -- Pre-release writeNAligned :: forall m a. (MonadIO m, Storable a) => Int -> Int -> Fold m a (Array a) -- | writeNAlignedUnmanaged n folds a maximum of n -- elements from the input stream to an Array aligned to the given -- size and using unmanaged memory. This could be useful to allocate -- memory that we need to allocate only once in the lifetime of the -- program. -- -- Pre-release writeNAlignedUnmanaged :: forall m a. (MonadIO m, Storable a) => Int -> Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Caution! Do not use this on infinite streams. -- -- Since 0.7.0 (Streamly.Memory.Array) write :: forall m a. (MonadIO m, Storable a) => Fold m a (Array a) -- | arraysOf n stream groups the input stream into a stream of -- arrays of size n. arraysOf :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> Stream m (Array a) bufferChunks :: (MonadIO m, Storable a) => Stream m a -> m (Stream m (Array a)) -- | Use the "read" unfold instead. -- --
--   flattenArrays = unfoldMany read
--   
-- -- We can try this if there are any fusion issues in the unfold. flattenArrays :: forall m a. (MonadIO m, Storable a) => Stream m (Array a) -> Stream m a -- | Use the "readRev" unfold instead. -- --
--   flattenArrays = unfoldMany readRev
--   
-- -- We can try this if there are any fusion issues in the unfold. flattenArraysRev :: forall m a. (MonadIO m, Storable a) => Stream m (Array a) -> Stream m a instance (GHC.Show.Show a, Foreign.Storable.Storable a) => GHC.Show.Show (Streamly.Internal.Data.Array.Foreign.Type.Array a) instance (Foreign.Storable.Storable a, GHC.Read.Read a, GHC.Show.Show a) => GHC.Read.Read (Streamly.Internal.Data.Array.Foreign.Type.Array a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString (Streamly.Internal.Data.Array.Foreign.Type.Array a) instance Foreign.Storable.Storable a => GHC.Exts.IsList (Streamly.Internal.Data.Array.Foreign.Type.Array a) instance (Foreign.Storable.Storable a, GHC.Classes.Eq a) => GHC.Classes.Eq (Streamly.Internal.Data.Array.Foreign.Type.Array a) instance Control.DeepSeq.NFData (Streamly.Internal.Data.Array.Foreign.Type.Array a) instance (Foreign.Storable.Storable a, GHC.Classes.Ord a) => GHC.Classes.Ord (Streamly.Internal.Data.Array.Foreign.Type.Array a) instance Foreign.Storable.Storable a => GHC.Base.Semigroup (Streamly.Internal.Data.Array.Foreign.Type.Array a) instance Foreign.Storable.Storable a => GHC.Base.Monoid (Streamly.Internal.Data.Array.Foreign.Type.Array a) -- | A ring array is a circular mutable array. module Streamly.Internal.Ring.Foreign -- | A ring buffer is a mutable array of fixed size. Initially the array is -- empty, with ringStart pointing at the start of allocated memory. We -- call the next location to be written in the ring as ringHead. -- Initially ringHead == ringStart. When the first item is added, -- ringHead points to ringStart + sizeof item. When the buffer becomes -- full ringHead would wrap around to ringStart. When the buffer is full, -- ringHead always points at the oldest item in the ring and the newest -- item added always overwrites the oldest item. -- -- When using it we should keep in mind that a ringBuffer is a mutable -- data structure. We should not leak out references to it for immutable -- use. data Ring a Ring :: {-# UNPACK #-} !ForeignPtr a -> {-# UNPACK #-} !Ptr a -> Ring a [ringStart] :: Ring a -> {-# UNPACK #-} !ForeignPtr a [ringBound] :: Ring a -> {-# UNPACK #-} !Ptr a -- | Create a new ringbuffer and return the ring buffer and the ringHead. -- Returns the ring and the ringHead, the ringHead is same as ringStart. new :: forall a. Storable a => Int -> IO (Ring a, Ptr a) -- | newRing count allocates an empty array that can hold -- count items. The memory of the array is uninitialized and the -- allocation is aligned as per the Storable instance of the type. -- -- Unimplemented newRing :: Int -> m (Ring a) -- | writeN n is a rolling fold that keeps the last n elements of -- the stream in a ring array. -- -- Unimplemented writeN :: Int -> Fold m a (Ring a) -- | Advance the ringHead by 1 item, wrap around if we hit the end of the -- array. advance :: forall a. Storable a => Ring a -> Ptr a -> Ptr a -- | Move the ringHead by n items. The direction depends on the sign on -- whether n is positive or negative. Wrap around if we hit the beginning -- or end of the array. moveBy :: forall a. Storable a => Int -> Ring a -> Ptr a -> Ptr a -- | Get the first address of the ring as a pointer. startOf :: Ring a -> Ptr a -- | Insert an item at the head of the ring, when the ring is full this -- replaces the oldest item in the ring with the new item. This is unsafe -- beause ringHead supplied is not verified to be within the Ring. Also, -- the ringStart foreignPtr must be guaranteed to be alive by the caller. unsafeInsert :: Storable a => Ring a -> Ptr a -> a -> IO (Ptr a) -- | Insert an item at the head of the ring, when the ring is full this -- replaces the oldest item in the ring with the new item. -- -- Unimplemented slide :: Ring a -> a -> m (Ring a) -- | O(1) Write the given element at the given index in the ring -- array. Performs in-place mutation of the array. -- --
--   >>> putIndex arr ix val = Ring.modifyIndex arr ix (const (val, ()))
--   
-- -- Unimplemented putIndex :: Ring a -> Int -> a -> m () -- | Modify a given index of a ring array using a modifier function. -- -- Unimplemented modifyIndex :: Ring a -> Int -> (a -> (a, b)) -> m b -- | Unfold a ring array into a stream. -- -- Unimplemented read :: Unfold m (Ring a) a -- | Unfold a ring array into a stream in reverse order. -- -- Unimplemented readRev :: Unfold m (Array a) a -- | O(1) Lookup the element at the given index. Index starts from -- 0. getIndex :: Ring a -> Int -> m a -- | Return the element at the specified index without checking the bounds. -- -- Unsafe because it does not check the bounds of the ring array. getIndexUnsafe :: Ring a -> Int -> m a -- | O(1) Lookup the element at the given index from the end of the -- array. Index starts from 0. -- -- Slightly faster than computing the forward index and using getIndex. getIndexRev :: Ring a -> Int -> m a -- | O(1) Get the length of the array i.e. the number of elements in -- the array. -- -- Note that byteLength is less expensive than this operation, as -- length involves a costly division operation. -- -- Unimplemented length :: Ring a -> Int -- | O(1) Get the byte length of the array. -- -- Unimplemented byteLength :: Ring a -> Int -- | Get the total capacity of an array. An array may have space reserved -- beyond the current used length of the array. -- -- Pre-release byteCapacity :: Ring a -> Int -- | The remaining capacity in the array for appending more elements -- without reallocation. -- -- Pre-release bytesFree :: Ring a -> Int -- | Cast an array having elements of type a into an array having -- elements of type b. The length of the array should be a -- multiple of the size of the target element otherwise Nothing is -- returned. -- -- Pre-release cast :: forall a b. Storable b => Ring a -> Maybe (Ring b) -- | Cast an array having elements of type a into an array having -- elements of type b. The array size must be a multiple of the -- size of type b. -- -- Unimplemented castUnsafe :: Ring a -> Ring b -- | Cast an Array a into an Array Word8. -- -- Unimplemented asBytes :: Ring a -> Ring Word8 -- | Cast a mutable array to a ring array. fromArray :: Array a -> Ring a -- | Fold the buffer starting from ringStart up to the given Ptr -- using a pure step function. This is useful to fold the items in the -- ring when the ring is not full. The supplied pointer is usually the -- end of the ring. -- -- Unsafe because the supplied Ptr is not checked to be in range. unsafeFoldRing :: forall a b. Storable a => Ptr a -> (b -> a -> b) -> b -> Ring a -> b -- | Like unsafeFoldRing but with a monadic step function. unsafeFoldRingM :: forall m a b. (MonadIO m, Storable a) => Ptr a -> (b -> a -> m b) -> b -> Ring a -> m b -- | Fold the entire length of a ring buffer starting at the supplied -- ringHead pointer. Assuming the supplied ringHead pointer points to the -- oldest item, this would fold the ring starting from the oldest item to -- the newest item in the ring. -- -- Note, this will crash on ring of 0 size. unsafeFoldRingFullM :: forall m a b. (MonadIO m, Storable a) => Ptr a -> (b -> a -> m b) -> b -> Ring a -> m b -- | Fold Int items in the ring starting at Ptr a. Won't -- fold more than the length of the ring. -- -- Note, this will crash on ring of 0 size. unsafeFoldRingNM :: forall m a b. (MonadIO m, Storable a) => Int -> Ptr a -> (b -> a -> m b) -> b -> Ring a -> m b -- | ringsOf n stream groups the input stream into a stream of -- ring arrays of size n. Each ring is a sliding window of size n. -- -- Unimplemented ringsOf :: Int -> SerialT m a -> SerialT m (Array a) -- | Byte compare the entire length of ringBuffer with the given array, -- starting at the supplied ringHead pointer. Returns true if the Array -- and the ringBuffer have identical contents. -- -- This is unsafe because the ringHead Ptr is not checked to be in range. -- The supplied array must be equal to or bigger than the ringBuffer, -- ARRAY BOUNDS ARE NOT CHECKED. unsafeEqArray :: Ring a -> Ptr a -> Array a -> Bool -- | Like unsafeEqArray but compares only N bytes instead of entire -- length of the ring buffer. This is unsafe because the ringHead Ptr is -- not checked to be in range. unsafeEqArrayN :: Ring a -> Ptr a -> Array a -> Int -> Bool -- | This module contains transformations involving multiple streams, -- unfolds or folds. There are two types of transformations generational -- or eliminational. Generational transformations are like the -- Generate module but they generate a stream by combining streams -- instead of elements. Eliminational transformations are like the -- Eliminate module but they transform a stream by eliminating -- parts of the stream instead of eliminating the whole stream. -- -- These combinators involve transformation, generation, elimination so -- can be classified under any of those. -- -- Ultimately these operations should be supported by Unfolds, Pipes and -- Folds, and this module may become redundant. module Streamly.Internal.Data.Stream.StreamD.Nesting data AppendState s1 s2 AppendFirst :: s1 -> AppendState s1 s2 AppendSecond :: s2 -> AppendState s1 s2 append :: Monad m => Stream m a -> Stream m a -> Stream m a data InterleaveState s1 s2 InterleaveFirst :: s1 -> s2 -> InterleaveState s1 s2 InterleaveSecond :: s1 -> s2 -> InterleaveState s1 s2 InterleaveSecondOnly :: s2 -> InterleaveState s1 s2 InterleaveFirstOnly :: s1 -> InterleaveState s1 s2 interleave :: Monad m => Stream m a -> Stream m a -> Stream m a interleaveMin :: Monad m => Stream m a -> Stream m a -> Stream m a interleaveSuffix :: Monad m => Stream m a -> Stream m a -> Stream m a interleaveInfix :: Monad m => Stream m a -> Stream m a -> Stream m a roundRobin :: Monad m => Stream m a -> Stream m a -> Stream m a zipWith :: Monad m => (a -> b -> c) -> Stream m a -> Stream m b -> Stream m c zipWithM :: Monad m => (a -> b -> m c) -> Stream m a -> Stream m b -> Stream m c mergeBy :: Monad m => (a -> a -> Ordering) -> Stream m a -> Stream m a -> Stream m a mergeByM :: Monad m => (a -> a -> m Ordering) -> Stream m a -> Stream m a -> Stream m a concatMap :: Monad m => (a -> Stream m b) -> Stream m a -> Stream m b concatMapM :: Monad m => (a -> m (Stream m b)) -> Stream m a -> Stream m b -- | unfoldMany unfold stream uses unfold to map the -- input stream elements to streams and then flattens the generated -- streams into a single output stream. unfoldMany :: Monad m => Unfold m a b -> Stream m a -> Stream m b data ConcatUnfoldInterleaveState o i ConcatUnfoldInterleaveOuter :: o -> [i] -> ConcatUnfoldInterleaveState o i ConcatUnfoldInterleaveInner :: o -> [i] -> ConcatUnfoldInterleaveState o i ConcatUnfoldInterleaveInnerL :: [i] -> [i] -> ConcatUnfoldInterleaveState o i ConcatUnfoldInterleaveInnerR :: [i] -> [i] -> ConcatUnfoldInterleaveState o i -- | This does not pair streams like concatPairsWith, instead, it goes -- through each stream one by one and yields one element from each -- stream. After it goes to the last stream it reverses the traversal to -- come back to the first stream yielding elements from each stream on -- its way back to the first stream and so on. -- --
--   >>> input = Stream.fromList [[1,1],[2,2],[3,3],[4,4],[5,5]]
--   
--   >>> Stream.toList $ Stream.unfoldManyInterleave Unfold.fromList input
--   [1,2,3,4,5,5,4,3,2,1]
--   
-- -- Note that this is order of magnitude more efficient than -- "concatPairsWith wSerial" unfoldManyInterleave :: Monad m => Unfold m a b -> Stream m a -> Stream m b unfoldManyRoundRobin :: Monad m => Unfold m a b -> Stream m a -> Stream m b interpose :: Monad m => m c -> Unfold m b c -> Stream m b -> Stream m c interposeSuffix :: Monad m => m c -> Unfold m b c -> Stream m b -> Stream m c -- | Interleave streams (full streams, not the elements) unfolded from two -- input streams and concat. Stop when the first stream stops. If the -- second stream ends before the first one then first stream still keeps -- running alone without any interleaving with the second stream. -- -- gintercalate :: Monad m => Unfold m a c -> Stream m a -> Unfold m b c -> Stream m b -> Stream m c -- | Interleave streams (full streams, not the elements) unfolded from two -- input streams and concat. Stop when the first stream stops. If the -- second stream ends before the first one then first stream still keeps -- running alone without any interleaving with the second stream. -- -- gintercalateSuffix :: Monad m => Unfold m a c -> Stream m a -> Unfold m b c -> Stream m b -> Stream m c -- | Apply a fold multiple times until the stream ends. If the stream is -- empty the output would be empty. -- --
--   foldMany f = parseMany (fromFold f)
--   
-- -- A terminating fold may terminate even without accepting a single -- input. So we run the fold's initial action before evaluating the -- stream. However, this means that if later the stream does not yield -- anything we have to discard the fold's initial result which could have -- generated an effect. foldMany :: Monad m => Fold m a b -> Stream m a -> Stream m b -- | Like foldMany but for the Refold type. The supplied -- action is used as the initial value for each refold. -- -- Internal refoldMany :: Monad m => Refold m x a b -> m x -> Stream m a -> Stream m b foldIterateM :: Monad m => (b -> m (Fold m a b)) -> m b -> Stream m a -> Stream m b -- | Like foldIterateM but using the Refold type instead. -- This could be much more efficient due to stream fusion. -- -- Internal refoldIterateM :: Monad m => Refold m b a b -> m b -> Stream m a -> Stream m b parseMany :: MonadThrow m => Parser m a b -> Stream m a -> Stream m b parseIterate :: MonadThrow m => (b -> Parser m a b) -> b -> Stream m a -> Stream m b chunksOf :: Monad m => Int -> Fold m a b -> Stream m a -> Stream m b groupsBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Stream m a -> Stream m b groupsRollingBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Stream m a -> Stream m b wordsBy :: Monad m => (a -> Bool) -> Fold m a b -> Stream m a -> Stream m b splitOnSeq :: forall m a b. (MonadIO m, Storable a, Enum a, Eq a) => Array a -> Fold m a b -> Stream m a -> Stream m b splitOnSuffixSeq :: forall m a b. (MonadIO m, Storable a, Enum a, Eq a) => Bool -> Array a -> Fold m a b -> Stream m a -> Stream m b sliceOnSuffix :: Monad m => (a -> Bool) -> Stream m a -> Stream m (Int, Int) -- | Performs infix separator style splitting. splitInnerBy :: Monad m => (f a -> m (f a, Maybe (f a))) -> (f a -> f a -> m (f a)) -> Stream m (f a) -> Stream m (f a) -- | Performs infix separator style splitting. splitInnerBySuffix :: (Monad m, Eq (f a), Monoid (f a)) => (f a -> m (f a, Maybe (f a))) -> (f a -> f a -> m (f a)) -> Stream m (f a) -> Stream m (f a) module Streamly.Internal.Data.Stream.StreamD.Eliminate fold :: Monad m => Fold m a b -> Stream m a -> m b -- | Run a Parse over a stream. parse :: MonadThrow m => Parser m a b -> Stream m a -> m b -- | Run a Parse over a stream and return rest of the Stream. parse_ :: MonadThrow m => Parser m a b -> Stream m a -> m (b, Stream m a) -- | Does not fuse, has the same performance as the StreamK version. uncons :: Monad m => Stream m a -> m (Maybe (a, Stream m a)) foldrM :: Monad m => (a -> m b -> m b) -> m b -> Stream m a -> m b foldr :: Monad m => (a -> b -> b) -> b -> Stream m a -> m b foldrMx :: Monad m => (a -> m x -> m x) -> m x -> (m x -> m b) -> Stream m a -> m b foldr1 :: Monad m => (a -> a -> a) -> Stream m a -> m (Maybe a) foldlM' :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> m b foldl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b foldlMx' :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream m a -> m b foldlx' :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream m a -> m b -- | Run a streaming composition, discard the results. drain :: Monad m => Stream m a -> m () -- | Execute a monadic action for each element of the Stream mapM_ :: Monad m => (a -> m b) -> Stream m a -> m () null :: Monad m => Stream m a -> m Bool head :: Monad m => Stream m a -> m (Maybe a) headElse :: Monad m => a -> Stream m a -> m a tail :: Monad m => Stream m a -> m (Maybe (Stream m a)) last :: Monad m => Stream m a -> m (Maybe a) elem :: (Monad m, Eq a) => a -> Stream m a -> m Bool notElem :: (Monad m, Eq a) => a -> Stream m a -> m Bool all :: Monad m => (a -> Bool) -> Stream m a -> m Bool any :: Monad m => (a -> Bool) -> Stream m a -> m Bool maximum :: (Monad m, Ord a) => Stream m a -> m (Maybe a) maximumBy :: Monad m => (a -> a -> Ordering) -> Stream m a -> m (Maybe a) minimum :: (Monad m, Ord a) => Stream m a -> m (Maybe a) minimumBy :: Monad m => (a -> a -> Ordering) -> Stream m a -> m (Maybe a) lookup :: (Monad m, Eq a) => a -> Stream m (a, b) -> m (Maybe b) findM :: Monad m => (a -> m Bool) -> Stream m a -> m (Maybe a) find :: Monad m => (a -> Bool) -> Stream m a -> m (Maybe a) (!!) :: Monad m => Stream m a -> Int -> m (Maybe a) the :: (Eq a, Monad m) => Stream m a -> m (Maybe a) toList :: Monad m => Stream m a -> m [a] toListRev :: Monad m => Stream m a -> m [a] eqBy :: Monad m => (a -> b -> Bool) -> Stream m a -> Stream m b -> m Bool -- | Compare two streams lexicographically cmpBy :: Monad m => (a -> b -> Ordering) -> Stream m a -> Stream m b -> m Ordering isPrefixOf :: (Eq a, Monad m) => Stream m a -> Stream m a -> m Bool isSubsequenceOf :: (Eq a, Monad m) => Stream m a -> Stream m a -> m Bool stripPrefix :: (Eq a, Monad m) => Stream m a -> Stream m a -> m (Maybe (Stream m a)) -- | Direct style re-implementation of CPS stream in -- Streamly.Internal.Data.Stream.StreamK. The symbol or suffix -- D in this module denotes the Direct style. GHC is able -- to INLINE and fuse direct style better, providing better performance -- than CPS implementation. -- --
--   import qualified Streamly.Internal.Data.Stream.StreamD as D
--   
module Streamly.Internal.Data.Stream.StreamD -- | To run examples in this module: -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
module Streamly.Internal.Data.Stream.Zip -- | For ZipSerialM streams: -- --
--   (<>) = serial
--   (*) = 'Streamly.Prelude.serial.zipWith' id
--   
-- -- Applicative evaluates the streams being zipped serially: -- --
--   >>> s1 = Stream.fromFoldable [1, 2]
--   
--   >>> s2 = Stream.fromFoldable [3, 4]
--   
--   >>> s3 = Stream.fromFoldable [5, 6]
--   
--   >>> Stream.toList $ Stream.fromZipSerial $ (,,) <$> s1 <*> s2 <*> s3
--   [(1,3,5),(2,4,6)]
--   
-- -- Since: 0.2.0 (Streamly) newtype ZipSerialM m a ZipSerialM :: Stream m a -> ZipSerialM m a [getZipSerialM] :: ZipSerialM m a -> Stream m a -- | An IO stream whose applicative instance zips streams serially. -- -- Since: 0.2.0 (Streamly) type ZipSerial = ZipSerialM IO consMZip :: Monad m => m a -> ZipSerialM m a -> ZipSerialM m a zipWithK :: Monad m => (a -> b -> c) -> Stream m a -> Stream m b -> Stream m c zipWithMK :: Monad m => (a -> b -> m c) -> Stream m a -> Stream m b -> Stream m c -- | For ZipAsyncM streams: -- --
--   (<>) = serial
--   (*) = 'Streamly.Prelude.serial.zipAsyncWith' id
--   
-- -- Applicative evaluates the streams being zipped concurrently, the -- following would take half the time that it would take in serial -- zipping: -- --
--   >>> s = Stream.fromFoldableM $ Prelude.map delay [1, 1, 1]
--   
--   >>> Stream.toList $ Stream.fromZipAsync $ (,) <$> s <*> s
--   ...
--   [(1,1),(1,1),(1,1)]
--   
-- -- Since: 0.2.0 (Streamly) newtype ZipAsyncM m a ZipAsyncM :: Stream m a -> ZipAsyncM m a [getZipAsyncM] :: ZipAsyncM m a -> Stream m a -- | An IO stream whose applicative instance zips streams wAsyncly. -- -- Since: 0.2.0 (Streamly) type ZipAsync = ZipAsyncM IO consMZipAsync :: Monad m => m a -> ZipAsyncM m a -> ZipAsyncM m a -- | Like zipWith but zips concurrently i.e. both the streams -- being zipped are evaluated concurrently using the ParallelT -- concurrent evaluation style. The maximum number of elements of each -- stream evaluated in advance can be controlled by maxBuffer. -- -- The stream ends if stream a or stream b ends. -- However, if stream b ends while we are still evaluating -- stream a and waiting for a result then stream will not end -- until after the evaluation of stream a finishes. This -- behavior can potentially be changed in future to end the stream -- immediately as soon as any of the stream end is detected. zipAsyncWithK :: MonadAsync m => (a -> b -> c) -> Stream m a -> Stream m b -> Stream m c -- | Like zipAsyncWith but with a monadic zipping function. zipAsyncWithMK :: MonadAsync m => (a -> b -> m c) -> Stream m a -> Stream m b -> Stream m c -- | Deprecated: Please use ZipSerialM instead. type ZipStream = ZipSerialM instance GHC.Base.Monoid (Streamly.Internal.Data.Stream.Zip.ZipSerialM m a) instance GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Zip.ZipSerialM m a) instance GHC.Base.Monoid (Streamly.Internal.Data.Stream.Zip.ZipAsyncM m a) instance GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Zip.ZipAsyncM m a) instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Stream.Zip.ZipAsyncM m) instance Streamly.Internal.Control.Concurrent.MonadAsync m => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Zip.ZipAsyncM m) instance GHC.Exts.IsList (Streamly.Internal.Data.Stream.Zip.ZipSerialM Data.Functor.Identity.Identity a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Streamly.Internal.Data.Stream.Zip.ZipSerialM Data.Functor.Identity.Identity a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Streamly.Internal.Data.Stream.Zip.ZipSerialM Data.Functor.Identity.Identity a) instance GHC.Show.Show a => GHC.Show.Show (Streamly.Internal.Data.Stream.Zip.ZipSerialM Data.Functor.Identity.Identity a) instance GHC.Read.Read a => GHC.Read.Read (Streamly.Internal.Data.Stream.Zip.ZipSerialM Data.Functor.Identity.Identity a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString (Streamly.Internal.Data.Stream.Zip.ZipSerialM Data.Functor.Identity.Identity a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Streamly.Internal.Data.Stream.Zip.ZipSerialM Data.Functor.Identity.Identity a) instance Control.DeepSeq.NFData1 (Streamly.Internal.Data.Stream.Zip.ZipSerialM Data.Functor.Identity.Identity) instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Stream.Zip.ZipSerialM m) instance GHC.Base.Monad m => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Zip.ZipSerialM m) instance (Data.Foldable.Foldable m, GHC.Base.Monad m) => Data.Foldable.Foldable (Streamly.Internal.Data.Stream.Zip.ZipSerialM m) instance Data.Traversable.Traversable (Streamly.Internal.Data.Stream.Zip.ZipSerialM Data.Functor.Identity.Identity) module Streamly.Internal.Data.Stream.IsStream.Type -- | Class of types that can represent a stream of elements of some type -- a in some monad m. -- -- Since: 0.2.0 (Streamly) class (forall m a. MonadAsync m => Semigroup (t m a), forall m a. MonadAsync m => Monoid (t m a), forall m. Monad m => Functor (t m), forall m. MonadAsync m => Applicative (t m)) => IsStream t toStream :: IsStream t => t m a -> Stream m a fromStream :: IsStream t => Stream m a -> t m a -- | Constructs a stream by adding a monadic action at the head of an -- existing stream. For example: -- --
--   > toList $ getLine `consM` getLine `consM` nil
--   hello
--   world
--   ["hello","world"]
--   
-- -- Concurrent (do not use fromParallel to construct infinite -- streams) consM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a -- | Operator equivalent of consM. We can read it as "parallel -- colon" to remember that | comes before :. -- --
--   > toList $ getLine |: getLine |: nil
--   hello
--   world
--   ["hello","world"]
--   
-- --
--   let delay = threadDelay 1000000 >> print 1
--   drain $ fromSerial  $ delay |: delay |: delay |: nil
--   drain $ fromParallel $ delay |: delay |: delay |: nil
--   
-- -- Concurrent (do not use fromParallel to construct infinite -- streams) (|:) :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 `consM` infixr 5 |: -- | The type Stream m a represents a monadic stream of values of -- type a constructed using actions in monad m. It uses -- stop, singleton and yield continuations equivalent to the following -- direct style type: -- --
--   data Stream m a = Stop | Singleton a | Yield a (Stream m a)
--   
-- -- To facilitate parallel composition we maintain a local state in an -- SVar that is shared across and is used for synchronization of -- the streams being composed. -- -- The singleton case can be expressed in terms of stop and yield but we -- have it as a separate case to optimize composition operations for -- streams with single element. We build singleton streams in the -- implementation of pure for Applicative and Monad, and in -- lift for MonadTrans. newtype Stream m a MkStream :: (forall r. State Stream m a -> (a -> Stream m a -> m r) -> (a -> m r) -> m r -> m r) -> Stream m a -- | Same as IsStream. -- | Deprecated: Please use IsStream instead. type Streaming = IsStream fromStreamS :: (IsStream t, Monad m) => Stream m a -> t m a toStreamS :: (IsStream t, Monad m) => t m a -> Stream m a fromStreamD :: (IsStream t, Monad m) => Stream m a -> t m a toStreamD :: (IsStream t, Monad m) => t m a -> Stream m a -- | Adapt any specific stream type to any other specific stream type. -- -- Since: 0.1.0 (Streamly) adapt :: (IsStream t1, IsStream t2) => t1 m a -> t2 m a -- | Adapt a polymorphic consM operation to a StreamK cons operation toConsK :: IsStream t => (m a -> t m a -> t m a) -> m a -> Stream m a -> Stream m a -- | Build a stream from an SVar, a stop continuation, a singleton -- stream continuation and a yield continuation. mkStream :: IsStream t => (forall r. State Stream m a -> (a -> t m a -> m r) -> (a -> m r) -> m r -> m r) -> t m a -- | Fold a stream by providing an SVar, a stop continuation, a singleton -- continuation and a yield continuation. The stream would share the -- current SVar passed via the State. foldStreamShared :: IsStream t => State Stream m a -> (a -> t m a -> m r) -> (a -> m r) -> m r -> t m a -> m r -- | Fold a stream by providing a State, stop continuation, a singleton -- continuation and a yield continuation. The stream will not use the -- SVar passed via State. foldStream :: IsStream t => State Stream m a -> (a -> t m a -> m r) -> (a -> m r) -> m r -> t m a -> m r -- | For SerialT streams: -- --
--   (<>) = serial                       -- Semigroup
--   (>>=) = flip . concatMapWith serial -- Monad
--   
-- -- A single Monad bind behaves like a for loop: -- --
--   >>> :{
--   Stream.toList $ do
--        x <- Stream.fromList [1,2] -- foreach x in stream
--        return x
--   :}
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops: -- --
--   >>> :{
--   Stream.toList $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [3,4] -- foreach y in stream
--       return (x, y)
--   :}
--   [(1,3),(1,4),(2,3),(2,4)]
--   
-- -- Since: 0.2.0 (Streamly) data SerialT m a -- | A serial IO stream of elements of type a. See SerialT -- documentation for more details. -- -- Since: 0.2.0 (Streamly) type Serial = SerialT IO -- | Fix the type of a polymorphic stream as SerialT. -- -- Since: 0.1.0 (Streamly) fromSerial :: IsStream t => SerialT m a -> t m a -- | For WSerialT streams: -- --
--   (<>) = wSerial                       -- Semigroup
--   (>>=) = flip . concatMapWith wSerial -- Monad
--   
-- -- Note that <> is associative only if we disregard the -- ordering of elements in the resulting stream. -- -- A single Monad bind behaves like a for loop: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWSerial $ do
--        x <- Stream.fromList [1,2] -- foreach x in stream
--        return x
--   :}
--   [1,2]
--   
-- -- Nested monad binds behave like interleaved nested for loops: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWSerial $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [3,4] -- foreach y in stream
--       return (x, y)
--   :}
--   [(1,3),(2,3),(1,4),(2,4)]
--   
-- -- It is a result of interleaving all the nested iterations corresponding -- to element 1 in the first stream with all the nested -- iterations of element 2: -- --
--   >>> import Streamly.Prelude (wSerial)
--   
--   >>> Stream.toList $ Stream.fromList [(1,3),(1,4)] `Stream.wSerial` Stream.fromList [(2,3),(2,4)]
--   [(1,3),(2,3),(1,4),(2,4)]
--   
-- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- SerialT. -- -- Since: 0.2.0 (Streamly) data WSerialT m a -- | An interleaving serial IO stream of elements of type a. See -- WSerialT documentation for more details. -- -- Since: 0.2.0 (Streamly) type WSerial = WSerialT IO -- | Fix the type of a polymorphic stream as WSerialT. -- -- Since: 0.2.0 (Streamly) fromWSerial :: IsStream t => WSerialT m a -> t m a -- | For AsyncT streams: -- --
--   (<>) = async
--   (>>=) = flip . concatMapWith async
--   
-- -- A single Monad bind behaves like a for loop with -- iterations of the loop executed concurrently a la the async -- combinator, producing results and side effects of iterations out of -- order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAsync $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, a la the async combinator: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAsync $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,4,5,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one output stream and all the iterations corresponding to 2 -- constitute another output stream and these two output streams are -- merged using async. -- -- Since: 0.1.0 (Streamly) data AsyncT m a -- | A demand driven left biased parallely composing IO stream of elements -- of type a. See AsyncT documentation for more details. -- -- Since: 0.2.0 (Streamly) type Async = AsyncT IO -- | Fix the type of a polymorphic stream as AsyncT. -- -- Since: 0.1.0 (Streamly) fromAsync :: IsStream t => AsyncT m a -> t m a -- | For WAsyncT streams: -- --
--   (<>) = wAsync
--   (>>=) = flip . concatMapWith wAsync
--   
-- -- A single Monad bind behaves like a for loop with -- iterations of the loop executed concurrently a la the wAsync -- combinator, producing results and side effects of iterations out of -- order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWAsync $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, a la the wAsync combinator: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWAsync $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,4,5,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one WAsyncT output stream and all the iterations corresponding -- to 2 constitute another WAsyncT output stream and -- these two output streams are merged using wAsync. -- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- AsyncT. -- -- Since: 0.2.0 (Streamly) data WAsyncT m a -- | A round robin parallely composing IO stream of elements of type -- a. See WAsyncT documentation for more details. -- -- Since: 0.2.0 (Streamly) type WAsync = WAsyncT IO -- | Fix the type of a polymorphic stream as WAsyncT. -- -- Since: 0.2.0 (Streamly) fromWAsync :: IsStream t => WAsyncT m a -> t m a -- | For AheadT streams: -- --
--   (<>) = ahead
--   (>>=) = flip . concatMapWith ahead
--   
-- -- A single Monad bind behaves like a for loop with -- iterations executed concurrently, ahead of time, producing side -- effects of iterations out of order, but results in order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAhead $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [2,1]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, ahead of time: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAhead $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,5,4,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one output stream and all the iterations corresponding to 2 -- constitute another output stream and these two output streams are -- merged using ahead. -- -- Since: 0.3.0 (Streamly) data AheadT m a -- | A serial IO stream of elements of type a with concurrent -- lookahead. See AheadT documentation for more details. -- -- Since: 0.3.0 (Streamly) type Ahead = AheadT IO -- | Fix the type of a polymorphic stream as AheadT. -- -- Since: 0.3.0 (Streamly) fromAhead :: IsStream t => AheadT m a -> t m a -- | For ParallelT streams: -- --
--   (<>) = parallel
--   (>>=) = flip . concatMapWith parallel
--   
-- -- See AsyncT, ParallelT is similar except that all -- iterations are strictly concurrent while in AsyncT it depends -- on the consumer demand and available threads. See parallel -- for more details. -- -- Since: 0.1.0 (Streamly) -- -- Since: 0.7.0 (maxBuffer applies to ParallelT streams) data ParallelT m a -- | A parallely composing IO stream of elements of type a. See -- ParallelT documentation for more details. -- -- Since: 0.2.0 (Streamly) type Parallel = ParallelT IO -- | Fix the type of a polymorphic stream as ParallelT. -- -- Since: 0.1.0 (Streamly) fromParallel :: IsStream t => ParallelT m a -> t m a -- | For ZipSerialM streams: -- --
--   (<>) = serial
--   (*) = 'Streamly.Prelude.serial.zipWith' id
--   
-- -- Applicative evaluates the streams being zipped serially: -- --
--   >>> s1 = Stream.fromFoldable [1, 2]
--   
--   >>> s2 = Stream.fromFoldable [3, 4]
--   
--   >>> s3 = Stream.fromFoldable [5, 6]
--   
--   >>> Stream.toList $ Stream.fromZipSerial $ (,,) <$> s1 <*> s2 <*> s3
--   [(1,3,5),(2,4,6)]
--   
-- -- Since: 0.2.0 (Streamly) data ZipSerialM m a -- | An IO stream whose applicative instance zips streams serially. -- -- Since: 0.2.0 (Streamly) type ZipSerial = ZipSerialM IO -- | Fix the type of a polymorphic stream as ZipSerialM. -- -- Since: 0.2.0 (Streamly) fromZipSerial :: IsStream t => ZipSerialM m a -> t m a -- | For ZipAsyncM streams: -- --
--   (<>) = serial
--   (*) = 'Streamly.Prelude.serial.zipAsyncWith' id
--   
-- -- Applicative evaluates the streams being zipped concurrently, the -- following would take half the time that it would take in serial -- zipping: -- --
--   >>> s = Stream.fromFoldableM $ Prelude.map delay [1, 1, 1]
--   
--   >>> Stream.toList $ Stream.fromZipAsync $ (,) <$> s <*> s
--   ...
--   [(1,1),(1,1),(1,1)]
--   
-- -- Since: 0.2.0 (Streamly) data ZipAsyncM m a -- | An IO stream whose applicative instance zips streams wAsyncly. -- -- Since: 0.2.0 (Streamly) type ZipAsync = ZipAsyncM IO -- | Fix the type of a polymorphic stream as ZipAsyncM. -- -- Since: 0.2.0 (Streamly) fromZipAsync :: IsStream t => ZipAsyncM m a -> t m a -- | Construct a stream by adding a pure value at the head of an existing -- stream. For serial streams this is the same as (return a) `consM` -- r but more efficient. For concurrent streams this is not -- concurrent whereas consM is concurrent. For example: -- --
--   > toList $ 1 `cons` 2 `cons` 3 `cons` nil
--   [1,2,3]
--   
cons :: IsStream t => a -> t m a -> t m a infixr 5 `cons` -- | Operator equivalent of cons. -- --
--   > toList $ 1 .: 2 .: 3 .: nil
--   [1,2,3]
--   
(.:) :: IsStream t => a -> t m a -> t m a infixr 5 .: nil :: IsStream t => t m a nilM :: (IsStream t, Monad m) => m b -> t m a fromPure :: IsStream t => a -> t m a fromEffect :: (Monad m, IsStream t) => m a -> t m a repeat :: IsStream t => a -> t m a bindWith :: IsStream t => (t m b -> t m b -> t m b) -> t m a -> (a -> t m b) -> t m b -- | concatMapWith mixer generator stream is a two dimensional -- looping combinator. The generator function is used to -- generate streams from the elements in the input stream and -- the mixer function is used to merge those streams. -- -- Note we can merge streams concurrently by using a concurrent merge -- function. -- -- Since: 0.7.0 -- -- Since: 0.8.0 (signature change) concatMapWith :: IsStream t => (t m b -> t m b -> t m b) -> (a -> t m b) -> t m a -> t m b -- | A variant of fold that allows you to fold a Foldable -- container of streams using the specified stream sum operation. -- --
--   concatFoldableWith async $ map return [1..3]
--   
-- -- Equivalent to: -- --
--   concatFoldableWith f = Prelude.foldr f S.nil
--   concatFoldableWith f = S.concatMapFoldableWith f id
--   
-- -- Since: 0.8.0 (Renamed foldWith to concatFoldableWith) -- -- Since: 0.1.0 (Streamly) concatFoldableWith :: (IsStream t, Foldable f) => (t m a -> t m a -> t m a) -> f (t m a) -> t m a -- | A variant of foldMap that allows you to map a monadic streaming -- action on a Foldable container and then fold it using the -- specified stream merge operation. -- --
--   concatMapFoldableWith async return [1..3]
--   
-- -- Equivalent to: -- --
--   concatMapFoldableWith f g = Prelude.foldr (f . g) S.nil
--   concatMapFoldableWith f g xs = S.concatMapWith f g (S.fromFoldable xs)
--   
-- -- Since: 0.8.0 (Renamed foldMapWith to concatMapFoldableWith) -- -- Since: 0.1.0 (Streamly) concatMapFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b -- | Like concatMapFoldableWith but with the last two arguments -- reversed i.e. the monadic streaming function is the last argument. -- -- Equivalent to: -- --
--   concatForFoldableWith f xs g = Prelude.foldr (f . g) S.nil xs
--   concatForFoldableWith f = flip (S.concatMapFoldableWith f)
--   
-- -- Since: 0.8.0 (Renamed forEachWith to concatForFoldableWith) -- -- Since: 0.1.0 (Streamly) concatForFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b drain :: (IsStream t, Monad m) => t m a -> m () -- |
--   fromList = foldr cons nil
--   
-- -- Construct a stream from a list of pure values. This is more efficient -- than fromFoldable for serial streams. fromList :: (Monad m, IsStream t) => [a] -> t m a -- | Convert a stream into a list in the underlying monad. toList :: (IsStream t, Monad m) => t m a -> m [a] foldrM :: (IsStream t, Monad m) => (a -> m b -> m b) -> m b -> t m a -> m b foldrMx :: (IsStream t, Monad m) => (a -> m x -> m x) -> m x -> (m x -> m b) -> t m a -> m b foldr :: (IsStream t, Monad m) => (a -> b -> b) -> b -> t m a -> m b -- | Strict left fold with an extraction function. Like the standard strict -- left fold, but applies a user supplied extraction function (the third -- argument) to the folded value at the end. This is designed to work -- with the foldl library. The suffix x is a mnemonic -- for extraction. foldlx' :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> m b -- | Like foldlx', but with a monadic step function. foldlMx' :: (IsStream t, Monad m) => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> m b -- | Strict left associative fold. foldl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> m b fold :: (IsStream t, Monad m) => Fold m a b -> t m a -> m b -- | Compare two streams for equality eqBy :: (IsStream t, Monad m) => (a -> b -> Bool) -> t m a -> t m b -> m Bool -- | Compare two streams cmpBy :: (IsStream t, Monad m) => (a -> b -> Ordering) -> t m a -> t m b -> m Ordering -- | Same as fromWSerial. -- | Deprecated: Please use fromWSerial instead. interleaving :: IsStream t => WSerialT m a -> t m a -- | Same as fromZipSerial. -- | Deprecated: Please use fromZipSerial instead. zipping :: IsStream t => ZipSerialM m a -> t m a -- | Same as fromZipAsync. -- | Deprecated: Please use fromZipAsync instead. zippingAsync :: IsStream t => ZipAsyncM m a -> t m a instance Streamly.Internal.Data.Stream.IsStream.Type.IsStream Streamly.Internal.Data.Stream.Serial.SerialT instance Streamly.Internal.Data.Stream.IsStream.Type.IsStream Streamly.Internal.Data.Stream.Serial.WSerialT instance Streamly.Internal.Data.Stream.IsStream.Type.IsStream Streamly.Internal.Data.Stream.Async.AsyncT instance Streamly.Internal.Data.Stream.IsStream.Type.IsStream Streamly.Internal.Data.Stream.Async.WAsyncT instance Streamly.Internal.Data.Stream.IsStream.Type.IsStream Streamly.Internal.Data.Stream.Ahead.AheadT instance Streamly.Internal.Data.Stream.IsStream.Type.IsStream Streamly.Internal.Data.Stream.Parallel.ParallelT instance Streamly.Internal.Data.Stream.IsStream.Type.IsStream Streamly.Internal.Data.Stream.Zip.ZipSerialM instance Streamly.Internal.Data.Stream.IsStream.Type.IsStream Streamly.Internal.Data.Stream.Zip.ZipAsyncM -- | To run the examples in this module: -- --
--   >>> import qualified Streamly.Data.Fold as Fold
--   
--   >>> import qualified Streamly.Internal.Data.Unfold as Unfold
--   
-- --

Unfolds and Streams

-- -- An Unfold type is the same as the direct style Stream -- type except that it uses an inject function to determine the initial -- state of the stream based on an input. A stream is a special case of -- Unfold when the static input is unit or Void. -- -- This allows an important optimization to occur in several cases, -- making the Unfold a more efficient abstraction. Consider the -- concatMap and unfoldMany operations, the latter is -- more efficient. concatMap generates a new stream object from -- each element in the stream by applying the supplied function to the -- element, the stream object includes the "step" function as well as the -- initial "state" of the stream. Since the stream is generated -- dynamically the compiler does not know the step function or the state -- type statically at compile time, therefore, it cannot inline it. On -- the other hand in case of unfoldMany the compiler has -- visibility into the unfold's state generation function, therefore, the -- compiler knows all the types statically and it can inline the inject -- as well as the step functions, generating efficient code. Essentially, -- the stream is not opaque to the consumer in case of unfolds, the -- consumer knows how to generate the stream from a seed using a known -- "inject" and "step" functions. -- -- A Stream is like a data object whereas unfold is like a function. -- Being function like, an Unfold is an instance of Category and -- Arrow type classes. -- --

Unfolds and Folds

-- -- Streams forcing a closed control flow loop can be categorized under -- two types, unfolds and folds, both of these are duals of each other. -- -- Unfold streams are really generators of a sequence of elements, we can -- also call them pull style streams. These are lazy producers of -- streams. On each evaluation the producer generates the next element. A -- consumer can therefore pull elements from the stream whenever it wants -- to. A stream consumer can multiplex pull streams by pulling elements -- from the chosen streams, therefore, pull streams allow merging or -- multiplexing. On the other hand, with this representation we cannot -- split or demultiplex a stream. So really these are stream sources that -- can be generated from a seed and can be merged or zipped into a single -- stream. -- -- The dual of Unfolds are Folds. Folds can also be called as push style -- streams or reducers. These are strict consumers of streams. We keep -- pushing elements to a fold and we can extract the result at any point. -- A driver can choose which fold to push to and can also push the same -- element to multiple folds. Therefore, folds allow splitting or -- demultiplexing a stream. On the other hand, we cannot merge streams -- using this representation. So really these are stream consumers that -- reduce the stream to a single value, these consumers can be composed -- such that a stream can be split over multiple consumers. -- -- Performance: -- -- Composing a tree or graph of computations with unfolds can be much -- more efficient compared to composing with the Monad instance. The -- reason is that unfolds allow the compiler to statically know the state -- and optimize it using stream fusion whereas it is not possible with -- the monad bind because the state is determined dynamically. module Streamly.Internal.Data.Unfold -- | A stream is a succession of Steps. A Yield produces a -- single value and the next state of the stream. Stop indicates -- there are no more values in the stream. data Step s a Yield :: a -> s -> Step s a Skip :: s -> Step s a Stop :: Step s a -- | An Unfold m a b is a generator of a stream of values of type -- b from a seed of type a in Monad m. data Unfold m a b -- | Make an unfold from step and inject functions. -- -- Pre-release mkUnfoldM :: (s -> m (Step s b)) -> (a -> m s) -> Unfold m a b -- | Make an unfold from a step function. -- -- See also: unfoldrM -- -- Pre-release mkUnfoldrM :: Applicative m => (a -> m (Step a b)) -> Unfold m a b -- | Build a stream by unfolding a monadic step function starting -- from a seed. The step function returns the next element in the stream -- and the next seed value. When it is done it returns Nothing and -- the stream ends. -- -- Since: 0.8.0 unfoldrM :: Applicative m => (a -> m (Maybe (b, a))) -> Unfold m a b -- | Like unfoldrM but uses a pure step function. -- --
--   >>> :{
--    f [] = Nothing
--    f (x:xs) = Just (x, xs)
--   :}
--   
-- --
--   >>> Unfold.fold Fold.toList (Unfold.unfoldr f) [1,2,3]
--   [1,2,3]
--   
-- -- Since: 0.8.0 unfoldr :: Applicative m => (a -> Maybe (b, a)) -> Unfold m a b -- | Lift a monadic function into an unfold. The unfold generates a -- singleton stream. -- -- Since: 0.8.0 functionM :: Applicative m => (a -> m b) -> Unfold m a b -- | Lift a pure function into an unfold. The unfold generates a singleton -- stream. -- --
--   function f = functionM $ return . f
--   
-- -- Since: 0.8.0 function :: Applicative m => (a -> b) -> Unfold m a b -- | Identity unfold. The unfold generates a singleton stream having the -- input as the only element. -- --
--   identity = function Prelude.id
--   
-- -- Pre-release identity :: Applicative m => Unfold m a a -- | Lift a monadic function into an unfold generating a nil stream with a -- side effect. nilM :: Applicative m => (a -> m c) -> Unfold m a b -- | Prepend a monadic single element generator function to an -- Unfold. The same seed is used in the action as well as the -- unfold. -- -- Pre-release consM :: Applicative m => (a -> m b) -> Unfold m a b -> Unfold m a b -- | The unfold discards its input and generates a function stream using -- the supplied monadic action. -- -- Pre-release fromEffect :: Applicative m => m b -> Unfold m a b -- | Discards the unfold input and always returns the argument of -- fromPure. -- --
--   fromPure = fromEffect . pure
--   
-- -- Pre-release fromPure :: Applicative m => b -> Unfold m a b -- | Generates an infinite stream repeating the seed. -- -- Since: 0.8.0 repeatM :: Monad m => Unfold m (m a) a -- | Generates a stream replicating the seed n times. -- -- Since: 0.8.0 replicateM :: Monad m => Int -> Unfold m (m a) a -- | fromIndicesM gen generates an infinite stream of values using -- gen starting from the seed. -- --
--   fromIndicesM f = Unfold.mapM f $ Unfold.enumerateFrom 0
--   
-- -- Pre-release fromIndicesM :: Applicative m => (Int -> m a) -> Unfold m Int a -- | Generates an infinite stream starting with the given seed and applying -- the given function repeatedly. -- -- Since: 0.8.0 iterateM :: Monad m => (a -> m a) -> Unfold m (m a) a -- | Types that can be enumerated as a stream. The operations in this type -- class are equivalent to those in the Enum type class, except -- that these generate a stream instead of a list. Use the functions in -- Streamly.Internal.Data.Unfold.Enumeration module to define new -- instances. -- -- Pre-release class Enum a => Enumerable a -- | Unfolds from generating a stream starting with the element -- from, enumerating up to maxBound when the type is -- Bounded or generating an infinite stream when the type is not -- Bounded. -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import qualified Streamly.Internal.Data.Unfold as Unfold
--   
-- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFrom (0 :: Int)
--   [0,1,2,3]
--   
-- -- For Fractional types, enumeration is numerically stable. -- However, no overflow or underflow checks are performed. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFrom 1.1
--   [1.1,2.1,3.1,4.1]
--   
-- -- Pre-release enumerateFrom :: (Enumerable a, Monad m) => Unfold m a a -- | Unfolds (from, to) generating a finite stream starting with -- the element from, enumerating the type up to the value -- to. If to is smaller than from then an -- empty stream is returned. -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import qualified Streamly.Internal.Data.Unfold as Unfold
--   
-- --
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromTo (0, 4)
--   [0,1,2,3,4]
--   
-- -- For Fractional types, the last element is equal to the -- specified to value after rounding to the nearest integral -- value. -- --
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromTo (1.1, 4)
--   [1.1,2.1,3.1,4.1]
--   
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromTo (1.1, 4.6)
--   [1.1,2.1,3.1,4.1,5.1]
--   
-- -- Pre-release enumerateFromTo :: (Enumerable a, Monad m) => Unfold m (a, a) a -- | Unfolds (from, then) generating a stream whose first element -- is from and the successive elements are in increments of -- then. Enumeration can occur downwards or upwards depending on -- whether then comes before or after from. For -- Bounded types the stream ends when maxBound is reached, -- for unbounded types it keeps enumerating infinitely. -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import qualified Streamly.Internal.Data.Unfold as Unfold
--   
-- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFromThen (0, 2)
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.take 4 $ Stream.unfold Unfold.enumerateFromThen (0,(-2))
--   [0,-2,-4,-6]
--   
-- -- Pre-release enumerateFromThen :: (Enumerable a, Monad m) => Unfold m (a, a) a -- | Unfolds (from, then, to) generating a finite stream whose -- first element is from and the successive elements are in -- increments of then up to to. Enumeration can occur -- downwards or upwards depending on whether then comes before -- or after from. -- --
--   >>> import qualified Streamly.Prelude as Stream
--   
--   >>> import qualified Streamly.Internal.Data.Unfold as Unfold
--   
-- --
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromThenTo (0, 2, 6)
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromThenTo (0, (-2), (-6))
--   [0,-2,-4,-6]
--   
-- -- Pre-release enumerateFromThenTo :: (Enumerable a, Monad m) => Unfold m (a, a, a) a -- | Same as enumerateFromStepNum using a stride of 1: -- --
--   >>> enumerateFromNum = lmap (from -> (from, 1)) Unfold.enumerateFromStepNum
--   >>> Stream.toList $ Stream.take 6 $ Stream.unfold enumerateFromNum (0.9)
--   [0.9,1.9,2.9,3.9,4.9,5.9]
--   
-- -- Also, same as enumerateFromThenNum using a stride of 1 but see -- the note in enumerateFromThenNum about the loss of precision: -- --
--   >>> enumerateFromNum = lmap (from -> (from, from + 1)) Unfold.enumerateFromThenNum
--   >>> Stream.toList $ Stream.take 6 $ Stream.unfold enumerateFromNum (0.9)
--   [0.9,1.9,2.9,3.8999999999999995,4.8999999999999995,5.8999999999999995]
--   
-- -- Internal enumerateFromNum :: (Monad m, Num a) => Unfold m a a -- | Same as 'enumerateFromStepNum (from, next)' using a stride of next -- - from: -- --
--   >>> enumerateFromThenNum = lmap ((from, next) -> (from, next - from)) Unfold.enumerateFromStepNum
--   
-- -- Example: @ >>> Stream.toList $ Stream.take 10 $ Stream.unfold -- enumerateFromThenNum (255::Word8,0) [255,0,1,2,3,4,5,6,7,8] -- --
--   The implementation is numerically stable for floating point values.
--   
--   Note that enumerateFromThenIntegral is faster for integrals.
--   
--   Note that in the strange world of floating point numbers, using
--   
-- -- enumerateFromThenNum (from, from + 1) is almost exactly the same -- as enumerateFromStepNum (from, 1) but not precisely the same. -- Because (from + 1) - from is not exactly 1, it may lose some -- precision, the loss may also be aggregated in each step, if you want -- that precision then use enumerateFromStepNum instead. -- -- Internal enumerateFromThenNum :: (Monad m, Num a) => Unfold m (a, a) a -- | Unfolds (from, stride) generating an infinite stream starting -- from from and incrementing every time by stride. For -- Bounded types, after the value overflows it keeps enumerating -- in a cycle: -- --
--   >>> Stream.toList $ Stream.take 10 $ Stream.unfold Unfold.enumerateFromStepNum (255::Word8,1)
--   [255,0,1,2,3,4,5,6,7,8]
--   
-- -- The implementation is numerically stable for floating point values. -- -- Note enumerateFromStepIntegral is faster for integrals. -- -- Internal enumerateFromStepNum :: (Monad m, Num a) => Unfold m (a, a) a enumerateFromIntegralBounded :: (Monad m, Integral a, Bounded a) => Unfold m a a enumerateFromThenIntegralBounded :: (Monad m, Integral a, Bounded a) => Unfold m (a, a) a enumerateFromToIntegralBounded :: (Monad m, Integral a, Bounded a) => Unfold m (a, a) a enumerateFromThenToIntegralBounded :: (Monad m, Integral a, Bounded a) => Unfold m (a, a, a) a enumerateFromIntegral :: (Monad m, Integral a) => Unfold m a a enumerateFromThenIntegral :: (Monad m, Integral a) => Unfold m (a, a) a enumerateFromToIntegral :: (Monad m, Integral a) => Unfold m (a, a) a enumerateFromThenToIntegral :: (Monad m, Integral a) => Unfold m (a, a, a) a -- | Enumerate from given starting Enum value from with stride of -- 1 till maxBound -- -- Internal enumerateFromSmallBounded :: (Monad m, Enum a, Bounded a) => Unfold m a a -- | Enumerate from given starting Enum value from and next Enum -- value next with stride of (fromEnum next - fromEnum from) -- till maxBound. -- -- Internal enumerateFromThenSmallBounded :: forall m a. (Monad m, Enum a, Bounded a) => Unfold m (a, a) a -- | Enumerate from given starting Enum value from and to Enum -- value to with stride of 1 till to value. -- -- Internal enumerateFromToSmall :: (Monad m, Enum a) => Unfold m (a, a) a -- | Enumerate from given starting Enum value from and then Enum -- value next and to Enum value to with stride of -- (fromEnum next - fromEnum from) till to value. -- -- Internal enumerateFromThenToSmall :: (Monad m, Enum a) => Unfold m (a, a, a) a enumerateFromFractional :: (Monad m, Fractional a) => Unfold m a a enumerateFromThenFractional :: (Monad m, Fractional a) => Unfold m (a, a) a -- | Same as enumerateFromStepNum with a step of 1 and enumerating -- up to the specified upper limit rounded to the nearest integral value: -- --
--   >>> Stream.toList $ Stream.unfold Unfold.enumerateFromToFractional (0.1, 6.3)
--   [0.1,1.1,2.1,3.1,4.1,5.1,6.1]
--   
-- -- Internal enumerateFromToFractional :: (Monad m, Fractional a, Ord a) => Unfold m (a, a) a enumerateFromThenToFractional :: (Monad m, Fractional a, Ord a) => Unfold m (a, a, a) a -- | Convert a list of pure values to a Stream -- -- Since: 0.8.0 fromList :: Monad m => Unfold m [a] a -- | Convert a list of monadic values to a Stream -- -- Since: 0.8.0 fromListM :: Monad m => Unfold m [m a] a -- | Convert a stream into an Unfold. Note that a stream converted -- to an Unfold may not be as efficient as an Unfold in -- some situations. -- -- Since: 0.8.0 fromStream :: (IsStream t, Monad m) => Unfold m (t m a) a fromStreamK :: Applicative m => Unfold m (Stream m a) a fromStreamD :: Applicative m => Unfold m (Stream m a) a -- | Map a function on the input argument of the Unfold. -- --
--   >>> u = Unfold.lmap (fmap (+1)) Unfold.fromList
--   
--   >>> Unfold.fold Fold.toList u [1..5]
--   [2,3,4,5,6]
--   
-- --
--   lmap f = Unfold.many (Unfold.function f)
--   
-- -- Since: 0.8.0 lmap :: (a -> c) -> Unfold m c b -> Unfold m a b -- | Map an action on the input argument of the Unfold. -- --
--   lmapM f = Unfold.many (Unfold.functionM f)
--   
-- -- Since: 0.8.0 lmapM :: Monad m => (a -> m c) -> Unfold m c b -> Unfold m a b -- | Supply the seed to an unfold closing the input end of the unfold. -- --
--   supply a = Unfold.lmap (Prelude.const a)
--   
-- -- Pre-release supply :: a -> Unfold m a b -> Unfold m Void b -- | Supply the first component of the tuple to an unfold that accepts a -- tuple as a seed resulting in a fold that accepts the second component -- of the tuple as a seed. -- --
--   supplyFirst a = Unfold.lmap (a, )
--   
-- -- Pre-release supplyFirst :: a -> Unfold m (a, b) c -> Unfold m b c -- | Supply the second component of the tuple to an unfold that accepts a -- tuple as a seed resulting in a fold that accepts the first component -- of the tuple as a seed. -- --
--   supplySecond b = Unfold.lmap (, b)
--   
-- -- Pre-release supplySecond :: b -> Unfold m (a, b) c -> Unfold m a c -- | Convert an Unfold into an unfold accepting a tuple as an -- argument, using the argument of the original fold as the second -- element of tuple and discarding the first element of the tuple. -- --
--   discardFirst = Unfold.lmap snd
--   
-- -- Pre-release discardFirst :: Unfold m a b -> Unfold m (c, a) b -- | Convert an Unfold into an unfold accepting a tuple as an -- argument, using the argument of the original fold as the first element -- of tuple and discarding the second element of the tuple. -- --
--   discardSecond = Unfold.lmap fst
--   
-- -- Pre-release discardSecond :: Unfold m a b -> Unfold m (a, c) b -- | Convert an Unfold that accepts a tuple as an argument into an -- unfold that accepts a tuple with elements swapped. -- --
--   swap = Unfold.lmap Tuple.swap
--   
-- -- Pre-release swap :: Unfold m (a, c) b -> Unfold m (c, a) b -- | Compose an Unfold and a Fold. Given an Unfold m a -- b and a Fold m b c, returns a monadic action a -> -- m c representing the application of the fold on the unfolded -- stream. -- --
--   >>> Unfold.fold Fold.sum Unfold.fromList [1..100]
--   5050
--   
-- --
--   >>> fold f u = Stream.fold f . Stream.unfold u
--   
-- -- Pre-release fold :: Monad m => Fold m b c -> Unfold m a b -> a -> m c -- | Map a function on the output of the unfold (the type b). -- -- Pre-release map :: Functor m => (b -> c) -> Unfold m a b -> Unfold m a c -- | Apply a monadic function to each element of the stream and replace it -- with the output of the resulting action. -- -- Since: 0.8.0 mapM :: Monad m => (b -> m c) -> Unfold m a b -> Unfold m a c mapMWithInput :: Monad m => (a -> b -> m c) -> Unfold m a b -> Unfold m a c -- | Scan the output of an Unfold to change it in a stateful manner. -- -- Unimplemented scanlM' :: Monad m => (b -> a -> m b) -> m b -> Unfold m c a -> Unfold m c b -- | Scan the output of an Unfold to change it in a stateful manner. -- -- Pre-release scan :: Monad m => Fold m b c -> Unfold m a b -> Unfold m a c -- | Apply a fold multiple times on the output of an unfold. -- -- Unimplemented foldMany :: Fold m b c -> Unfold m a b -> Unfold m a c -- | Make an unfold operate on values wrapped in an Either a a -- type. 'Right a' translates to 'Right b' and 'Left a' translates to -- 'Left b'. -- -- Internal either :: Applicative m => Unfold m a b -> Unfold m (Either a a) (Either b b) -- | Same as takeWhile but with a monadic predicate. -- -- Since: 0.8.0 takeWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b -- | End the stream generated by the Unfold as soon as the predicate -- fails on an element. -- -- Since: 0.8.0 takeWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b -- |
--   >>> u = Unfold.take 2 Unfold.fromList
--   
--   >>> Unfold.fold Fold.toList u [1..100]
--   [1,2]
--   
-- -- Since: 0.8.0 take :: Monad m => Int -> Unfold m a b -> Unfold m a b -- | Include only those elements that pass a predicate. -- -- Since: 0.8.0 filter :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b -- | Same as filter but with a monadic predicate. -- -- Since: 0.8.0 filterM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b -- | drop n unf drops n elements from the stream -- generated by unf. -- -- Since: 0.8.0 drop :: Monad m => Int -> Unfold m a b -> Unfold m a b -- | Similar to dropWhileM but with a pure condition function. -- -- Since: 0.8.0 dropWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b -- | dropWhileM f unf drops elements from the stream generated by -- unf while the condition holds true. The condition function -- f is monadic in nature. -- -- Since: 0.8.0 dropWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b -- | Distribute the input to two unfolds and then zip the outputs to a -- single stream using a monadic zip function. -- -- Stops as soon as any of the unfolds stops. -- -- Pre-release zipWithM :: Monad m => (b -> c -> m d) -> Unfold m a b -> Unfold m a c -> Unfold m a d -- | Like zipWithM but with a pure zip function. -- --
--   >>> square = fmap (\x -> x * x) Unfold.fromList
--   
--   >>> cube = fmap (\x -> x * x * x) Unfold.fromList
--   
--   >>> u = Unfold.zipWith (,) square cube
--   
--   >>> Unfold.fold Fold.toList u [1..5]
--   [(1,1),(4,8),(9,27),(16,64),(25,125)]
--   
-- --
--   zipWith f = zipWithM (\a b -> return $ f a b)
--   
-- -- Since: 0.8.0 zipWith :: Monad m => (b -> c -> d) -> Unfold m a b -> Unfold m a c -> Unfold m a d -- | Create a cross product (vector product or cartesian product) of the -- output streams of two unfolds using a monadic combining function. -- -- Pre-release crossWithM :: Monad m => (b -> c -> m d) -> Unfold m a b -> Unfold m a c -> Unfold m a d -- | Like crossWithM but uses a pure combining function. -- --
--   crossWith f = crossWithM (\b c -> return $ f b c)
--   
-- --
--   >>> u1 = Unfold.lmap fst Unfold.fromList
--   
--   >>> u2 = Unfold.lmap snd Unfold.fromList
--   
--   >>> u = Unfold.crossWith (,) u1 u2
--   
--   >>> Unfold.fold Fold.toList u ([1,2,3], [4,5,6])
--   [(1,4),(1,5),(1,6),(2,4),(2,5),(2,6),(3,4),(3,5),(3,6)]
--   
-- -- Since: 0.8.0 crossWith :: Monad m => (b -> c -> d) -> Unfold m a b -> Unfold m a c -> Unfold m a d -- | See crossWith. -- --
--   cross = crossWith (,)
--   
-- -- To cross the streams from a tuple we can write: -- --
--   crossProduct :: Monad m => Unfold m a b -> Unfold m c d -> Unfold m (a, c) (b, d)
--   crossProduct u1 u2 = cross (lmap fst u1) (lmap snd u2)
--   
-- -- Pre-release cross :: Monad m => Unfold m a b -> Unfold m a c -> Unfold m a (b, c) apply :: Monad m => Unfold m a (b -> c) -> Unfold m a b -> Unfold m a c data ConcatState s1 s2 ConcatOuter :: s1 -> ConcatState s1 s2 ConcatInner :: s1 -> s2 -> ConcatState s1 s2 -- | Apply the second unfold to each output element of the first unfold and -- flatten the output in a single stream. -- -- Since: 0.8.0 many :: Monad m => Unfold m a b -> Unfold m b c -> Unfold m a c -- | Map an unfold generating action to each element of an unfold and -- flatten the results into a single stream. concatMapM :: Monad m => (b -> m (Unfold m a c)) -> Unfold m a b -> Unfold m a c bind :: Monad m => Unfold m a b -> (b -> Unfold m a c) -> Unfold m a c infixl 1 `bind` -- | Like gbracket but with following differences: -- -- -- -- Inhibits stream fusion -- -- Pre-release gbracket_ :: Monad m => (a -> m c) -> (forall s. m s -> m (Either e s)) -> (c -> m d) -> Unfold m (c, e) b -> Unfold m c b -> Unfold m a b -- | Run the alloc action a -> m c with async exceptions -- disabled but keeping blocking operations interruptible (see -- mask). Use the output c as input to Unfold m c -- b to generate an output stream. When unfolding use the supplied -- try operation forall s. m s -> m (Either e s) to -- catch synchronous exceptions. If an exception occurs run the exception -- handling unfold Unfold m (c, e) b. -- -- The cleanup action c -> m d, runs whenever the stream ends -- normally, due to a sync or async exception or if it gets garbage -- collected after a partial lazy evaluation. See bracket for the -- semantics of the cleanup action. -- -- gbracket can express all other exception handling combinators. -- -- Inhibits stream fusion -- -- Pre-release gbracket :: (MonadIO m, MonadBaseControl IO m) => (a -> m c) -> (forall s. m s -> m (Either e s)) -> (c -> m d) -> Unfold m (c, e) b -> Unfold m c b -> Unfold m a b -- | Run a side effect a -> m c on the input a before -- unfolding it using Unfold m a b. -- --
--   before f = lmapM (\a -> f a >> return a)
--   
-- -- Pre-release before :: (a -> m c) -> Unfold m a b -> Unfold m a b -- | Unfold the input a using Unfold m a b, run an action -- on a whenever the unfold stops normally, or if it is garbage -- collected after a partial lazy evaluation. -- -- The semantics of the action a -> m c are similar to the -- cleanup action semantics in bracket. -- -- See also after_ -- -- Pre-release after :: (MonadIO m, MonadBaseControl IO m) => (a -> m c) -> Unfold m a b -> Unfold m a b -- | Like after with following differences: -- -- -- -- Pre-release after_ :: Monad m => (a -> m c) -> Unfold m a b -> Unfold m a b -- | Unfold the input a using Unfold m a b, run an action -- on a whenever the unfold stops normally, aborts due to an -- exception or if it is garbage collected after a partial lazy -- evaluation. -- -- The semantics of the action a -> m c are similar to the -- cleanup action semantics in bracket. -- --
--   finally release = bracket return release
--   
-- -- See also finally_ -- -- Inhibits stream fusion -- -- Pre-release finally :: (MonadAsync m, MonadCatch m) => (a -> m c) -> Unfold m a b -> Unfold m a b -- | Like finally with following differences: -- -- -- -- Inhibits stream fusion -- -- Pre-release finally_ :: MonadCatch m => (a -> m c) -> Unfold m a b -> Unfold m a b -- | Run the alloc action a -> m c with async exceptions -- disabled but keeping blocking operations interruptible (see -- mask). Use the output c as input to Unfold m c -- b to generate an output stream. -- -- c is usually a resource under the state of monad m, -- e.g. a file handle, that requires a cleanup after use. The cleanup -- action c -> m d, runs whenever the stream ends normally, -- due to a sync or async exception or if it gets garbage collected after -- a partial lazy evaluation. -- -- bracket only guarantees that the cleanup action runs, and it -- runs with async exceptions enabled. The action must ensure that it can -- successfully cleanup the resource in the face of sync or async -- exceptions. -- -- When the stream ends normally or on a sync exception, cleanup action -- runs immediately in the current thread context, whereas in other cases -- it runs in the GC context, therefore, cleanup may be delayed until the -- GC gets to run. -- -- See also: bracket_, gbracket -- -- Inhibits stream fusion -- -- Pre-release bracket :: (MonadAsync m, MonadCatch m) => (a -> m c) -> (c -> m d) -> Unfold m c b -> Unfold m a b -- | Like bracket but with following differences: -- -- -- -- Inhibits stream fusion -- -- Pre-release bracket_ :: MonadCatch m => (a -> m c) -> (c -> m d) -> Unfold m c b -> Unfold m a b -- | Unfold the input a using Unfold m a b, run the -- action a -> m c on a if the unfold aborts due to -- an exception. -- -- Inhibits stream fusion -- -- Pre-release onException :: MonadCatch m => (a -> m c) -> Unfold m a b -> Unfold m a b -- | When unfolding Unfold m a b if an exception e -- occurs, unfold e using Unfold m e b. -- -- Inhibits stream fusion -- -- Pre-release handle :: (MonadCatch m, Exception e) => Unfold m e b -> Unfold m a b -> Unfold m a b -- | An Unfold is a source or a producer of a stream of values. It -- takes a seed value as an input and unfolds it into a sequence of -- values. -- --
--   >>> import qualified Streamly.Data.Fold as Fold
--   
--   >>> import qualified Streamly.Data.Unfold as Unfold
--   
--   >>> import qualified Streamly.Prelude as Stream
--   
-- -- For example, the fromList Unfold generates a stream of values -- from a supplied list. Unfolds can be converted to SerialT -- stream using the Stream.unfold operation. -- --
--   >>> stream = Stream.unfold Unfold.fromList [1..100]
--   
--   >>> Stream.sum stream
--   5050
--   
-- -- All the serial stream generation operations in Streamly.Prelude -- can be expressed using unfolds: -- --
--   Stream.fromList = Stream.unfold Unfold.fromList [1..100]
--   
-- -- Conceptually, an Unfold is just like "Data.List.unfoldr". Let -- us write a step function to unfold a list using "Data.List.unfoldr": -- --
--   >>> :{
--    f [] = Nothing
--    f (x:xs) = Just (x, xs)
--   :}
--   
-- --
--   >>> Data.List.unfoldr f [1,2,3]
--   [1,2,3]
--   
-- -- Unfold.unfoldr is just the same, it uses the same step function: -- --
--   >>> Stream.toList $ Stream.unfold (Unfold.unfoldr f) [1,2,3]
--   [1,2,3]
--   
-- -- The input of an unfold can be transformed using lmap: -- --
--   >>> u = Unfold.lmap (fmap (+1)) Unfold.fromList
--   
--   >>> Stream.toList $ Stream.unfold u [1..5]
--   [2,3,4,5,6]
--   
-- -- Unfold streams can be transformed using transformation -- combinators. For example, to retain only the first two elements of an -- unfold: -- --
--   >>> u = Unfold.take 2 Unfold.fromList
--   
--   >>> Stream.toList $ Stream.unfold u [1..100]
--   [1,2]
--   
-- -- Multiple unfolds can be combined in several interesting ways. For -- example, to generate nested looping as in imperative languages (also -- known as cross product of the two streams): -- --
--   >>> u1 = Unfold.lmap fst Unfold.fromList
--   
--   >>> u2 = Unfold.lmap snd Unfold.fromList
--   
--   >>> u = Unfold.crossWith (,) u1 u2
--   
--   >>> Stream.toList $ Stream.unfold u ([1,2,3], [4,5,6])
--   [(1,4),(1,5),(1,6),(2,4),(2,5),(2,6),(3,4),(3,5),(3,6)]
--   
-- -- Nested loops using unfolds provide C like performance due to complete -- stream fusion. -- -- Please see Streamly.Internal.Data.Unfold for additional -- Pre-release functions. -- --

Unfolds vs. Streams

-- -- Unfolds' raison d'etre is their efficiency in nested stream operations -- due to complete stream fusion. concatMap or the Monad -- instance of streams use stream generation operations of the shape -- a -> t m b and then flatten the resulting stream. This -- implementation is more powerful but does not allow for complete stream -- fusion. Unfolds provide less powerful but more efficient -- unfoldMany, many and crossWith operations as an -- alternative to a subset of use cases of concatMap and -- Applicative stream operations. -- -- Streamly.Prelude exports polymorphic stream generation -- operations that provide the same functionality as unfolds in this -- module. Since unfolds can be easily converted to streams, several -- modules in streamly provide only unfolds for serial stream generation. -- We cannot use unfolds exclusively for stream generation as they do not -- support concurrency. module Streamly.Data.Unfold -- | An Unfold m a b is a generator of a stream of values of type -- b from a seed of type a in Monad m. data Unfold m a b -- | Build a stream by unfolding a monadic step function starting -- from a seed. The step function returns the next element in the stream -- and the next seed value. When it is done it returns Nothing and -- the stream ends. -- -- Since: 0.8.0 unfoldrM :: Applicative m => (a -> m (Maybe (b, a))) -> Unfold m a b -- | Like unfoldrM but uses a pure step function. -- --
--   >>> :{
--    f [] = Nothing
--    f (x:xs) = Just (x, xs)
--   :}
--   
-- --
--   >>> Unfold.fold Fold.toList (Unfold.unfoldr f) [1,2,3]
--   [1,2,3]
--   
-- -- Since: 0.8.0 unfoldr :: Applicative m => (a -> Maybe (b, a)) -> Unfold m a b -- | Lift a pure function into an unfold. The unfold generates a singleton -- stream. -- --
--   function f = functionM $ return . f
--   
-- -- Since: 0.8.0 function :: Applicative m => (a -> b) -> Unfold m a b -- | Lift a monadic function into an unfold. The unfold generates a -- singleton stream. -- -- Since: 0.8.0 functionM :: Applicative m => (a -> m b) -> Unfold m a b -- | Generates an infinite stream repeating the seed. -- -- Since: 0.8.0 repeatM :: Monad m => Unfold m (m a) a -- | Generates a stream replicating the seed n times. -- -- Since: 0.8.0 replicateM :: Monad m => Int -> Unfold m (m a) a -- | Generates an infinite stream starting with the given seed and applying -- the given function repeatedly. -- -- Since: 0.8.0 iterateM :: Monad m => (a -> m a) -> Unfold m (m a) a -- | Convert a list of pure values to a Stream -- -- Since: 0.8.0 fromList :: Monad m => Unfold m [a] a -- | Convert a list of monadic values to a Stream -- -- Since: 0.8.0 fromListM :: Monad m => Unfold m [m a] a -- | Convert a stream into an Unfold. Note that a stream converted -- to an Unfold may not be as efficient as an Unfold in -- some situations. -- -- Since: 0.8.0 fromStream :: (IsStream t, Monad m) => Unfold m (t m a) a -- | Map a function on the input argument of the Unfold. -- --
--   >>> u = Unfold.lmap (fmap (+1)) Unfold.fromList
--   
--   >>> Unfold.fold Fold.toList u [1..5]
--   [2,3,4,5,6]
--   
-- --
--   lmap f = Unfold.many (Unfold.function f)
--   
-- -- Since: 0.8.0 lmap :: (a -> c) -> Unfold m c b -> Unfold m a b -- | Map an action on the input argument of the Unfold. -- --
--   lmapM f = Unfold.many (Unfold.functionM f)
--   
-- -- Since: 0.8.0 lmapM :: Monad m => (a -> m c) -> Unfold m c b -> Unfold m a b -- | Apply a monadic function to each element of the stream and replace it -- with the output of the resulting action. -- -- Since: 0.8.0 mapM :: Monad m => (b -> m c) -> Unfold m a b -> Unfold m a c -- | Same as takeWhile but with a monadic predicate. -- -- Since: 0.8.0 takeWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b -- | End the stream generated by the Unfold as soon as the predicate -- fails on an element. -- -- Since: 0.8.0 takeWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b -- |
--   >>> u = Unfold.take 2 Unfold.fromList
--   
--   >>> Unfold.fold Fold.toList u [1..100]
--   [1,2]
--   
-- -- Since: 0.8.0 take :: Monad m => Int -> Unfold m a b -> Unfold m a b -- | Include only those elements that pass a predicate. -- -- Since: 0.8.0 filter :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b -- | Same as filter but with a monadic predicate. -- -- Since: 0.8.0 filterM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b -- | drop n unf drops n elements from the stream -- generated by unf. -- -- Since: 0.8.0 drop :: Monad m => Int -> Unfold m a b -> Unfold m a b -- | Similar to dropWhileM but with a pure condition function. -- -- Since: 0.8.0 dropWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b -- | dropWhileM f unf drops elements from the stream generated by -- unf while the condition holds true. The condition function -- f is monadic in nature. -- -- Since: 0.8.0 dropWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b -- | Like zipWithM but with a pure zip function. -- --
--   >>> square = fmap (\x -> x * x) Unfold.fromList
--   
--   >>> cube = fmap (\x -> x * x * x) Unfold.fromList
--   
--   >>> u = Unfold.zipWith (,) square cube
--   
--   >>> Unfold.fold Fold.toList u [1..5]
--   [(1,1),(4,8),(9,27),(16,64),(25,125)]
--   
-- --
--   zipWith f = zipWithM (\a b -> return $ f a b)
--   
-- -- Since: 0.8.0 zipWith :: Monad m => (b -> c -> d) -> Unfold m a b -> Unfold m a c -> Unfold m a d -- | Like crossWithM but uses a pure combining function. -- --
--   crossWith f = crossWithM (\b c -> return $ f b c)
--   
-- --
--   >>> u1 = Unfold.lmap fst Unfold.fromList
--   
--   >>> u2 = Unfold.lmap snd Unfold.fromList
--   
--   >>> u = Unfold.crossWith (,) u1 u2
--   
--   >>> Unfold.fold Fold.toList u ([1,2,3], [4,5,6])
--   [(1,4),(1,5),(1,6),(2,4),(2,5),(2,6),(3,4),(3,5),(3,6)]
--   
-- -- Since: 0.8.0 crossWith :: Monad m => (b -> c -> d) -> Unfold m a b -> Unfold m a c -> Unfold m a d -- | Apply the second unfold to each output element of the first unfold and -- flatten the output in a single stream. -- -- Since: 0.8.0 many :: Monad m => Unfold m a b -> Unfold m b c -> Unfold m a c -- | The functions defined in this module should be rarely needed for -- direct use, try to use the operations from the Enumerable type -- class instances instead. -- -- This module provides an Enumerable type class to enumerate -- Enum types into a stream. The operations in this type class -- correspond to similar perations in the Enum type class, the -- only difference is that they produce a stream instead of a list. These -- operations cannot be defined generically based on the Enum type -- class. We provide instances for commonly used types. If instances for -- other types are needed convenience functions defined in this module -- can be used to define them. Alternatively, these functions can be used -- directly. module Streamly.Internal.Data.Stream.IsStream.Enumeration -- | Types that can be enumerated as a stream. The operations in this type -- class are equivalent to those in the Enum type class, except -- that these generate a stream instead of a list. Use the functions in -- Streamly.Internal.Data.Stream.Enumeration module to define new -- instances. class Enum a => Enumerable a -- | enumerateFrom from generates a stream starting with the -- element from, enumerating up to maxBound when the type -- is Bounded or generating an infinite stream when the type is -- not Bounded. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFrom (0 :: Int)
--   [0,1,2,3]
--   
-- -- For Fractional types, enumeration is numerically stable. -- However, no overflow or underflow checks are performed. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFrom 1.1
--   [1.1,2.1,3.1,4.1]
--   
enumerateFrom :: (Enumerable a, IsStream t, Monad m) => a -> t m a -- | Generate a finite stream starting with the element from, -- enumerating the type up to the value to. If to is -- smaller than from then an empty stream is returned. -- --
--   >>> Stream.toList $ Stream.enumerateFromTo 0 4
--   [0,1,2,3,4]
--   
-- -- For Fractional types, the last element is equal to the -- specified to value after rounding to the nearest integral -- value. -- --
--   >>> Stream.toList $ Stream.enumerateFromTo 1.1 4
--   [1.1,2.1,3.1,4.1]
--   
--   >>> Stream.toList $ Stream.enumerateFromTo 1.1 4.6
--   [1.1,2.1,3.1,4.1,5.1]
--   
enumerateFromTo :: (Enumerable a, IsStream t, Monad m) => a -> a -> t m a -- | enumerateFromThen from then generates a stream whose first -- element is from, the second element is then and the -- successive elements are in increments of then - from. -- Enumeration can occur downwards or upwards depending on whether -- then comes before or after from. For Bounded -- types the stream ends when maxBound is reached, for unbounded -- types it keeps enumerating infinitely. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThen 0 2
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThen 0 (-2)
--   [0,-2,-4,-6]
--   
enumerateFromThen :: (Enumerable a, IsStream t, Monad m) => a -> a -> t m a -- | enumerateFromThenTo from then to generates a finite stream -- whose first element is from, the second element is -- then and the successive elements are in increments of -- then - from up to to. Enumeration can occur -- downwards or upwards depending on whether then comes before -- or after from. -- --
--   >>> Stream.toList $ Stream.enumerateFromThenTo 0 2 6
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.enumerateFromThenTo 0 (-2) (-6)
--   [0,-2,-4,-6]
--   
enumerateFromThenTo :: (Enumerable a, IsStream t, Monad m) => a -> a -> a -> t m a -- |
--   enumerate = enumerateFrom minBound
--   
-- -- Enumerate a Bounded type from its minBound to -- maxBound enumerate :: (IsStream t, Monad m, Bounded a, Enumerable a) => t m a -- |
--   enumerateTo = enumerateFromTo minBound
--   
-- -- Enumerate a Bounded type from its minBound to specified -- value. enumerateTo :: (IsStream t, Monad m, Bounded a, Enumerable a) => a -> t m a -- |
--   enumerateFromBounded = enumerateFromTo from maxBound
--   
-- -- enumerateFrom for Bounded Enum types. enumerateFromBounded :: (IsStream t, Monad m, Enumerable a, Bounded a) => a -> t m a -- | enumerateFromTo for Enum types not larger than -- Int. enumerateFromToSmall :: (IsStream t, Monad m, Enum a) => a -> a -> t m a -- | enumerateFromThenTo for Enum types not larger than -- Int. enumerateFromThenToSmall :: (IsStream t, Monad m, Enum a) => a -> a -> a -> t m a -- | enumerateFromThen for Enum types not larger than -- Int. -- -- Note: We convert the Enum to Int and enumerate the -- Int. If a type is bounded but does not have a Bounded -- instance then we can go on enumerating it beyond the legal values of -- the type, resulting in the failure of toEnum when converting -- back to Enum. Therefore we require a Bounded instance -- for this function to be safely used. enumerateFromThenSmallBounded :: (IsStream t, Monad m, Enumerable a, Bounded a) => a -> a -> t m a -- | Enumerate an Integral type. enumerateFromIntegral from -- generates a stream whose first element is from and the -- successive elements are in increments of 1. The stream is -- bounded by the size of the Integral type. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromIntegral (0 :: Int)
--   [0,1,2,3]
--   
enumerateFromIntegral :: (IsStream t, Monad m, Integral a, Bounded a) => a -> t m a -- | Enumerate an Integral type in steps. -- enumerateFromThenIntegral from then generates a stream whose -- first element is from, the second element is then -- and the successive elements are in increments of then - from. -- The stream is bounded by the size of the Integral type. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThenIntegral (0 :: Int) 2
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThenIntegral (0 :: Int) (-2)
--   [0,-2,-4,-6]
--   
enumerateFromThenIntegral :: (IsStream t, Monad m, Integral a, Bounded a) => a -> a -> t m a -- | Enumerate an Integral type up to a given limit. -- enumerateFromToIntegral from to generates a finite stream -- whose first element is from and successive elements are in -- increments of 1 up to to. -- --
--   >>> Stream.toList $ Stream.enumerateFromToIntegral 0 4
--   [0,1,2,3,4]
--   
enumerateFromToIntegral :: (IsStream t, Monad m, Integral a) => a -> a -> t m a -- | Enumerate an Integral type in steps up to a given limit. -- enumerateFromThenToIntegral from then to generates a finite -- stream whose first element is from, the second element is -- then and the successive elements are in increments of -- then - from up to to. -- --
--   >>> Stream.toList $ Stream.enumerateFromThenToIntegral 0 2 6
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.enumerateFromThenToIntegral 0 (-2) (-6)
--   [0,-2,-4,-6]
--   
enumerateFromThenToIntegral :: (IsStream t, Monad m, Integral a) => a -> a -> a -> t m a -- | enumerateFromStepIntegral from step generates an infinite -- stream whose first element is from and the successive -- elements are in increments of step. -- -- CAUTION: This function is not safe for finite integral types. It does -- not check for overflow, underflow or bounds. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromStepIntegral 0 2
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.take 3 $ Stream.enumerateFromStepIntegral 0 (-2)
--   [0,-2,-4]
--   
enumerateFromStepIntegral :: (IsStream t, Monad m, Integral a) => a -> a -> t m a -- | Numerically stable enumeration from a Fractional number in -- steps of size 1. enumerateFromFractional from -- generates a stream whose first element is from and the -- successive elements are in increments of 1. No overflow or -- underflow checks are performed. -- -- This is the equivalent to enumFrom for Fractional types. -- For example: -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromFractional 1.1
--   [1.1,2.1,3.1,4.1]
--   
enumerateFromFractional :: (IsStream t, Monad m, Fractional a) => a -> t m a -- | Numerically stable enumeration from a Fractional number to a -- given limit. enumerateFromToFractional from to generates a -- finite stream whose first element is from and successive -- elements are in increments of 1 up to to. -- -- This is the equivalent of enumFromTo for Fractional -- types. For example: -- --
--   >>> Stream.toList $ Stream.enumerateFromToFractional 1.1 4
--   [1.1,2.1,3.1,4.1]
--   
--   >>> Stream.toList $ Stream.enumerateFromToFractional 1.1 4.6
--   [1.1,2.1,3.1,4.1,5.1]
--   
-- -- Notice that the last element is equal to the specified to -- value after rounding to the nearest integer. enumerateFromToFractional :: (IsStream t, Monad m, Fractional a, Ord a) => a -> a -> t m a -- | Numerically stable enumeration from a Fractional number in -- steps. enumerateFromThenFractional from then generates a -- stream whose first element is from, the second element is -- then and the successive elements are in increments of -- then - from. No overflow or underflow checks are performed. -- -- This is the equivalent of enumFromThen for Fractional -- types. For example: -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThenFractional 1.1 2.1
--   [1.1,2.1,3.1,4.1]
--   
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThenFractional 1.1 (-2.1)
--   [1.1,-2.1,-5.300000000000001,-8.500000000000002]
--   
enumerateFromThenFractional :: (IsStream t, Monad m, Fractional a) => a -> a -> t m a -- | Numerically stable enumeration from a Fractional number in -- steps up to a given limit. enumerateFromThenToFractional from then -- to generates a finite stream whose first element is -- from, the second element is then and the successive -- elements are in increments of then - from up to to. -- -- This is the equivalent of enumFromThenTo for Fractional -- types. For example: -- --
--   >>> Stream.toList $ Stream.enumerateFromThenToFractional 0.1 2 6
--   [0.1,2.0,3.9,5.799999999999999]
--   
--   >>> Stream.toList $ Stream.enumerateFromThenToFractional 0.1 (-2) (-6)
--   [0.1,-2.0,-4.1000000000000005,-6.200000000000001]
--   
enumerateFromThenToFractional :: (IsStream t, Monad m, Fractional a, Ord a) => a -> a -> a -> t m a instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable () instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Types.Bool instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Types.Ordering instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Types.Char instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Types.Int instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Int.Int8 instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Int.Int16 instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Int.Int32 instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Int.Int64 instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Types.Word instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Word.Word8 instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Word.Word16 instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Word.Word32 instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Word.Word64 instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Integer.Type.Integer instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Natural.Natural instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Types.Float instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable GHC.Types.Double instance Data.Fixed.HasResolution a => Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable (Data.Fixed.Fixed a) instance GHC.Real.Integral a => Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable (GHC.Real.Ratio a) instance Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable a => Streamly.Internal.Data.Stream.IsStream.Enumeration.Enumerable (Data.Functor.Identity.Identity a) module Streamly.Internal.Data.Stream.IsStream.Combinators -- | Specify the maximum number of threads that can be spawned concurrently -- for any concurrent combinator in a stream. A value of 0 resets the -- thread limit to default, a negative value means there is no limit. The -- default value is 1500. maxThreads does not affect -- ParallelT streams as they can use unbounded number of -- threads. -- -- When the actions in a stream are IO bound, having blocking IO calls, -- this option can be used to control the maximum number of in-flight IO -- requests. When the actions are CPU bound this option can be used to -- control the amount of CPU used by the stream. -- -- Since: 0.4.0 (Streamly) maxThreads :: IsStream t => Int -> t m a -> t m a -- | Specify the maximum size of the buffer for storing the results from -- concurrent computations. If the buffer becomes full we stop spawning -- more concurrent tasks until there is space in the buffer. A value of 0 -- resets the buffer size to default, a negative value means there is no -- limit. The default value is 1500. -- -- CAUTION! using an unbounded maxBuffer value (i.e. a negative -- value) coupled with an unbounded maxThreads value is a recipe -- for disaster in presence of infinite streams, or very large streams. -- Especially, it must not be used when pure is used in -- ZipAsyncM streams as pure in applicative zip streams -- generates an infinite stream causing unbounded concurrent generation -- with no limit on the buffer or threads. -- -- Since: 0.4.0 (Streamly) maxBuffer :: IsStream t => Int -> t m a -> t m a maxYields :: IsStream t => Maybe Int64 -> t m a -> t m a -- | Specify the pull rate of a stream. A Nothing value resets the -- rate to default which is unlimited. When the rate is specified, -- concurrent production may be ramped up or down automatically to -- achieve the specified yield rate. The specific behavior for different -- styles of Rate specifications is documented under Rate. -- The effective maximum production rate achieved by a stream is governed -- by: -- -- -- -- Since: 0.5.0 (Streamly) rate :: IsStream t => Maybe Rate -> t m a -> t m a -- | Same as rate (Just $ Rate (r/2) r (2*r) maxBound) -- -- Specifies the average production rate of a stream in number of yields -- per second (i.e. Hertz). Concurrent production is ramped up -- or down automatically to achieve the specified average yield rate. The -- rate can go down to half of the specified rate on the lower side and -- double of the specified rate on the higher side. -- -- Since: 0.5.0 (Streamly) avgRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate r r (2*r) maxBound) -- -- Specifies the minimum rate at which the stream should yield values. As -- far as possible the yield rate would never be allowed to go below the -- specified rate, even though it may possibly go above it at times, the -- upper limit is double of the specified rate. -- -- Since: 0.5.0 (Streamly) minRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate (r/2) r r maxBound) -- -- Specifies the maximum rate at which the stream should yield values. As -- far as possible the yield rate would never be allowed to go above the -- specified rate, even though it may possibly go below it at times, the -- lower limit is half of the specified rate. This can be useful in -- applications where certain resource usage must not be allowed to go -- beyond certain limits. -- -- Since: 0.5.0 (Streamly) maxRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate r r r 0) -- -- Specifies a constant yield rate. If for some reason the actual rate -- goes above or below the specified rate we do not try to recover it by -- increasing or decreasing the rate in future. This can be useful in -- applications like graphics frame refresh where we need to maintain a -- constant refresh rate. -- -- Since: 0.5.0 (Streamly) constRate :: IsStream t => Double -> t m a -> t m a -- | Print debug information about an SVar when the stream ends -- -- Pre-release inspectMode :: IsStream t => t m a -> t m a printState :: MonadIO m => State Stream m a -> m () -- | Lists are just a special case of monadic streams. The stream type -- SerialT Identity a can be used as a replacement for -- [a]. The List type in this module is just a newtype -- wrapper around SerialT Identity for better type inference -- when using the OverloadedLists GHC extension. List a -- provides better performance compared to [a]. Standard list, -- string and list comprehension syntax can be used with the List -- type by enabling OverloadedLists, OverloadedStrings -- and MonadComprehensions GHC extensions. There would be a -- slight difference in the Show and Read strings of -- streamly list as compared to regular lists. -- -- Conversion to stream types is free, any stream combinator can be used -- on lists by converting them to streams. However, for convenience, this -- module provides combinators that work directly on the List -- type. -- --
--   List $ S.map (+ 1) $ toSerial (1 `Cons` Nil)
--   
-- -- To convert a List to regular lists, you can use any of the -- following: -- -- -- -- If you have made use of Nil and Cons constructors in the -- code and you want to replace streamly lists with standard lists, all -- you need to do is import these definitions: -- --
--   type List = []
--   pattern Nil <- [] where Nil = []
--   pattern Cons x xs = x : xs
--   infixr 5 Cons
--   {-# COMPLETE Cons, Nil #-}
--   
-- -- See src/docs/streamly-vs-lists.md for more details and -- src/test/PureStreams.hs for comprehensive usage examples. module Streamly.Internal.Data.List -- | List a is a replacement for [a]. newtype List a List :: SerialT Identity a -> List a [toSerial] :: List a -> SerialT Identity a -- | An empty list constructor and pattern that matches an empty -- List. Corresponds to '[]' for Haskell lists. pattern Nil :: List a -- | A list constructor and pattern that deconstructs a List into -- its head and tail. Corresponds to : for Haskell lists. pattern Cons :: a -> List a -> List a infixr 5 `Cons` -- | Just like List except that it has a zipping Applicative -- instance and no Monad instance. newtype ZipList a ZipList :: ZipSerialM Identity a -> ZipList a [toZipSerial] :: ZipList a -> ZipSerialM Identity a -- | Convert a ZipList to a regular List fromZipList :: ZipList a -> List a -- | Convert a regular List to a ZipList toZipList :: List a -> ZipList a instance GHC.Base.Monad Streamly.Internal.Data.List.List instance Data.Traversable.Traversable Streamly.Internal.Data.List.List instance GHC.Base.Applicative Streamly.Internal.Data.List.List instance Data.Foldable.Foldable Streamly.Internal.Data.List.List instance GHC.Base.Functor Streamly.Internal.Data.List.List instance GHC.Base.Monoid (Streamly.Internal.Data.List.List a) instance GHC.Base.Semigroup (Streamly.Internal.Data.List.List a) instance Control.DeepSeq.NFData1 Streamly.Internal.Data.List.List instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Streamly.Internal.Data.List.List a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Streamly.Internal.Data.List.List a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Streamly.Internal.Data.List.List a) instance GHC.Read.Read a => GHC.Read.Read (Streamly.Internal.Data.List.List a) instance GHC.Show.Show a => GHC.Show.Show (Streamly.Internal.Data.List.List a) instance Data.Traversable.Traversable Streamly.Internal.Data.List.ZipList instance GHC.Base.Applicative Streamly.Internal.Data.List.ZipList instance Data.Foldable.Foldable Streamly.Internal.Data.List.ZipList instance GHC.Base.Functor Streamly.Internal.Data.List.ZipList instance GHC.Base.Monoid (Streamly.Internal.Data.List.ZipList a) instance GHC.Base.Semigroup (Streamly.Internal.Data.List.ZipList a) instance Control.DeepSeq.NFData1 Streamly.Internal.Data.List.ZipList instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Streamly.Internal.Data.List.ZipList a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Streamly.Internal.Data.List.ZipList a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Streamly.Internal.Data.List.ZipList a) instance GHC.Read.Read a => GHC.Read.Read (Streamly.Internal.Data.List.ZipList a) instance GHC.Show.Show a => GHC.Show.Show (Streamly.Internal.Data.List.ZipList a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString (Streamly.Internal.Data.List.ZipList a) instance GHC.Exts.IsList (Streamly.Internal.Data.List.ZipList a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString (Streamly.Internal.Data.List.List a) instance GHC.Exts.IsList (Streamly.Internal.Data.List.List a) module Streamly.Internal.Data.Stream.IsStream.Lift -- | Transform the inner monad of a stream using a natural transformation. -- -- Internal hoist :: (Monad m, Monad n) => (forall x. m x -> n x) -> SerialT m a -> SerialT n a -- | Generalize the inner monad of the stream from Identity to any -- monad. -- -- Internal generally :: (IsStream t, Monad m) => t Identity a -> t m a -- | Lift the inner monad m of a stream t m a to tr -- m using the monad transformer tr. liftInner :: (Monad m, IsStream t, MonadTrans tr, Monad (tr m)) => t m a -> t (tr m) a -- | Run a stream transformation using a given environment. -- -- See also: map -- -- Internal usingReaderT :: (Monad m, IsStream t) => m r -> (t (ReaderT r m) a -> t (ReaderT r m) a) -> t m a -> t m a -- | Evaluate the inner monad of a stream as ReaderT. runReaderT :: (IsStream t, Monad m) => m s -> t (ReaderT s m) a -> t m a -- | Evaluate the inner monad of a stream as StateT. -- -- This is supported only for SerialT as concurrent state updation -- may not be safe. -- --
--   evalStateT s = Stream.map snd . Stream.runStateT s
--   
-- -- Internal evalStateT :: Monad m => m s -> SerialT (StateT s m) a -> SerialT m a -- | Run a stateful (StateT) stream transformation using a given state. -- -- This is supported only for SerialT as concurrent state updation -- may not be safe. -- --
--   usingStateT s f = evalStateT s . f . liftInner
--   
-- -- See also: scanl' -- -- Internal usingStateT :: Monad m => m s -> (SerialT (StateT s m) a -> SerialT (StateT s m) a) -> SerialT m a -> SerialT m a -- | Evaluate the inner monad of a stream as StateT and emit the -- resulting state and value pair after each step. -- -- This is supported only for SerialT as concurrent state updation -- may not be safe. runStateT :: Monad m => m s -> SerialT (StateT s m) a -> SerialT m (s, a) module Streamly.Internal.Data.Stream.IsStream.Exception -- | Run the action m b before the stream yields its first -- element. -- -- Same as the following but more efficient due to fusion: -- --
--   >>> before action xs = Stream.nilM action <> xs
--   
--   >>> before action xs = Stream.concatMap (const xs) (Stream.fromEffect action)
--   
before :: (IsStream t, Monad m) => m b -> t m a -> t m a -- | Like after, with following differences: -- -- -- -- Same as the following, but with stream fusion: -- --
--   after_ action xs = xs <> 'nilM' action
--   
-- -- Pre-release after_ :: (IsStream t, Monad m) => m b -> t m a -> t m a -- | Run the action m b whenever the stream t m a stops -- normally, or if it is garbage collected after a partial lazy -- evaluation. -- -- The semantics of the action m b are similar to the semantics -- of cleanup action in bracket. -- -- See also after_ after :: (IsStream t, MonadIO m, MonadBaseControl IO m) => m b -> t m a -> t m a -- | Like bracket but with following differences: -- -- -- -- Inhibits stream fusion -- -- Pre-release bracket_ :: (IsStream t, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a -- | Run the alloc action m b with async exceptions disabled but -- keeping blocking operations interruptible (see mask). Use the -- output b as input to b -> t m a to generate an -- output stream. -- -- b is usually a resource under the state of monad m, -- e.g. a file handle, that requires a cleanup after use. The cleanup -- action b -> m c, runs whenever the stream ends normally, -- due to a sync or async exception or if it gets garbage collected after -- a partial lazy evaluation. -- -- bracket only guarantees that the cleanup action runs, and it -- runs with async exceptions enabled. The action must ensure that it can -- successfully cleanup the resource in the face of sync or async -- exceptions. -- -- When the stream ends normally or on a sync exception, cleanup action -- runs immediately in the current thread context, whereas in other cases -- it runs in the GC context, therefore, cleanup may be delayed until the -- GC gets to run. -- -- See also: bracket_ -- -- Inhibits stream fusion bracket :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a -- | Like bracket but can use separate cleanup actions depending on -- the mode of termination. bracket' before onStop onGC onException -- action runs action using the result of before. -- If the stream stops, onStop action is executed, if the stream -- is abandoned onGC is executed, if the stream encounters an -- exception onException is executed. -- -- Pre-release bracket' :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> (b -> m c) -> (b -> m d) -> (b -> m e) -> (b -> t m a) -> t m a -- | Run the action m b if the stream aborts due to an exception. -- The exception is not caught, simply rethrown. -- -- Inhibits stream fusion onException :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a -- | Like finally with following differences: -- -- -- -- Inhibits stream fusion -- -- Pre-release finally_ :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a -- | Run the action m b whenever the stream t m a stops -- normally, aborts due to an exception or if it is garbage collected -- after a partial lazy evaluation. -- -- The semantics of running the action m b are similar to the -- cleanup action semantics described in bracket. -- --
--   finally release = bracket (return ()) (const release)
--   
-- -- See also finally_ -- -- Inhibits stream fusion finally :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> t m a -> t m a -- | Like handle but the exception handler is also provided with the -- stream that generated the exception as input. The exception handler -- can thus re-evaluate the stream to retry the action that failed. The -- exception handler can again call ghandle on it to retry the -- action multiple times. -- -- This is highly experimental. In a stream of actions we can map the -- stream with a retry combinator to retry each action on failure. -- -- Inhibits stream fusion -- -- Pre-release ghandle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a -> t m a) -> t m a -> t m a -- | When evaluating a stream if an exception occurs, stream evaluation -- aborts and the specified exception handler is run with the exception -- as argument. -- -- Inhibits stream fusion handle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a) -> t m a -> t m a -- | retry takes 3 arguments -- --
    --
  1. A map m whose keys are exceptions and values are the -- number of times to retry the action given that the exception -- occurs.
  2. --
  3. A handler han that decides how to handle an exception -- when the exception cannot be retried.
  4. --
  5. The stream itself that we want to run this mechanism on.
  6. --
-- -- When evaluating a stream if an exception occurs, -- --
    --
  1. The stream evaluation aborts
  2. --
  3. The exception is looked up in m
  4. --
-- -- a. If the exception exists and the mapped value is > 0 then, -- -- i. The value is decreased by 1. -- -- ii. The stream is resumed from where the exception was called, -- retrying the action. -- -- b. If the exception exists and the mapped value is == 0 then the -- stream evaluation stops. -- -- c. If the exception does not exist then we handle the exception using -- han. -- -- Internal retry :: (IsStream t, MonadCatch m, Exception e, Ord e) => Map e Int -> (e -> t m a) -> t m a -> t m a module Streamly.Internal.Data.SmallArray data SmallArray a SmallArray :: SmallArray# a -> SmallArray a foldl' :: (b -> a -> b) -> b -> SmallArray a -> b foldr :: (a -> b -> b) -> b -> SmallArray a -> b length :: SmallArray a -> Int -- | writeN n folds a maximum of n elements from the -- input stream to an SmallArray. -- -- Since we are folding to a SmallArray n should be <= -- 128, for larger number of elements use an Array from either -- Streamly.Data.Array or Streamly.Data.Array.Foreign. writeN :: MonadIO m => Int -> Fold m a (SmallArray a) toStreamD :: Monad m => SmallArray a -> Stream m a toStreamDRev :: Monad m => SmallArray a -> Stream m a toStream :: Monad m => SmallArray a -> SerialT m a toStreamRev :: Monad m => SmallArray a -> SerialT m a read :: Monad m => Unfold m (SmallArray a) a -- | Create a SmallArray from the first n elements of a -- list. The array may hold less than n elements if the length -- of the list <= n. -- -- It is recommended to use a value of n <= 128. For larger -- sized arrays, use an Array from Streamly.Data.Array or -- Streamly.Data.Array.Foreign fromListN :: Int -> [a] -> SmallArray a fromStreamDN :: MonadIO m => Int -> Stream m a -> m (SmallArray a) -- | Create a SmallArray from the first n elements of a -- stream. The array is allocated to size n, if the stream -- terminates before n elements then the array may hold less -- than n elements. -- -- For optimal performance use this with n <= 128. fromStreamN :: MonadIO m => Int -> SerialT m a -> m (SmallArray a) streamFold :: Monad m => (SerialT m a -> m b) -> SmallArray a -> m b fold :: Monad m => Fold m a b -> SmallArray a -> m b instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Streamly.Internal.Data.SmallArray.Type.SmallArray a) -- | Combinators to efficiently manipulate streams of mutable arrays. module Streamly.Internal.Data.Array.Stream.Mut.Foreign -- | arraysOf n stream groups the elements in the input stream -- into arrays of n elements each. -- -- Same as the following but may be more efficient: -- --
--   arraysOf n = Stream.foldMany (MArray.writeN n)
--   
-- -- Pre-release arraysOf :: (IsStream t, MonadIO m, Storable a) => Int -> t m a -> t m (Array a) -- | This mutates the first array (if it has space) to append values from -- the second one. This would work for immutable arrays as well because -- an immutable array never has space so a new array is allocated instead -- of mutating it. -- -- | Coalesce adjacent arrays in incoming stream to form bigger arrays of -- a maximum specified size. Note that if a single array is bigger than -- the specified size we do not split it to fit. When we coalesce -- multiple arrays if the size would exceed the specified size we do not -- coalesce therefore the actual array size may be less than the -- specified chunk size. packArraysChunksOf :: (MonadIO m, Storable a) => Int -> Stream m (Array a) -> Stream m (Array a) data SpliceState s arr SpliceInitial :: s -> SpliceState s arr SpliceBuffering :: s -> arr -> SpliceState s arr SpliceYielding :: arr -> SpliceState s arr -> SpliceState s arr SpliceFinish :: SpliceState s arr lpackArraysChunksOf :: (MonadIO m, Storable a) => Int -> Fold m (Array a) () -> Fold m (Array a) () -- | Coalesce adjacent arrays in incoming stream to form bigger arrays of a -- maximum specified size in bytes. -- -- Internal compact :: (MonadIO m, Storable a) => Int -> SerialT m (Array a) -> SerialT m (Array a) -- | Coalesce adjacent arrays in incoming stream to form bigger arrays of a -- maximum specified size in bytes. -- -- Internal compactLE :: MonadIO m => Int -> SerialT m (Array a) -> SerialT m (Array a) -- | Like compactLE but generates arrays of exactly equal to the -- size specified except for the last array in the stream which could be -- shorter. -- -- Unimplemented compactEQ :: Int -> SerialT m (Array a) -> SerialT m (Array a) -- | Like compactLE but generates arrays of size greater than or -- equal to the specified except for the last array in the stream which -- could be shorter. -- -- Unimplemented compactGE :: Int -> SerialT m (Array a) -> SerialT m (Array a) module Streamly.Internal.Data.Array.Prim.Pinned.Mut.Type data Array a Array :: MutableByteArray# RealWorld -> Array a -- | Allocate an array that is pinned and can hold count items. -- The memory of the array is uninitialized. -- -- Note that this is internal routine, the reference to this array cannot -- be given out until the array has been written to and frozen. newArray :: forall m a. (MonadIO m, Prim a) => Int -> m (Array a) -- | Allocate a new array aligned to the specified alignment and using -- pinned memory. newAlignedArray :: forall m a. (MonadIO m, Prim a) => Int -> Int -> m (Array a) unsafeWriteIndex :: (MonadIO m, Prim a) => Array a -> Int -> a -> m () spliceTwo :: (MonadIO m, Prim a) => Array a -> Array a -> m (Array a) -- | Copy a range of the first array to the specified region in the second -- array. Both arrays must fully contain the specified ranges, but this -- is not checked. The regions are allowed to overlap, although this is -- only possible when the same array is provided as both the source and -- the destination. unsafeCopy :: forall m a. (MonadIO m, Prim a) => Array a -> Int -> Array a -> Int -> Int -> m () fromListM :: (MonadIO m, Prim a) => [a] -> m (Array a) fromListNM :: (MonadIO m, Prim a) => Int -> [a] -> m (Array a) fromStreamDN :: (MonadIO m, Prim a) => Int -> Stream m a -> m (Array a) fromStreamD :: (MonadIO m, Prim a) => Stream m a -> m (Array a) -- | fromStreamArraysOf n stream groups the input stream into a -- stream of arrays of size n. fromStreamDArraysOf :: (MonadIO m, Prim a) => Int -> Stream m a -> Stream m (Array a) -- | Coalesce adjacent arrays in incoming stream to form bigger arrays of a -- maximum specified size in bytes. Note that if a single array is bigger -- than the specified size we do not split it to fit. When we coalesce -- multiple arrays if the size would exceed the specified size we do not -- coalesce therefore the actual array size may be less than the -- specified chunk size. -- -- Pre-release packArraysChunksOf :: (MonadIO m, Prim a) => Int -> Stream m (Array a) -> Stream m (Array a) lpackArraysChunksOf :: (MonadIO m, Prim a) => Int -> Fold m (Array a) () -> Fold m (Array a) () unsafeReadIndex :: (MonadIO m, Prim a) => Array a -> Int -> m a length :: forall m a. (MonadIO m, Prim a) => Array a -> m Int byteLength :: MonadIO m => Array a -> m Int -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- -- Pre-release writeN :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) data ArrayUnsafe a ArrayUnsafe :: {-# UNPACK #-} !Array a -> {-# UNPACK #-} !Int -> ArrayUnsafe a -- | Like writeN but does not check the array bounds when writing. -- The fold driver must not call the step function more than n -- times otherwise it will corrupt the memory and crash. This function -- exists mainly because any conditional in the step function blocks -- fusion causing 10x performance slowdown. -- -- Pre-release writeNUnsafe :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) writeNAligned :: (MonadIO m, Prim a) => Int -> Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Caution! Do not use this on infinite streams. -- -- Pre-release write :: (MonadIO m, Prim a) => Fold m a (Array a) -- | Resize (pinned) mutable byte array to new specified size (in elem -- count). The returned array is either the original array resized -- in-place or, if not possible, a newly allocated (pinned) array (with -- the original content copied over). resizeArray :: (MonadIO m, Prim a) => Array a -> Int -> m (Array a) shrinkArray :: forall m a. (MonadIO m, Prim a) => Array a -> Int -> m () touchArray :: Array a -> IO () withArrayAsPtr :: Array a -> (Ptr a -> IO b) -> IO b module Streamly.Internal.Data.Array.Prim.Pinned.Type data Array a Array :: ByteArray# -> Int -> Int -> Array a unsafeFreeze :: (Prim a, MonadIO m) => Array a -> m (Array a) unsafeFreezeWithShrink :: (Prim a, MonadIO m) => Array a -> Int -> m (Array a) -- | Default maximum buffer size in bytes, for reading from and writing to -- IO devices, the value is 32KB minus GHC allocation overhead, which is -- a few bytes, so that the actual allocation is 32KB. defaultChunkSize :: Int nil :: Prim a => Array a -- | Splice two immutable arrays creating a new immutable array. spliceTwo :: (MonadIO m, Prim a) => Array a -> Array a -> m (Array a) fromList :: Prim a => [a] -> Array a fromListN :: Prim a => Int -> [a] -> Array a fromStreamDN :: (MonadIO m, Prim a) => Int -> Stream m a -> m (Array a) fromStreamD :: (MonadIO m, Prim a) => Stream m a -> m (Array a) -- | fromStreamArraysOf n stream groups the input stream into a -- stream of arrays of size n. fromStreamDArraysOf :: (MonadIO m, Prim a) => Int -> Stream m a -> Stream m (Array a) data FlattenState s a OuterLoop :: s -> FlattenState s a InnerLoop :: s -> !Array a -> !Int -> !Int -> FlattenState s a flattenArrays :: (MonadIO m, Prim a) => Stream m (Array a) -> Stream m a flattenArraysRev :: (MonadIO m, Prim a) => Stream m (Array a) -> Stream m a data SpliceState s arr1 arr2 SpliceInitial :: s -> SpliceState s arr1 arr2 SpliceBuffering :: s -> arr2 -> SpliceState s arr1 arr2 SpliceYielding :: arr1 -> SpliceState s arr1 arr2 -> SpliceState s arr1 arr2 SpliceFinish :: SpliceState s arr1 arr2 -- | Coalesce adjacent arrays in incoming stream to form bigger arrays of a -- maximum specified size in bytes. Note that if a single array is bigger -- than the specified size we do not split it to fit. When we coalesce -- multiple arrays if the size would exceed the specified size we do not -- coalesce therefore the actual array size may be less than the -- specified chunk size. -- -- Pre-release packArraysChunksOf :: forall m a. (MonadIO m, Prim a) => Int -> Stream m (Array a) -> Stream m (Array a) lpackArraysChunksOf :: forall m a. (MonadIO m, Prim a) => Int -> Fold m (Array a) () -> Fold m (Array a) () -- | Split a stream of arrays on a given separator byte, dropping the -- separator and coalescing all the arrays between two separators into a -- single array. -- -- Pre-release splitOn :: MonadIO m => Word8 -> Stream m (Array Word8) -> Stream m (Array Word8) breakOn :: MonadIO m => Word8 -> Array Word8 -> m (Array Word8, Maybe (Array Word8)) unsafeIndex :: Prim a => Array a -> Int -> a byteLength :: forall a. Prim a => Array a -> Int length :: Array a -> Int -- | Strict left-associated fold over the elements of an Array. foldl' :: Prim a => (b -> a -> b) -> b -> Array a -> b foldr :: Prim a => (a -> b -> b) -> b -> Array a -> b -- | Strict right-associated fold over the elements of an Array. foldr' :: Prim a => (a -> b -> b) -> b -> Array a -> b -- | Strict left-associated fold over the elements of an Array. foldlM' :: (Prim a, Monad m) => (b -> a -> m b) -> b -> Array a -> m b -- | splitAt n xs returns a tuple where first element is -- xs prefix of length n and second element is the -- remainder of the list: -- --
--   splitAt 6 "Hello World!" == ("Hello ","World!")
--   splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5])
--   splitAt 1 [1,2,3] == ([1],[2,3])
--   splitAt 3 [1,2,3] == ([1,2,3],[])
--   splitAt 4 [1,2,3] == ([1,2,3],[])
--   splitAt 0 [1,2,3] == ([],[1,2,3])
--   splitAt (-1) [1,2,3] == ([],[1,2,3])
--   
-- -- It is equivalent to (take n xs, drop n xs) when -- n is not _|_ (splitAt _|_ xs = _|_). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) toStreamD :: (Prim a, Monad m) => Array a -> Stream m a toStreamDRev :: (Prim a, Monad m) => Array a -> Stream m a toStreamK :: Prim a => Array a -> Stream m a toStreamKRev :: Prim a => Array a -> Stream m a -- | Convert an Array into a list. -- -- Pre-release toList :: Prim a => Array a -> [a] -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- -- Pre-release writeN :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) data ArrayUnsafe a ArrayUnsafe :: {-# UNPACK #-} !Array a -> {-# UNPACK #-} !Int -> ArrayUnsafe a -- | Like writeN but does not check the array bounds when writing. -- The fold driver must not call the step function more than n -- times otherwise it will corrupt the memory and crash. This function -- exists mainly because any conditional in the step function blocks -- fusion causing 10x performance slowdown. -- -- Pre-release writeNUnsafe :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Caution! Do not use this on infinite streams. -- -- Pre-release write :: (MonadIO m, Prim a) => Fold m a (Array a) unlines :: (MonadIO m, Prim a) => a -> Stream m (Array a) -> Stream m a toPtr :: Array a -> Ptr a touchArray :: Array a -> IO () withArrayAsPtr :: Array a -> (Ptr a -> IO b) -> IO b instance (GHC.Classes.Eq a, Data.Primitive.Types.Prim a) => GHC.Classes.Eq (Streamly.Internal.Data.Array.Prim.Pinned.Type.Array a) instance (GHC.Classes.Ord a, Data.Primitive.Types.Prim a) => GHC.Classes.Ord (Streamly.Internal.Data.Array.Prim.Pinned.Type.Array a) instance Data.Primitive.Types.Prim a => GHC.Base.Semigroup (Streamly.Internal.Data.Array.Prim.Pinned.Type.Array a) instance Data.Primitive.Types.Prim a => GHC.Base.Monoid (Streamly.Internal.Data.Array.Prim.Pinned.Type.Array a) instance Control.DeepSeq.NFData (Streamly.Internal.Data.Array.Prim.Pinned.Type.Array a) instance (GHC.Show.Show a, Data.Primitive.Types.Prim a) => GHC.Show.Show (Streamly.Internal.Data.Array.Prim.Pinned.Type.Array a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString (Streamly.Internal.Data.Array.Prim.Pinned.Type.Array a) instance Data.Primitive.Types.Prim a => GHC.Exts.IsList (Streamly.Internal.Data.Array.Prim.Pinned.Type.Array a) instance (Data.Primitive.Types.Prim a, GHC.Read.Read a, GHC.Show.Show a) => GHC.Read.Read (Streamly.Internal.Data.Array.Prim.Pinned.Type.Array a) module Streamly.Internal.Data.Array.Prim.Pinned data Array a fromListN :: Prim a => Int -> [a] -> Array a fromList :: Prim a => [a] -> Array a -- | Create an Array from the first N elements of a stream. The -- array is allocated to size N, if the stream terminates before N -- elements then the array may hold less than N elements. -- -- Pre-release fromStreamN :: (MonadIO m, Prim a) => Int -> SerialT m a -> m (Array a) -- | Create an Array from a stream. This is useful when we want to -- create a single array from a stream of unknown size. writeN -- is at least twice as efficient when the size is already known. -- -- Note that if the input stream is too large memory allocation for the -- array may fail. When the stream size is not known, arraysOf -- followed by processing of indvidual arrays in the resulting stream -- should be preferred. -- -- Pre-release fromStream :: (MonadIO m, Prim a) => SerialT m a -> m (Array a) -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- -- Pre-release writeN :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Caution! Do not use this on infinite streams. -- -- Pre-release write :: (MonadIO m, Prim a) => Fold m a (Array a) -- | Convert an Array into a list. -- -- Pre-release toList :: Prim a => Array a -> [a] -- | Convert an Array into a stream. -- -- Pre-release toStream :: (MonadIO m, Prim a) => Array a -> SerialT m a -- | Convert an Array into a stream in reverse order. -- -- Pre-release toStreamRev :: (MonadIO m, Prim a) => Array a -> SerialT m a -- | Unfold an array into a stream. read :: (MonadIO m, Prim a) => Unfold m (Array a) a -- | Unfold an array into a stream, does not check the end of the array, -- the user is responsible for terminating the stream within the array -- bounds. For high performance application where the end condition can -- be determined by a terminating fold. -- -- The following might not be true, not that the representation changed. -- Written in the hope that it may be faster than "read", however, in the -- case for which this was written, "read" proves to be faster even -- though the core generated with unsafeRead looks simpler. -- -- Pre-release unsafeRead :: (MonadIO m, Prim a) => Unfold m (Array a) a length :: Array a -> Int -- |
--   null arr = length arr == 0
--   
-- -- Pre-release null :: Array a -> Bool -- |
--   last arr = readIndex arr (length arr - 1)
--   
-- -- Pre-release last :: Prim a => Array a -> Maybe a -- | O(1) Lookup the element at the given index, starting from 0. -- -- Pre-release readIndex :: Prim a => Array a -> Int -> Maybe a unsafeIndex :: Prim a => Array a -> Int -> a -- | Fold an array using a stream fold operation. -- -- Pre-release streamFold :: (MonadIO m, Prim a) => (SerialT m a -> m b) -> Array a -> m b -- | Fold an array using a Fold. -- -- Pre-release fold :: forall m a b. (MonadIO m, Prim a) => Fold m a b -> Array a -> m b -- | Convert a stream of arrays into a stream of their elements. -- -- Same as the following but more efficient: -- --
--   concat = S.concatMap A.read
--   
-- -- Pre-release concat :: (MonadIO m, Prim a) => SerialT m (Array a) -> SerialT m a -- | Coalesce adjacent arrays in incoming stream to form bigger arrays of a -- maximum specified size in bytes. -- -- Pre-release compact :: (MonadIO m, Prim a) => Int -> SerialT m (Array a) -> SerialT m (Array a) module Streamly.Internal.Data.Array.Prim.Mut.Type data Array a Array :: MutableByteArray# RealWorld -> Array a -- | Allocate an array that is unpinned and can hold count items. -- The memory of the array is uninitialized. -- -- Note that this is internal routine, the reference to this array cannot -- be given out until the array has been written to and frozen. newArray :: forall m a. (MonadIO m, Prim a) => Int -> m (Array a) unsafeWriteIndex :: (MonadIO m, Prim a) => Array a -> Int -> a -> m () spliceTwo :: (MonadIO m, Prim a) => Array a -> Array a -> m (Array a) -- | Copy a range of the first array to the specified region in the second -- array. Both arrays must fully contain the specified ranges, but this -- is not checked. The regions are allowed to overlap, although this is -- only possible when the same array is provided as both the source and -- the destination. unsafeCopy :: forall m a. (MonadIO m, Prim a) => Array a -> Int -> Array a -> Int -> Int -> m () fromListM :: (MonadIO m, Prim a) => [a] -> m (Array a) fromListNM :: (MonadIO m, Prim a) => Int -> [a] -> m (Array a) fromStreamDN :: (MonadIO m, Prim a) => Int -> Stream m a -> m (Array a) fromStreamD :: (MonadIO m, Prim a) => Stream m a -> m (Array a) -- | fromStreamArraysOf n stream groups the input stream into a -- stream of arrays of size n. fromStreamDArraysOf :: (MonadIO m, Prim a) => Int -> Stream m a -> Stream m (Array a) -- | Coalesce adjacent arrays in incoming stream to form bigger arrays of a -- maximum specified size in bytes. Note that if a single array is bigger -- than the specified size we do not split it to fit. When we coalesce -- multiple arrays if the size would exceed the specified size we do not -- coalesce therefore the actual array size may be less than the -- specified chunk size. -- -- Pre-release packArraysChunksOf :: (MonadIO m, Prim a) => Int -> Stream m (Array a) -> Stream m (Array a) lpackArraysChunksOf :: (MonadIO m, Prim a) => Int -> Fold m (Array a) () -> Fold m (Array a) () unsafeReadIndex :: (MonadIO m, Prim a) => Array a -> Int -> m a length :: forall m a. (MonadIO m, Prim a) => Array a -> m Int byteLength :: MonadIO m => Array a -> m Int -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- -- Pre-release writeN :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) data ArrayUnsafe a ArrayUnsafe :: {-# UNPACK #-} !Array a -> {-# UNPACK #-} !Int -> ArrayUnsafe a -- | Like writeN but does not check the array bounds when writing. -- The fold driver must not call the step function more than n -- times otherwise it will corrupt the memory and crash. This function -- exists mainly because any conditional in the step function blocks -- fusion causing 10x performance slowdown. -- -- Pre-release writeNUnsafe :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Caution! Do not use this on infinite streams. -- -- Pre-release write :: (MonadIO m, Prim a) => Fold m a (Array a) -- | Resize (unpinned) mutable byte array to new specified size (in elem -- count). The returned array is either the original array resized -- in-place or, if not possible, a newly allocated (unpinned) array (with -- the original content copied over). resizeArray :: forall m a. (MonadIO m, Prim a) => Array a -> Int -> m (Array a) shrinkArray :: forall m a. (MonadIO m, Prim a) => Array a -> Int -> m () module Streamly.Internal.Data.Array.Prim.Type data Array a Array :: ByteArray# -> Int -> Int -> Array a unsafeFreeze :: (Prim a, MonadIO m) => Array a -> m (Array a) unsafeFreezeWithShrink :: (Prim a, MonadIO m) => Array a -> Int -> m (Array a) -- | Default maximum buffer size in bytes, for reading from and writing to -- IO devices, the value is 32KB minus GHC allocation overhead, which is -- a few bytes, so that the actual allocation is 32KB. defaultChunkSize :: Int nil :: Prim a => Array a -- | Splice two immutable arrays creating a new immutable array. spliceTwo :: (MonadIO m, Prim a) => Array a -> Array a -> m (Array a) fromList :: Prim a => [a] -> Array a fromListN :: Prim a => Int -> [a] -> Array a fromStreamDN :: (MonadIO m, Prim a) => Int -> Stream m a -> m (Array a) fromStreamD :: (MonadIO m, Prim a) => Stream m a -> m (Array a) -- | fromStreamArraysOf n stream groups the input stream into a -- stream of arrays of size n. fromStreamDArraysOf :: (MonadIO m, Prim a) => Int -> Stream m a -> Stream m (Array a) data FlattenState s a OuterLoop :: s -> FlattenState s a InnerLoop :: s -> !Array a -> !Int -> !Int -> FlattenState s a flattenArrays :: (MonadIO m, Prim a) => Stream m (Array a) -> Stream m a flattenArraysRev :: (MonadIO m, Prim a) => Stream m (Array a) -> Stream m a data SpliceState s arr1 arr2 SpliceInitial :: s -> SpliceState s arr1 arr2 SpliceBuffering :: s -> arr2 -> SpliceState s arr1 arr2 SpliceYielding :: arr1 -> SpliceState s arr1 arr2 -> SpliceState s arr1 arr2 SpliceFinish :: SpliceState s arr1 arr2 -- | Coalesce adjacent arrays in incoming stream to form bigger arrays of a -- maximum specified size in bytes. Note that if a single array is bigger -- than the specified size we do not split it to fit. When we coalesce -- multiple arrays if the size would exceed the specified size we do not -- coalesce therefore the actual array size may be less than the -- specified chunk size. -- -- Pre-release packArraysChunksOf :: forall m a. (MonadIO m, Prim a) => Int -> Stream m (Array a) -> Stream m (Array a) lpackArraysChunksOf :: forall m a. (MonadIO m, Prim a) => Int -> Fold m (Array a) () -> Fold m (Array a) () -- | Split a stream of arrays on a given separator byte, dropping the -- separator and coalescing all the arrays between two separators into a -- single array. -- -- Pre-release splitOn :: MonadIO m => Word8 -> Stream m (Array Word8) -> Stream m (Array Word8) breakOn :: MonadIO m => Word8 -> Array Word8 -> m (Array Word8, Maybe (Array Word8)) unsafeIndex :: Prim a => Array a -> Int -> a byteLength :: forall a. Prim a => Array a -> Int length :: Array a -> Int -- | Strict left-associated fold over the elements of an Array. foldl' :: Prim a => (b -> a -> b) -> b -> Array a -> b foldr :: Prim a => (a -> b -> b) -> b -> Array a -> b -- | Strict right-associated fold over the elements of an Array. foldr' :: Prim a => (a -> b -> b) -> b -> Array a -> b -- | Strict left-associated fold over the elements of an Array. foldlM' :: (Prim a, Monad m) => (b -> a -> m b) -> b -> Array a -> m b -- | splitAt n xs returns a tuple where first element is -- xs prefix of length n and second element is the -- remainder of the list: -- --
--   splitAt 6 "Hello World!" == ("Hello ","World!")
--   splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5])
--   splitAt 1 [1,2,3] == ([1],[2,3])
--   splitAt 3 [1,2,3] == ([1,2,3],[])
--   splitAt 4 [1,2,3] == ([1,2,3],[])
--   splitAt 0 [1,2,3] == ([],[1,2,3])
--   splitAt (-1) [1,2,3] == ([],[1,2,3])
--   
-- -- It is equivalent to (take n xs, drop n xs) when -- n is not _|_ (splitAt _|_ xs = _|_). -- splitAt is an instance of the more general -- genericSplitAt, in which n may be of any integral -- type. splitAt :: Int -> [a] -> ([a], [a]) toStreamD :: (Prim a, Monad m) => Array a -> Stream m a toStreamDRev :: (Prim a, Monad m) => Array a -> Stream m a toStreamK :: Prim a => Array a -> Stream m a toStreamKRev :: Prim a => Array a -> Stream m a -- | Convert an Array into a list. -- -- Pre-release toList :: Prim a => Array a -> [a] -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- -- Pre-release writeN :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) data ArrayUnsafe a ArrayUnsafe :: {-# UNPACK #-} !Array a -> {-# UNPACK #-} !Int -> ArrayUnsafe a -- | Like writeN but does not check the array bounds when writing. -- The fold driver must not call the step function more than n -- times otherwise it will corrupt the memory and crash. This function -- exists mainly because any conditional in the step function blocks -- fusion causing 10x performance slowdown. -- -- Pre-release writeNUnsafe :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Caution! Do not use this on infinite streams. -- -- Pre-release write :: (MonadIO m, Prim a) => Fold m a (Array a) unlines :: (MonadIO m, Prim a) => a -> Stream m (Array a) -> Stream m a instance (GHC.Classes.Eq a, Data.Primitive.Types.Prim a) => GHC.Classes.Eq (Streamly.Internal.Data.Array.Prim.Type.Array a) instance (GHC.Classes.Ord a, Data.Primitive.Types.Prim a) => GHC.Classes.Ord (Streamly.Internal.Data.Array.Prim.Type.Array a) instance Data.Primitive.Types.Prim a => GHC.Base.Semigroup (Streamly.Internal.Data.Array.Prim.Type.Array a) instance Data.Primitive.Types.Prim a => GHC.Base.Monoid (Streamly.Internal.Data.Array.Prim.Type.Array a) instance Control.DeepSeq.NFData (Streamly.Internal.Data.Array.Prim.Type.Array a) instance (GHC.Show.Show a, Data.Primitive.Types.Prim a) => GHC.Show.Show (Streamly.Internal.Data.Array.Prim.Type.Array a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString (Streamly.Internal.Data.Array.Prim.Type.Array a) instance Data.Primitive.Types.Prim a => GHC.Exts.IsList (Streamly.Internal.Data.Array.Prim.Type.Array a) instance (Data.Primitive.Types.Prim a, GHC.Read.Read a, GHC.Show.Show a) => GHC.Read.Read (Streamly.Internal.Data.Array.Prim.Type.Array a) module Streamly.Internal.Data.Array.Prim data Array a fromListN :: Prim a => Int -> [a] -> Array a fromList :: Prim a => [a] -> Array a -- | Create an Array from the first N elements of a stream. The -- array is allocated to size N, if the stream terminates before N -- elements then the array may hold less than N elements. -- -- Pre-release fromStreamN :: (MonadIO m, Prim a) => Int -> SerialT m a -> m (Array a) -- | Create an Array from a stream. This is useful when we want to -- create a single array from a stream of unknown size. writeN -- is at least twice as efficient when the size is already known. -- -- Note that if the input stream is too large memory allocation for the -- array may fail. When the stream size is not known, arraysOf -- followed by processing of indvidual arrays in the resulting stream -- should be preferred. -- -- Pre-release fromStream :: (MonadIO m, Prim a) => SerialT m a -> m (Array a) -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- -- Pre-release writeN :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Caution! Do not use this on infinite streams. -- -- Pre-release write :: (MonadIO m, Prim a) => Fold m a (Array a) -- | Convert an Array into a list. -- -- Pre-release toList :: Prim a => Array a -> [a] -- | Convert an Array into a stream. -- -- Pre-release toStream :: (MonadIO m, Prim a) => Array a -> SerialT m a -- | Convert an Array into a stream in reverse order. -- -- Pre-release toStreamRev :: (MonadIO m, Prim a) => Array a -> SerialT m a -- | Unfold an array into a stream. read :: (MonadIO m, Prim a) => Unfold m (Array a) a -- | Unfold an array into a stream, does not check the end of the array, -- the user is responsible for terminating the stream within the array -- bounds. For high performance application where the end condition can -- be determined by a terminating fold. -- -- The following might not be true, not that the representation changed. -- Written in the hope that it may be faster than "read", however, in the -- case for which this was written, "read" proves to be faster even -- though the core generated with unsafeRead looks simpler. -- -- Pre-release unsafeRead :: (MonadIO m, Prim a) => Unfold m (Array a) a length :: Array a -> Int -- |
--   null arr = length arr == 0
--   
-- -- Pre-release null :: Array a -> Bool -- |
--   last arr = readIndex arr (length arr - 1)
--   
-- -- Pre-release last :: Prim a => Array a -> Maybe a -- | O(1) Lookup the element at the given index, starting from 0. -- -- Pre-release readIndex :: Prim a => Array a -> Int -> Maybe a unsafeIndex :: Prim a => Array a -> Int -> a -- | Fold an array using a stream fold operation. -- -- Pre-release streamFold :: (MonadIO m, Prim a) => (SerialT m a -> m b) -> Array a -> m b -- | Fold an array using a Fold. -- -- Pre-release fold :: forall m a b. (MonadIO m, Prim a) => Fold m a b -> Array a -> m b -- | Convert a stream of arrays into a stream of their elements. -- -- Same as the following but more efficient: -- --
--   concat = S.concatMap A.read
--   
-- -- Pre-release concat :: (MonadIO m, Prim a) => SerialT m (Array a) -> SerialT m a -- | Coalesce adjacent arrays in incoming stream to form bigger arrays of a -- maximum specified size in bytes. -- -- Pre-release compact :: (MonadIO m, Prim a) => Int -> SerialT m (Array a) -> SerialT m (Array a) module Streamly.Internal.Data.Array -- | Boxed arrays. data Array a Array :: Array# a -> Array a [array#] :: Array a -> Array# a nil :: Array a writeN :: MonadIO m => Int -> Fold m a (Array a) write :: MonadIO m => Fold m a (Array a) writeLastN :: MonadIO m => Int -> Fold m a (Array a) fromStreamDN :: MonadIO m => Int -> Stream m a -> m (Array a) fromStreamD :: MonadIO m => Stream m a -> m (Array a) fromStreamN :: MonadIO m => Int -> SerialT m a -> m (Array a) fromStream :: MonadIO m => SerialT m a -> m (Array a) fromListN :: Int -> [a] -> Array a fromList :: [a] -> Array a length :: Array a -> Int read :: Monad m => Unfold m (Array a) a toStreamD :: Monad m => Array a -> Stream m a toStreamDRev :: Monad m => Array a -> Stream m a toStream :: Monad m => Array a -> SerialT m a toStreamRev :: Monad m => Array a -> SerialT m a foldl' :: (b -> a -> b) -> b -> Array a -> b foldr :: (a -> b -> b) -> b -> Array a -> b streamFold :: Monad m => (SerialT m a -> m b) -> Array a -> m b fold :: Monad m => Fold m a b -> Array a -> m b -- | O(1) Lookup the element at the given index. Index starts from -- 0. Does not check the bounds. getIndexUnsafe :: Array a -> Int -> a -- | Truncate the array at the beginning and end as long as the predicate -- holds true. strip :: (a -> Bool) -> Array a -> Array a -- | Bottom level IsStream module that can be used by all other upper level -- IsStream modules. module Streamly.Internal.Data.Stream.IsStream.Common -- |
--   fromPure a = a `cons` nil
--   
-- -- Create a singleton stream from a pure value. -- -- The following holds in monadic streams, but not in Zip streams: -- --
--   fromPure = pure
--   fromPure = fromEffect . pure
--   
-- -- In Zip applicative streams fromPure is not the same as -- pure because in that case pure is equivalent to -- repeat instead. fromPure and pure are equally -- efficient, in other cases fromPure may be slightly more -- efficient than the other equivalent definitions. -- -- Since: 0.8.0 (Renamed yield to fromPure) fromPure :: IsStream t => a -> t m a -- |
--   fromEffect m = m `consM` nil
--   
-- -- Create a singleton stream from a monadic action. -- --
--   > Stream.toList $ Stream.fromEffect getLine
--   hello
--   ["hello"]
--   
-- -- Since: 0.8.0 (Renamed yieldM to fromEffect) fromEffect :: (Monad m, IsStream t) => m a -> t m a -- |
--   >>> repeatM = fix . consM
--   
--   >>> repeatM = cycle1 . fromEffect
--   
-- -- Generate a stream by repeatedly executing a monadic action forever. -- --
--   >>> :{
--   repeatAsync =
--          Stream.repeatM (threadDelay 1000000 >> print 1)
--        & Stream.take 10
--        & Stream.fromAsync
--        & Stream.drain
--   :}
--   
-- -- Concurrent, infinite (do not use with fromParallel) repeatM :: (IsStream t, MonadAsync m) => m a -> t m a -- | timesWith g returns a stream of time value tuples. The first -- component of the tuple is an absolute time reference (epoch) denoting -- the start of the stream and the second component is a time relative to -- the reference. -- -- The argument g specifies the granularity of the relative time -- in seconds. A lower granularity clock gives higher precision but is -- more expensive in terms of CPU usage. Any granularity lower than 1 ms -- is treated as 1 ms. -- --
--   >>> import Control.Concurrent (threadDelay)
--   
--   >>> import Streamly.Internal.Data.Stream.IsStream.Common as Stream (timesWith)
--   
--   >>> Stream.mapM_ (\x -> print x >> threadDelay 1000000) $ Stream.take 3 $ Stream.timesWith 0.01
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
--   
-- -- Note: This API is not safe on 32-bit machines. -- -- Pre-release timesWith :: (IsStream t, MonadAsync m) => Double -> t m (AbsTime, RelTime64) -- | absTimesWith g returns a stream of absolute timestamps using -- a clock of granularity g specified in seconds. A low -- granularity clock is more expensive in terms of CPU usage. Any -- granularity lower than 1 ms is treated as 1 ms. -- --
--   >>> Stream.mapM_ print $ Stream.delayPre 1 $ Stream.take 3 $ absTimesWith 0.01
--   AbsTime (TimeSpec {sec = ..., nsec = ...})
--   AbsTime (TimeSpec {sec = ..., nsec = ...})
--   AbsTime (TimeSpec {sec = ..., nsec = ...})
--   
-- -- Note: This API is not safe on 32-bit machines. -- -- Pre-release absTimesWith :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m AbsTime -- | relTimesWith g returns a stream of relative time values -- starting from 0, using a clock of granularity g specified in -- seconds. A low granularity clock is more expensive in terms of CPU -- usage. Any granularity lower than 1 ms is treated as 1 ms. -- --
--   >>> Stream.mapM_ print $ Stream.delayPre 1 $ Stream.take 3 $ Stream.relTimesWith 0.01
--   RelTime64 (NanoSecond64 ...)
--   RelTime64 (NanoSecond64 ...)
--   RelTime64 (NanoSecond64 ...)
--   
-- -- Note: This API is not safe on 32-bit machines. -- -- Pre-release relTimesWith :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m RelTime64 -- | We can create higher order folds using foldOn. We can fold a -- number of streams to a given fold efficiently with full stream fusion. -- For example, to fold a list of streams on the same sum fold: -- --
--   >>> concatFold = Prelude.foldl Stream.foldOn Fold.sum
--   
-- --
--   >>> fold f = Fold.finish . Stream.foldOn f
--   
-- -- Internal foldOn :: Monad m => Fold m a b -> SerialT m a -> Fold m a b -- | Fold a stream using the supplied left Fold and reducing the -- resulting expression strictly at each step. The behavior is similar to -- foldl'. A Fold can terminate early without consuming -- the full stream. See the documentation of individual Folds for -- termination behavior. -- --
--   >>> Stream.fold Fold.sum (Stream.enumerateFromTo 1 100)
--   5050
--   
-- -- Folds never fail, therefore, they produce a default value even when no -- input is provided. It means we can always fold an empty stream and get -- a valid result. For example: -- --
--   >>> Stream.fold Fold.sum Stream.nil
--   0
--   
-- -- However, foldMany on an empty stream results in an empty -- stream. Therefore, Stream.fold f is not the same as -- Stream.head . Stream.foldMany f. -- --
--   fold f = Stream.parse (Parser.fromFold f)
--   
fold :: Monad m => Fold m a b -> SerialT m a -> m b fold_ :: Monad m => Fold m a b -> SerialT m a -> m (b, SerialT m a) -- |
--   map = fmap
--   
-- -- Same as fmap. -- --
--   > S.toList $ S.map (+1) $ S.fromList [1,2,3]
--   [2,3,4]
--   
map :: (IsStream t, Monad m) => (a -> b) -> t m a -> t m b -- | scanlMAfter' accumulate initial done stream is like -- scanlM' except that it provides an additional done -- function to be applied on the accumulator when the stream stops. The -- result of done is also emitted in the stream. -- -- This function can be used to allocate a resource in the beginning of -- the scan and release it when the stream ends or to flush the internal -- state of the scan at the end. -- -- Pre-release scanlMAfter' :: (IsStream t, Monad m) => (b -> a -> m b) -> m b -> (b -> m b) -> t m a -> t m b -- | Like postscanl' but with a monadic step function and a -- monadic seed. -- --
--   >>> postscanlM' f z xs = Stream.drop 1 $ Stream.scanlM' f z xs
--   
-- -- Since: 0.7.0 -- -- Since: 0.8.0 (signature change) postscanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> m b -> t m a -> t m b -- | A stateful mapM, equivalent to a left scan, more like -- mapAccumL. Hopefully, this is a better alternative to scan. -- Separation of state from the output makes it easier to think in terms -- of a shared state, and also makes it easier to keep the state fully -- strict and the output lazy. -- -- See also: scanlM' -- -- Pre-release smapM :: (IsStream t, Monad m) => (s -> a -> m (s, b)) -> m s -> t m a -> t m b -- | Take first n elements from the stream and discard the rest. take :: (IsStream t, Monad m) => Int -> t m a -> t m a -- | End the stream as soon as the predicate fails on an element. takeWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a -- | Discard first n elements from the stream and take the rest. drop :: (IsStream t, Monad m) => Int -> t m a -> t m a -- | Find all the indices where the element in the stream satisfies the -- given predicate. -- --
--   findIndices = fold Fold.findIndices
--   
findIndices :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m Int -- | Insert an effect and its output before consuming an element of a -- stream except the first one. -- --
--   >>> Stream.toList $ Stream.trace putChar $ Stream.intersperseM (putChar '.' >> return ',') $ Stream.fromList "hello"
--   h.,e.,l.,l.,o"h,e,l,l,o"
--   
intersperseM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a -- | Intersperse a monadic action into the input stream after every -- n seconds. -- --
--   > import Control.Concurrent (threadDelay)
--   > Stream.drain $ Stream.interjectSuffix 1 (putChar ',') $ Stream.mapM (x -> threadDelay 1000000 >> putChar x) $ Stream.fromList "hello"
--   h,e,l,l,o
--   
-- -- Pre-release interjectSuffix :: (IsStream t, MonadAsync m) => Double -> m a -> t m a -> t m a -- | Returns the elements of the stream in reverse order. The stream must -- be finite. Note that this necessarily buffers the entire stream in -- memory. -- --
--   >>> reverse = Stream.foldlT (flip Stream.cons) Stream.nil
--   
-- -- Since 0.7.0 (Monad m constraint) -- -- Since: 0.1.1 reverse :: (IsStream t, Monad m) => t m a -> t m a -- | Like reverse but several times faster, requires a -- Storable instance. -- -- Pre-release reverse' :: (IsStream t, MonadIO m, Storable a) => t m a -> t m a -- | Make the stream producer and consumer run concurrently by introducing -- a buffer between them. The producer thread evaluates the input stream -- until the buffer fills, it terminates if the buffer is full and a -- worker thread is kicked off again to evaluate the remaining stream -- when there is space in the buffer. The consumer consumes the stream -- lazily from the buffer. -- -- Since: 0.2.0 (Streamly) mkAsync :: (IsStream t, MonadAsync m) => t m a -> t m a -- | Make the stream producer and consumer run concurrently by introducing -- a buffer between them. The producer thread evaluates the input stream -- until the buffer fills, it blocks if the buffer is full until there is -- space in the buffer. The consumer consumes the stream lazily from the -- buffer. -- --
--   mkParallel = IsStream.fromStreamD . mkParallelD . IsStream.toStreamD
--   
-- -- Pre-release mkParallel :: (IsStream t, MonadAsync m) => t m a -> t m a -- | Like parallel but stops the output as soon as the first -- stream stops. -- -- Pre-release parallelFst :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | Given a stream value in the underlying monad, lift and join the -- underlying monad with the stream monad. -- --
--   >>> concatM = Stream.concat . Stream.fromEffect
--   
--   >>> concatM = Stream.concat . lift    -- requires (MonadTrans t)
--   
--   >>> concatM = join . lift             -- requires (MonadTrans t, Monad (t m))
--   
-- -- See also: concat, sequence -- -- Internal concatM :: (IsStream t, Monad m) => m (t m a) -> t m a -- | Map a stream producing monadic function on each element of the stream -- and then flatten the results into a single stream. Since the stream -- generation function is monadic, unlike concatMap, it can -- produce an effect at the beginning of each iteration of the inner -- loop. concatMapM :: (IsStream t, Monad m) => (a -> m (t m b)) -> t m a -> t m b -- | Map a stream producing function on each element of the stream and then -- flatten the results into a single stream. -- --
--   >>> concatMap f = Stream.concatMapM (return . f)
--   
--   >>> concatMap f = Stream.concatMapWith Stream.serial f
--   
--   >>> concatMap f = Stream.concat . Stream.map f
--   
--   >>> concatMap f = Stream.unfoldMany (Unfold.lmap f Unfold.fromStream)
--   
concatMap :: (IsStream t, Monad m) => (a -> t m b) -> t m a -> t m b -- | Like splitOn but the separator is a sequence of elements -- instead of a single element. -- -- For illustration, let's define a function that operates on pure lists: -- --
--   >>> splitOnSeq' pat xs = Stream.toList $ Stream.splitOnSeq (Array.fromList pat) Fold.toList (Stream.fromList xs)
--   
-- --
--   >>> splitOnSeq' "" "hello"
--   ["h","e","l","l","o"]
--   
-- --
--   >>> splitOnSeq' "hello" ""
--   [""]
--   
-- --
--   >>> splitOnSeq' "hello" "hello"
--   ["",""]
--   
-- --
--   >>> splitOnSeq' "x" "hello"
--   ["hello"]
--   
-- --
--   >>> splitOnSeq' "h" "hello"
--   ["","ello"]
--   
-- --
--   >>> splitOnSeq' "o" "hello"
--   ["hell",""]
--   
-- --
--   >>> splitOnSeq' "e" "hello"
--   ["h","llo"]
--   
-- --
--   >>> splitOnSeq' "l" "hello"
--   ["he","","o"]
--   
-- --
--   >>> splitOnSeq' "ll" "hello"
--   ["he","o"]
--   
-- -- splitOnSeq is an inverse of intercalate. The following -- law always holds: -- --
--   intercalate . splitOnSeq == id
--   
-- -- The following law holds when the separator is non-empty and contains -- none of the elements present in the input lists: -- --
--   splitOnSeq . intercalate == id
--   
-- -- Pre-release splitOnSeq :: (IsStream t, MonadIO m, Storable a, Enum a, Eq a) => Array a -> Fold m a b -> t m a -> t m b -- | Like zipWith but using a monadic zipping function. zipWithM :: (IsStream t, Monad m) => (a -> b -> m c) -> t m a -> t m b -> t m c -- | Stream a is evaluated first, followed by stream b, -- the resulting elements a and b are then zipped using -- the supplied zip function and the result c is yielded to the -- consumer. -- -- If stream a or stream b ends, the zipped stream -- ends. If stream b ends first, the element a from -- previous evaluation of stream a is discarded. -- --
--   > S.toList $ S.zipWith (+) (S.fromList [1,2,3]) (S.fromList [4,5,6])
--   [5,7,9]
--   
zipWith :: (IsStream t, Monad m) => (a -> b -> c) -> t m a -> t m b -> t m c -- | Same as fromPure -- | Deprecated: Please use fromPure instead. yield :: IsStream t => a -> t m a -- | Same as fromEffect -- | Deprecated: Please use fromEffect instead. yieldM :: (Monad m, IsStream t) => m a -> t m a module Streamly.Internal.Data.Stream.IsStream.Transform -- | Use a Pipe to transform a stream. -- -- Pre-release transform :: (IsStream t, Monad m) => Pipe m a b -> t m a -> t m b -- | Right fold to a streaming monad. -- --
--   foldrS Stream.cons Stream.nil === id
--   
-- -- foldrS can be used to perform stateless stream to stream -- transformations like map and filter in general. It can be coupled with -- a scan to perform stateful transformations. However, note that the -- custom map and filter routines can be much more efficient than this -- due to better stream fusion. -- --
--   >>> Stream.toList $ Stream.foldrS Stream.cons Stream.nil $ Stream.fromList [1..5]
--   [1,2,3,4,5]
--   
-- -- Find if any element in the stream is True: -- --
--   >>> Stream.toList $ Stream.foldrS (\x xs -> if odd x then return True else xs) (return False) $ (Stream.fromList (2:4:5:undefined) :: Stream.SerialT IO Int)
--   [True]
--   
-- -- Map (+2) on odd elements and filter out the even elements: -- --
--   >>> Stream.toList $ Stream.foldrS (\x xs -> if odd x then (x + 2) `Stream.cons` xs else xs) Stream.nil $ (Stream.fromList [1..5] :: Stream.SerialT IO Int)
--   [3,5,7]
--   
-- -- foldrM can also be represented in terms of foldrS, -- however, the former is much more efficient: -- --
--   foldrM f z s = runIdentityT $ foldrS (\x xs -> lift $ f x (runIdentityT xs)) (lift z) s
--   
-- -- Pre-release foldrS :: IsStream t => (a -> t m b -> t m b) -> t m b -> t m a -> t m b foldrSShared :: IsStream t => (a -> t m b -> t m b) -> t m b -> t m a -> t m b -- | Right fold to a transformer monad. This is the most general right fold -- function. foldrS is a special case of foldrT, however -- foldrS implementation can be more efficient: -- --
--   foldrS = foldrT
--   foldrM f z s = runIdentityT $ foldrT (\x xs -> lift $ f x (runIdentityT xs)) (lift z) s
--   
-- -- foldrT can be used to translate streamly streams to other -- transformer monads e.g. to a different streaming type. -- -- Pre-release foldrT :: (IsStream t, Monad m, Monad (s m), MonadTrans s) => (a -> s m b -> s m b) -> s m b -> t m a -> s m b -- |
--   map = fmap
--   
-- -- Same as fmap. -- --
--   > S.toList $ S.map (+1) $ S.fromList [1,2,3]
--   [2,3,4]
--   
map :: (IsStream t, Monad m) => (a -> b) -> t m a -> t m b -- |
--   sequence = mapM id
--   
-- -- Replace the elements of a stream of monadic actions with the outputs -- of those actions. -- --
--   >>> drain $ Stream.sequence $ Stream.fromList [putStr "a", putStr "b", putStrLn "c"]
--   abc
--   
--   >>> :{
--   drain $ Stream.replicateM 3 (return $ threadDelay 1000000 >> print 1)
--    & (fromSerial . Stream.sequence)
--   :}
--   1
--   1
--   1
--   
--   >>> :{
--   drain $ Stream.replicateM 3 (return $ threadDelay 1000000 >> print 1)
--    & (fromAsync . Stream.sequence)
--   :}
--   1
--   1
--   1
--   
-- -- Concurrent (do not use with fromParallel on infinite -- streams) sequence :: (IsStream t, MonadAsync m) => t m (m a) -> t m a -- |
--   mapM f = sequence . map f
--   
-- -- Apply a monadic function to each element of the stream and replace it -- with the output of the resulting action. -- --
--   >>> drain $ Stream.mapM putStr $ Stream.fromList ["a", "b", "c"]
--   abc
--   
--   >>> :{
--      drain $ Stream.replicateM 10 (return 1)
--        & (fromSerial . Stream.mapM (x -> threadDelay 1000000 >> print x))
--   :}
--   1
--   ...
--   1
--   
--   > drain $ Stream.replicateM 10 (return 1)
--    & (fromAsync . Stream.mapM (x -> threadDelay 1000000 >> print x))
--   
-- -- Concurrent (do not use with fromParallel on infinite -- streams) mapM :: forall t m a b. (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m b -- | A stateful mapM, equivalent to a left scan, more like -- mapAccumL. Hopefully, this is a better alternative to scan. -- Separation of state from the output makes it easier to think in terms -- of a shared state, and also makes it easier to keep the state fully -- strict and the output lazy. -- -- See also: scanlM' -- -- Pre-release smapM :: (IsStream t, Monad m) => (s -> a -> m (s, b)) -> m s -> t m a -> t m b -- | Apply a monadic function to each element flowing through the stream -- and discard the results. -- --
--   >>> Stream.drain $ Stream.trace print (Stream.enumerateFromTo 1 2)
--   1
--   2
--   
-- -- Compare with tap. trace :: (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m a -- | Perform a side effect before yielding each element of the stream and -- discard the results. -- --
--   >>> Stream.drain $ Stream.trace_ (print "got here") (Stream.enumerateFromTo 1 2)
--   "got here"
--   "got here"
--   
-- -- Same as interspersePrefix_ but always serial. -- -- See also: trace -- -- Pre-release trace_ :: (IsStream t, Monad m) => m b -> t m a -> t m a -- | Tap the data flowing through a stream into a Fold. For example, -- you may add a tap to log the contents flowing through the stream. The -- fold is used only for effects, its result is discarded. -- --
--                     Fold m a b
--                         |
--   -----stream m a ---------------stream m a-----
--   
-- --
--   >>> Stream.drain $ Stream.tap (Fold.drainBy print) (Stream.enumerateFromTo 1 2)
--   1
--   2
--   
-- -- Compare with trace. tap :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m a -- | tapOffsetEvery offset n taps every nth element in -- the stream starting at offset. offset can be between -- 0 and n - 1. Offset 0 means start at the first -- element in the stream. If the offset is outside this range then -- offset mod n is used as offset. -- --
--   >>> Stream.drain $ Stream.tapOffsetEvery 0 2 (Fold.rmapM print Fold.toList) $ Stream.enumerateFromTo 0 10
--   [0,2,4,6,8,10]
--   
tapOffsetEvery :: (IsStream t, Monad m) => Int -> Int -> Fold m a b -> t m a -> t m a -- | Redirect a copy of the stream to a supplied fold and run it -- concurrently in an independent thread. The fold may buffer some -- elements. The buffer size is determined by the prevailing -- maxBuffer setting. -- --
--                 Stream m a -> m b
--                         |
--   -----stream m a ---------------stream m a-----
--   
-- --
--   >>> Stream.drain $ Stream.tapAsync (Fold.drainBy print) (Stream.enumerateFromTo 1 2)
--   1
--   2
--   
-- -- Exceptions from the concurrently running fold are propagated to the -- current computation. Note that, because of buffering in the fold, -- exceptions may be delayed and may not correspond to the current -- element being processed in the parent stream, but we guarantee that -- before the parent stream stops the tap finishes and all exceptions -- from it are drained. -- -- Compare with tap. -- -- Pre-release tapAsync :: (IsStream t, MonadAsync m) => Fold m a b -> t m a -> t m a -- | Redirect a copy of the stream to a supplied fold and run it -- concurrently in an independent thread. The fold may buffer some -- elements. The buffer size is determined by the prevailing -- maxBuffer setting. -- --
--                 Stream m a -> m b
--                         |
--   -----stream m a ---------------stream m a-----
--   
-- --
--   > S.drain $ S.tapAsync (S.mapM_ print) (S.enumerateFromTo 1 2)
--   1
--   2
--   
-- -- Exceptions from the concurrently running fold are propagated to the -- current computation. Note that, because of buffering in the fold, -- exceptions may be delayed and may not correspond to the current -- element being processed in the parent stream, but we guarantee that -- before the parent stream stops the tap finishes and all exceptions -- from it are drained. -- -- Compare with tap. -- -- Pre-release tapAsyncK :: (IsStream t, MonadAsync m) => (t m a -> m b) -> t m a -> t m a -- | Concurrently distribute a stream to a collection of fold functions, -- discarding the outputs of the folds. -- --
--   > Stream.drain $ Stream.distributeAsync_ [Stream.mapM_ print, Stream.mapM_ print] (Stream.enumerateFromTo 1 2)
--   1
--   2
--   1
--   2
--   
-- --
--   distributeAsync_ = flip (foldr tapAsync)
--   
-- -- Pre-release distributeAsync_ :: (Foldable f, IsStream t, MonadAsync m) => f (t m a -> m b) -> t m a -> t m a -- | Calls the supplied function with the number of elements consumed every -- n seconds. The given function is run in a separate thread -- until the end of the stream. In case there is an exception in the -- stream the thread is killed during the next major GC. -- -- Note: The action is not guaranteed to run if the main thread exits. -- --
--   > delay n = threadDelay (round $ n * 1000000) >> return n
--   > Stream.toList $ Stream.tapRate 2 (n -> print $ show n ++ " elements processed") (delay 1 Stream.|: delay 0.5 Stream.|: delay 0.5 Stream.|: Stream.nil)
--   "2 elements processed"
--   [1.0,0.5,0.5]
--   "1 elements processed"
--   
-- -- Note: This may not work correctly on 32-bit machines. -- -- Pre-release tapRate :: (IsStream t, MonadAsync m, MonadCatch m) => Double -> (Int -> m b) -> t m a -> t m a -- | pollCounts predicate transform fold stream counts those -- elements in the stream that pass the predicate. The resulting -- count stream is sent to another thread which transforms it using -- transform and then folds it using fold. The thread -- is automatically cleaned up if the stream stops or aborts due to -- exception. -- -- For example, to print the count of elements processed every second: -- --
--   > Stream.drain $ Stream.pollCounts (const True) (Stream.rollingMap (-) . Stream.delayPost 1) (FLold.drainBy print)
--             $ Stream.enumerateFrom 0
--   
-- -- Note: This may not work correctly on 32-bit machines. -- -- Pre-release pollCounts :: (IsStream t, MonadAsync m) => (a -> Bool) -> (t m Int -> t m Int) -> Fold m Int b -> t m a -> t m a -- | Scan a stream using the given monadic fold. -- --
--   >>> Stream.toList $ Stream.takeWhile (< 10) $ Stream.scan Fold.sum (Stream.fromList [1..10])
--   [0,1,3,6]
--   
scan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | Postscan a stream using the given monadic fold. -- -- The following example extracts the input stream up to a point where -- the running average of elements is no more than 10: -- --
--   >>> import Data.Maybe (fromJust)
--   
--   >>> let avg = Fold.teeWith (/) Fold.sum (fmap fromIntegral Fold.length)
--   
--   >>> :{
--    Stream.toList
--     $ Stream.map (fromJust . fst)
--     $ Stream.takeWhile (\(_,x) -> x <= 10)
--     $ Stream.postscan (Fold.tee Fold.last avg) (Stream.enumerateFromTo 1.0 100.0)
--   :}
--   [1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0,16.0,17.0,18.0,19.0]
--   
postscan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | Strict left scan. Like map, scanl' too is a one to one -- transformation, however it adds an extra element. -- --
--   >>> Stream.toList $ Stream.scanl' (+) 0 $ fromList [1,2,3,4]
--   [0,1,3,6,10]
--   
-- --
--   >>> Stream.toList $ Stream.scanl' (flip (:)) [] $ Stream.fromList [1,2,3,4]
--   [[],[1],[2,1],[3,2,1],[4,3,2,1]]
--   
-- -- The output of scanl' is the initial value of the accumulator -- followed by all the intermediate steps and the final result of -- foldl'. -- -- By streaming the accumulated state after each fold step, we can share -- the state across multiple stages of stream composition. Each stage can -- modify or extend the state, do some processing with it and emit it for -- the next stage, thus modularizing the stream processing. This can be -- useful in stateful or event-driven programming. -- -- Consider the following monolithic example, computing the sum and the -- product of the elements in a stream in one go using a foldl': -- --
--   >>> Stream.foldl' ((s, p) x -> (s + x, p * x)) (0,1) $ Stream.fromList 1,2,3,4
--   
-- -- Using scanl' we can make it modular by computing the sum in -- the first stage and passing it down to the next stage for computing -- the product: -- --
--   >>> :{
--     Stream.foldl' ((_, p) (s, x) -> (s, p * x)) (0,1)
--     $ Stream.scanl' ((s, _) x -> (s + x, x)) (0,1)
--     $ Stream.fromList [1,2,3,4]
--   :}
--   (10,24)
--   
-- -- IMPORTANT: scanl' evaluates the accumulator to WHNF. To avoid -- building lazy expressions inside the accumulator, it is recommended -- that a strict data structure is used for accumulator. -- --
--   >>> scanl' f z xs = scanlM' (\a b -> return (f a b)) (return z) xs
--   
--   >>> scanl' f z xs = z `Stream.cons` postscanl' f z xs
--   
-- -- See also: usingStateT scanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b -- | Like scanl' but with a monadic step function and a monadic -- seed. -- -- Since: 0.4.0 -- -- Since: 0.8.0 (signature change) scanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> m b -> t m a -> t m b -- | scanlMAfter' accumulate initial done stream is like -- scanlM' except that it provides an additional done -- function to be applied on the accumulator when the stream stops. The -- result of done is also emitted in the stream. -- -- This function can be used to allocate a resource in the beginning of -- the scan and release it when the stream ends or to flush the internal -- state of the scan at the end. -- -- Pre-release scanlMAfter' :: (IsStream t, Monad m) => (b -> a -> m b) -> m b -> (b -> m b) -> t m a -> t m b -- | Like scanl' but does not stream the initial value of the -- accumulator. -- --
--   >>> postscanl' f z = postscanlM' (\a b -> return (f a b)) (return z)
--   
--   >>> postscanl' f z xs = Stream.drop 1 $ Stream.scanl' f z xs
--   
postscanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b -- | Like postscanl' but with a monadic step function and a -- monadic seed. -- --
--   >>> postscanlM' f z xs = Stream.drop 1 $ Stream.scanlM' f z xs
--   
-- -- Since: 0.7.0 -- -- Since: 0.8.0 (signature change) postscanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> m b -> t m a -> t m b -- | Like scanl' but does not stream the final value of the accumulator. -- -- Pre-release prescanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b -- | Like prescanl' but with a monadic step function and a monadic seed. -- -- Pre-release prescanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> m b -> t m a -> t m b -- | Like scanl' but for a non-empty stream. The first element of -- the stream is used as the initial value of the accumulator. Does -- nothing if the stream is empty. -- --
--   >>> Stream.toList $ Stream.scanl1' (+) $ fromList [1,2,3,4]
--   [1,3,6,10]
--   
scanl1' :: (IsStream t, Monad m) => (a -> a -> a) -> t m a -> t m a -- | Like scanl1' but with a monadic step function. scanl1M' :: (IsStream t, Monad m) => (a -> a -> m a) -> t m a -> t m a -- | Modify a t m a -> t m a stream transformation that accepts -- a predicate (a -> b) to accept ((s, a) -> b) -- instead, provided a transformation t m a -> t m (s, a). -- Convenient to filter with index or time. -- --
--   filterWithIndex = with indexed filter
--   filterWithAbsTime = with timestamped filter
--   filterWithRelTime = with timeIndexed filter
--   
-- -- Pre-release with :: forall (t :: (Type -> Type) -> Type -> Type) m a b s. Functor (t m) => (t m a -> t m (s, a)) -> (((s, a) -> b) -> t m (s, a) -> t m (s, a)) -> ((s, a) -> b) -> t m a -> t m a -- | Deletes the first occurrence of the element in the stream that -- satisfies the given equality predicate. -- --
--   >>> Stream.toList $ Stream.deleteBy (==) 3 $ Stream.fromList [1,3,3,5]
--   [1,3,5]
--   
deleteBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> a -> t m a -> t m a -- | Include only those elements that pass a predicate. filter :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a -- | Same as filter but with a monadic predicate. filterM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a -- | Drop repeated elements that are adjacent to each other. uniq :: (Eq a, IsStream t, Monad m) => t m a -> t m a -- | Drop repeated elements that are adjacent to each other using the -- supplied comparison function. -- -- @uniq = uniqBy (==) -- -- To strip duplicate path separators: -- --
--   f x y = x == / && x == y
--   Stream.toList $ Stream.uniqBy f $ Stream.fromList "/a/b"
--   "ab"
--   
-- -- Space: O(1) -- -- See also: nubBy. -- -- Pre-release uniqBy :: (IsStream t, Monad m, Functor (t m)) => (a -> a -> Bool) -> t m a -> t m a -- | Drop repeated elements anywhere in the stream. -- -- Caution: not scalable for infinite streams -- -- See also: nubWindowBy -- -- Unimplemented nubBy :: (a -> a -> Bool) -> t m a -> t m a -- | Drop repeated elements within the specified tumbling window in the -- stream. -- --
--   nubBy = nubWindowBy maxBound
--   
-- -- Unimplemented nubWindowBy :: Int -> (a -> a -> Bool) -> t m a -> t m a -- | Strip all leading and trailing occurrences of an element passing a -- predicate and make all other consecutive occurrences uniq. -- --
--   prune p = dropWhileAround p $ uniqBy (x y -> p x && p y)
--   
-- --
--   > Stream.prune isSpace (Stream.fromList "  hello      world!   ")
--   "hello world!"
--   
-- -- Space: O(1) -- -- Unimplemented prune :: (a -> Bool) -> t m a -> t m a -- | Emit only repeated elements, once. -- -- Unimplemented repeated :: t m a -> t m a -- | Take first n elements from the stream and discard the rest. take :: (IsStream t, Monad m) => Int -> t m a -> t m a -- | takeInterval duration yields stream elements upto specified -- time duration. The duration starts when the stream is -- evaluated for the first time, before the first element is yielded. The -- time duration is checked before generating each element, if the -- duration has expired the stream stops. -- -- The total time taken in executing the stream is guaranteed to be at -- least duration, however, because the duration is checked -- before generating an element, the upper bound is indeterminate and -- depends on the time taken in generating and processing the last -- element. -- -- No element is yielded if the duration is zero. At least one element is -- yielded if the duration is non-zero. -- -- Pre-release takeInterval :: (MonadIO m, IsStream t, TimeUnit64 d) => d -> t m a -> t m a -- | Take n elements at the end of the stream. -- -- O(n) space, where n is the number elements taken. -- -- Unimplemented takeLast :: Int -> t m a -> t m a -- | Take time interval i seconds at the end of the stream. -- -- O(n) space, where n is the number elements taken. -- -- Unimplemented takeLastInterval :: Double -> t m a -> t m a -- | End the stream as soon as the predicate fails on an element. takeWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a -- | Same as takeWhile but with a monadic predicate. takeWhileM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a -- | Take all consecutive elements at the end of the stream for which the -- predicate is true. -- -- O(n) space, where n is the number elements taken. -- -- Unimplemented takeWhileLast :: (a -> Bool) -> t m a -> t m a -- | Like takeWhile and takeWhileLast combined. -- -- O(n) space, where n is the number elements taken from the end. -- -- Unimplemented takeWhileAround :: (a -> Bool) -> t m a -> t m a -- | Discard first n elements from the stream and take the rest. drop :: (IsStream t, Monad m) => Int -> t m a -> t m a -- | dropInterval duration drops stream elements until specified -- duration has passed. The duration begins when the stream is -- evaluated for the first time. The time duration is checked -- after generating a stream element, the element is yielded if -- the duration has expired otherwise it is dropped. -- -- The time elapsed before starting to generate the first element is -- at most duration, however, because the duration expiry -- is checked after the element is generated, the lower bound is -- indeterminate and depends on the time taken in generating an element. -- -- All elements are yielded if the duration is zero. -- -- Pre-release dropInterval :: (MonadIO m, IsStream t, TimeUnit64 d) => d -> t m a -> t m a -- | Drop n elements at the end of the stream. -- -- O(n) space, where n is the number elements dropped. -- -- Unimplemented dropLast :: Int -> t m a -> t m a -- | Drop time interval i seconds at the end of the stream. -- -- O(n) space, where n is the number elements dropped. -- -- Unimplemented dropLastInterval :: Int -> t m a -> t m a -- | Drop elements in the stream as long as the predicate succeeds and then -- take the rest of the stream. dropWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a -- | Same as dropWhile but with a monadic predicate. dropWhileM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a -- | Drop all consecutive elements at the end of the stream for which the -- predicate is true. -- -- O(n) space, where n is the number elements dropped. -- -- Unimplemented dropWhileLast :: (a -> Bool) -> t m a -> t m a -- | Like dropWhile and dropWhileLast combined. -- -- O(n) space, where n is the number elements dropped from the end. -- -- Unimplemented dropWhileAround :: (a -> Bool) -> t m a -> t m a -- | Insert a pure value between successive elements of a stream. -- --
--   >>> Stream.toList $ Stream.intersperse ',' $ Stream.fromList "hello"
--   "h,e,l,l,o"
--   
intersperse :: (IsStream t, MonadAsync m) => a -> t m a -> t m a -- | Insert an effect and its output before consuming an element of a -- stream except the first one. -- --
--   >>> Stream.toList $ Stream.trace putChar $ Stream.intersperseM (putChar '.' >> return ',') $ Stream.fromList "hello"
--   h.,e.,l.,l.,o"h,e,l,l,o"
--   
intersperseM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a -- | Intersperse a monadic action into the input stream after every -- n elements. -- --
--   > Stream.toList $ Stream.intersperseBySpan 2 (return ',') $ Stream.fromList "hello"
--   "he,ll,o"
--   
-- -- Unimplemented intersperseBySpan :: Int -> m a -> t m a -> t m a -- | Insert an effect and its output after consuming an element of a -- stream. -- --
--   >>> Stream.toList $ Stream.trace putChar $ intersperseSuffix (putChar '.' >> return ',') $ Stream.fromList "hello"
--   h.,e.,l.,l.,o.,"h,e,l,l,o,"
--   
-- -- Pre-release intersperseSuffix :: (IsStream t, Monad m) => m a -> t m a -> t m a -- | Like intersperseSuffix but intersperses an effectful action -- into the input stream after every n elements and after the -- last element. -- --
--   >>> Stream.toList $ Stream.intersperseSuffixBySpan 2 (return ',') $ Stream.fromList "hello"
--   "he,ll,o,"
--   
-- -- Pre-release intersperseSuffixBySpan :: (IsStream t, Monad m) => Int -> m a -> t m a -> t m a -- | Intersperse a monadic action into the input stream after every -- n seconds. -- --
--   > import Control.Concurrent (threadDelay)
--   > Stream.drain $ Stream.interjectSuffix 1 (putChar ',') $ Stream.mapM (x -> threadDelay 1000000 >> putChar x) $ Stream.fromList "hello"
--   h,e,l,l,o
--   
-- -- Pre-release interjectSuffix :: (IsStream t, MonadAsync m) => Double -> m a -> t m a -> t m a -- | Insert a side effect before consuming an element of a stream except -- the first one. -- --
--   >>> Stream.drain $ Stream.trace putChar $ Stream.intersperseM_ (putChar '.') $ Stream.fromList "hello"
--   h.e.l.l.o
--   
-- -- Pre-release intersperseM_ :: (IsStream t, Monad m) => m b -> t m a -> t m a -- | Introduce a delay of specified seconds before consuming an element of -- the stream except the first one. -- --
--   >>> Stream.mapM_ print $ Stream.timestamped $ Stream.delay 1 $ Stream.enumerateFromTo 1 3
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),1)
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),2)
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),3)
--   
delay :: (IsStream t, MonadIO m) => Double -> t m a -> t m a -- | Insert a side effect after consuming an element of a stream. -- --
--   >>> Stream.mapM_ putChar $ Stream.intersperseSuffix_ (threadDelay 1000000) $ Stream.fromList "hello"
--   hello
--   
-- -- Pre-release intersperseSuffix_ :: (IsStream t, Monad m) => m b -> t m a -> t m a -- | Introduce a delay of specified seconds after consuming an element of a -- stream. -- --
--   >>> Stream.mapM_ print $ Stream.timestamped $ Stream.delayPost 1 $ Stream.enumerateFromTo 1 3
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),1)
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),2)
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),3)
--   
-- -- Pre-release delayPost :: (IsStream t, MonadIO m) => Double -> t m a -> t m a -- | Insert a side effect before consuming an element of a stream. -- --
--   >>> Stream.toList $ Stream.trace putChar $ Stream.interspersePrefix_ (putChar '.' >> return ',') $ Stream.fromList "hello"
--   .h.e.l.l.o"hello"
--   
-- -- Same as trace_ but may be concurrent. -- -- Concurrent -- -- Pre-release interspersePrefix_ :: (IsStream t, MonadAsync m) => m b -> t m a -> t m a -- | Introduce a delay of specified seconds before consuming an element of -- a stream. -- --
--   >>> Stream.mapM_ print $ Stream.timestamped $ Stream.delayPre 1 $ Stream.enumerateFromTo 1 3
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),1)
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),2)
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),3)
--   
-- -- Pre-release delayPre :: (IsStream t, MonadIO m) => Double -> t m a -> t m a -- | insertBy cmp elem stream inserts elem before the -- first element in stream that is less than elem when -- compared using cmp. -- --
--   insertBy cmp x = mergeBy cmp (fromPure x)
--   
-- --
--   >>> Stream.toList $ Stream.insertBy compare 2 $ Stream.fromList [1,3,5]
--   [1,2,3,5]
--   
insertBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> a -> t m a -> t m a -- | Returns the elements of the stream in reverse order. The stream must -- be finite. Note that this necessarily buffers the entire stream in -- memory. -- --
--   >>> reverse = Stream.foldlT (flip Stream.cons) Stream.nil
--   
-- -- Since 0.7.0 (Monad m constraint) -- -- Since: 0.1.1 reverse :: (IsStream t, Monad m) => t m a -> t m a -- | Like reverse but several times faster, requires a -- Storable instance. -- -- Pre-release reverse' :: (IsStream t, MonadIO m, Storable a) => t m a -> t m a -- | Buffer until the next element in sequence arrives. The function -- argument determines the difference in sequence numbers. This could be -- useful in implementing sequenced streams, for example, TCP reassembly. -- -- Unimplemented reassembleBy :: Fold m a b -> (a -> a -> Int) -> t m a -> t m b -- |
--   indexed = Stream.postscanl' (\(i, _) x -> (i + 1, x)) (-1,undefined)
--   indexed = Stream.zipWith (,) (Stream.enumerateFrom 0)
--   
-- -- Pair each element in a stream with its index, starting from index 0. -- --
--   >>> Stream.toList $ Stream.indexed $ Stream.fromList "hello"
--   [(0,'h'),(1,'e'),(2,'l'),(3,'l'),(4,'o')]
--   
indexed :: (IsStream t, Monad m) => t m a -> t m (Int, a) -- |
--   indexedR n = Stream.postscanl' (\(i, _) x -> (i - 1, x)) (n + 1,undefined)
--   indexedR n = Stream.zipWith (,) (Stream.enumerateFromThen n (n - 1))
--   
-- -- Pair each element in a stream with its index, starting from the given -- index n and counting down. -- --
--   >>> Stream.toList $ Stream.indexedR 10 $ Stream.fromList "hello"
--   [(10,'h'),(9,'e'),(8,'l'),(7,'l'),(6,'o')]
--   
indexedR :: (IsStream t, Monad m) => Int -> t m a -> t m (Int, a) timestamped :: (IsStream t, MonadAsync m, Functor (t m)) => t m a -> t m (AbsTime, a) -- | Pair each element in a stream with an absolute timestamp, using a -- clock of specified granularity. The timestamp is generated just before -- the element is consumed. -- --
--   >>> Stream.mapM_ print $ Stream.timestampWith 0.01 $ Stream.delay 1 $ Stream.enumerateFromTo 1 3
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),1)
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),2)
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),3)
--   
-- -- Pre-release timestampWith :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m a -> t m (AbsTime, a) -- | Pair each element in a stream with relative times starting from 0, -- using a 10 ms granularity clock. The time is measured just before the -- element is consumed. -- --
--   >>> Stream.mapM_ print $ Stream.timeIndexed $ Stream.delay 1 $ Stream.enumerateFromTo 1 3
--   (RelTime64 (NanoSecond64 ...),1)
--   (RelTime64 (NanoSecond64 ...),2)
--   (RelTime64 (NanoSecond64 ...),3)
--   
-- -- Pre-release timeIndexed :: (IsStream t, MonadAsync m, Functor (t m)) => t m a -> t m (RelTime64, a) -- | Pair each element in a stream with relative times starting from 0, -- using a clock with the specified granularity. The time is measured -- just before the element is consumed. -- --
--   >>> Stream.mapM_ print $ Stream.timeIndexWith 0.01 $ Stream.delay 1 $ Stream.enumerateFromTo 1 3
--   (RelTime64 (NanoSecond64 ...),1)
--   (RelTime64 (NanoSecond64 ...),2)
--   (RelTime64 (NanoSecond64 ...),3)
--   
-- -- Pre-release timeIndexWith :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m a -> t m (RelTime64, a) -- | Find all the indices where the element in the stream satisfies the -- given predicate. -- --
--   findIndices = fold Fold.findIndices
--   
findIndices :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m Int -- | Find all the indices where the value of the element in the stream is -- equal to the given value. -- --
--   elemIndices a = findIndices (== a)
--   
elemIndices :: (IsStream t, Eq a, Monad m) => a -> t m a -> t m Int -- | Like rollingMap but with an effectful map function. -- -- Pre-release rollingMapM :: (IsStream t, Monad m) => (a -> a -> m b) -> t m a -> t m b -- | Apply a function on every two successive elements of a stream. If the -- stream consists of a single element the output is an empty stream. -- -- This is the stream equivalent of the list idiom zipWith f xs (tail -- xs). -- -- Pre-release rollingMap :: (IsStream t, Monad m) => (a -> a -> b) -> t m a -> t m b -- | In a stream of Maybes, discard Nothings and unwrap -- Justs. -- -- Pre-release catMaybes :: (IsStream t, Monad m, Functor (t m)) => t m (Maybe a) -> t m a -- | Map a Maybe returning function to a stream, filter out the -- Nothing elements, and return a stream of values extracted from -- Just. -- -- Equivalent to: -- --
--   mapMaybe f = Stream.map fromJust . Stream.filter isJust . Stream.map f
--   
mapMaybe :: (IsStream t, Monad m) => (a -> Maybe b) -> t m a -> t m b -- | Like mapMaybe but maps a monadic function. -- -- Equivalent to: -- --
--   mapMaybeM f = Stream.map fromJust . Stream.filter isJust . Stream.mapM f
--   
-- -- Concurrent (do not use with fromParallel on infinite -- streams) mapMaybeM :: (IsStream t, MonadAsync m, Functor (t m)) => (a -> m (Maybe b)) -> t m a -> t m b -- | Discard Rights and unwrap Lefts in an Either -- stream. -- -- Pre-release lefts :: (IsStream t, Monad m, Functor (t m)) => t m (Either a b) -> t m a -- | Discard Lefts and unwrap Rights in an Either -- stream. -- -- Pre-release rights :: (IsStream t, Monad m, Functor (t m)) => t m (Either a b) -> t m b -- | Remove the either wrapper and flatten both lefts and as well as rights -- in the output stream. -- -- Pre-release both :: Functor (t m) => t m (Either a a) -> t m a -- | Make the stream producer and consumer run concurrently by introducing -- a buffer between them. The producer thread evaluates the input stream -- until the buffer fills, it terminates if the buffer is full and a -- worker thread is kicked off again to evaluate the remaining stream -- when there is space in the buffer. The consumer consumes the stream -- lazily from the buffer. -- -- Since: 0.2.0 (Streamly) mkAsync :: (IsStream t, MonadAsync m) => t m a -> t m a -- | Make the stream producer and consumer run concurrently by introducing -- a buffer between them. The producer thread evaluates the input stream -- until the buffer fills, it blocks if the buffer is full until there is -- space in the buffer. The consumer consumes the stream lazily from the -- buffer. -- --
--   mkParallel = IsStream.fromStreamD . mkParallelD . IsStream.toStreamD
--   
-- -- Pre-release mkParallel :: (IsStream t, MonadAsync m) => t m a -> t m a -- | Same as |$. -- -- Internal applyAsync :: (IsStream t, MonadAsync m) => (t m a -> t m b) -> t m a -> t m b -- | Parallel transform application operator; applies a stream -- transformation function t m a -> t m b to a stream t m -- a concurrently; the input stream is evaluated asynchronously in -- an independent thread yielding elements to a buffer and the -- transformation function runs in another thread consuming the input -- from the buffer. |$ is just like regular function application -- operator $ except that it is concurrent. -- -- If you read the signature as (t m a -> t m b) -> (t m a -- -> t m b) you can look at it as a transformation that converts -- a transform function to a buffered concurrent transform function. -- -- The following code prints a value every second even though each stage -- adds a 1 second delay. -- --
--   >>> :{
--   Stream.drain $
--      Stream.mapM (\x -> threadDelay 1000000 >> print x)
--        |$ Stream.replicateM 3 (threadDelay 1000000 >> return 1)
--   :}
--   1
--   1
--   1
--   
-- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|$) :: (IsStream t, MonadAsync m) => (t m a -> t m b) -> t m a -> t m b infixr 0 |$ -- | Same as |$ but with arguments reversed. -- -- (|&) = flip (|$) -- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|&) :: (IsStream t, MonadAsync m) => t m a -> (t m a -> t m b) -> t m b infixl 1 |& -- | Specify the maximum number of threads that can be spawned concurrently -- for any concurrent combinator in a stream. A value of 0 resets the -- thread limit to default, a negative value means there is no limit. The -- default value is 1500. maxThreads does not affect -- ParallelT streams as they can use unbounded number of -- threads. -- -- When the actions in a stream are IO bound, having blocking IO calls, -- this option can be used to control the maximum number of in-flight IO -- requests. When the actions are CPU bound this option can be used to -- control the amount of CPU used by the stream. -- -- Since: 0.4.0 (Streamly) maxThreads :: IsStream t => Int -> t m a -> t m a -- | Specify the maximum size of the buffer for storing the results from -- concurrent computations. If the buffer becomes full we stop spawning -- more concurrent tasks until there is space in the buffer. A value of 0 -- resets the buffer size to default, a negative value means there is no -- limit. The default value is 1500. -- -- CAUTION! using an unbounded maxBuffer value (i.e. a negative -- value) coupled with an unbounded maxThreads value is a recipe -- for disaster in presence of infinite streams, or very large streams. -- Especially, it must not be used when pure is used in -- ZipAsyncM streams as pure in applicative zip streams -- generates an infinite stream causing unbounded concurrent generation -- with no limit on the buffer or threads. -- -- Since: 0.4.0 (Streamly) maxBuffer :: IsStream t => Int -> t m a -> t m a -- | Evaluate the input stream continuously and keep only the oldest -- n elements in the buffer, discard the new ones when the -- buffer is full. When the output stream is evaluated it consumes the -- values from the buffer in a FIFO manner. -- -- Unimplemented sampleOld :: Int -> t m a -> t m a -- | Evaluate the input stream continuously and keep only the latest -- n elements in a ring buffer, keep discarding the older ones -- to make space for the new ones. When the output stream is evaluated it -- consumes the values from the buffer in a FIFO manner. -- -- Unimplemented sampleNew :: Int -> t m a -> t m a -- | Like sampleNew but samples at uniform intervals to match the -- consumer rate. Note that sampleNew leads to non-uniform -- sampling depending on the consumer pattern. -- -- Unimplemented sampleRate :: Double -> t m a -> t m a -- | Specifies the stream yield rate in yields per second (Hertz). -- We keep accumulating yield credits at rateGoal. At any point of -- time we allow only as many yields as we have accumulated as per -- rateGoal since the start of time. If the consumer or the -- producer is slower or faster, the actual rate may fall behind or -- exceed rateGoal. We try to recover the gap between the two by -- increasing or decreasing the pull rate from the producer. However, if -- the gap becomes more than rateBuffer we try to recover only as -- much as rateBuffer. -- -- rateLow puts a bound on how low the instantaneous rate can go -- when recovering the rate gap. In other words, it determines the -- maximum yield latency. Similarly, rateHigh puts a bound on how -- high the instantaneous rate can go when recovering the rate gap. In -- other words, it determines the minimum yield latency. We reduce the -- latency by increasing concurrency, therefore we can say that it puts -- an upper bound on concurrency. -- -- If the rateGoal is 0 or negative the stream never yields a -- value. If the rateBuffer is 0 or negative we do not attempt to -- recover. -- -- Since: 0.5.0 (Streamly) data Rate Rate :: Double -> Double -> Double -> Int -> Rate -- | The lower rate limit [rateLow] :: Rate -> Double -- | The target rate we want to achieve [rateGoal] :: Rate -> Double -- | The upper rate limit [rateHigh] :: Rate -> Double -- | Maximum slack from the goal [rateBuffer] :: Rate -> Int -- | Specify the pull rate of a stream. A Nothing value resets the -- rate to default which is unlimited. When the rate is specified, -- concurrent production may be ramped up or down automatically to -- achieve the specified yield rate. The specific behavior for different -- styles of Rate specifications is documented under Rate. -- The effective maximum production rate achieved by a stream is governed -- by: -- -- -- -- Since: 0.5.0 (Streamly) rate :: IsStream t => Maybe Rate -> t m a -> t m a -- | Same as rate (Just $ Rate (r/2) r (2*r) maxBound) -- -- Specifies the average production rate of a stream in number of yields -- per second (i.e. Hertz). Concurrent production is ramped up -- or down automatically to achieve the specified average yield rate. The -- rate can go down to half of the specified rate on the lower side and -- double of the specified rate on the higher side. -- -- Since: 0.5.0 (Streamly) avgRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate r r (2*r) maxBound) -- -- Specifies the minimum rate at which the stream should yield values. As -- far as possible the yield rate would never be allowed to go below the -- specified rate, even though it may possibly go above it at times, the -- upper limit is double of the specified rate. -- -- Since: 0.5.0 (Streamly) minRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate (r/2) r r maxBound) -- -- Specifies the maximum rate at which the stream should yield values. As -- far as possible the yield rate would never be allowed to go above the -- specified rate, even though it may possibly go below it at times, the -- lower limit is half of the specified rate. This can be useful in -- applications where certain resource usage must not be allowed to go -- beyond certain limits. -- -- Since: 0.5.0 (Streamly) maxRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate r r r 0) -- -- Specifies a constant yield rate. If for some reason the actual rate -- goes above or below the specified rate we do not try to recover it by -- increasing or decreasing the rate in future. This can be useful in -- applications like graphics frame refresh where we need to maintain a -- constant refresh rate. -- -- Since: 0.5.0 (Streamly) constRate :: IsStream t => Double -> t m a -> t m a -- | Print debug information about an SVar when the stream ends -- -- Pre-release inspectMode :: IsStream t => t m a -> t m a -- | Strict left scan with an extraction function. Like scanl', but -- applies a user supplied extraction function (the third argument) at -- each step. This is designed to work with the foldl library. -- The suffix x is a mnemonic for extraction. -- -- Since 0.2.0 -- -- Since: 0.7.0 (Monad m constraint) -- | Deprecated: Please use scanl followed by map instead. scanx :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b -- | Reduce streams by streams, folds or parsers. module Streamly.Internal.Data.Stream.IsStream.Reduce -- | Drop prefix from the input stream if present. -- -- Space: O(1) -- -- Unimplemented - Help wanted. dropPrefix :: t m a -> t m a -> t m a -- | Drop all matching infix from the input stream if present. Infix stream -- may be consumed multiple times. -- -- Space: O(n) where n is the length of the infix. -- -- Unimplemented - Help wanted. dropInfix :: t m a -> t m a -> t m a -- | Drop suffix from the input stream if present. Suffix stream may be -- consumed multiple times. -- -- Space: O(n) where n is the length of the suffix. -- -- Unimplemented - Help wanted. dropSuffix :: t m a -> t m a -> t m a -- | Apply a Fold repeatedly on a stream and emit the fold outputs -- in the output stream. -- -- To sum every two contiguous elements in a stream: -- --
--   >>> f = Fold.take 2 Fold.sum
--   
--   >>> Stream.toList $ Stream.foldMany f $ Stream.fromList [1..10]
--   [3,7,11,15,19]
--   
-- -- On an empty stream the output is empty: -- --
--   >>> Stream.toList $ Stream.foldMany f $ Stream.fromList []
--   []
--   
-- -- Note Stream.foldMany (Fold.take 0) would result in an -- infinite loop in a non-empty stream. foldMany :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | Like foldMany but appends empty fold output if the fold and -- stream termination aligns: -- --
--   >>> f = Fold.take 2 Fold.sum
--   
--   >>> Stream.toList $ Stream.foldManyPost f $ Stream.fromList []
--   [0]
--   
--   >>> Stream.toList $ Stream.foldManyPost f $ Stream.fromList [1..9]
--   [3,7,11,15,9]
--   
--   >>> Stream.toList $ Stream.foldManyPost f $ Stream.fromList [1..10]
--   [3,7,11,15,19,0]
--   
-- -- Pre-release foldManyPost :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | Like foldMany but using the Refold type instead of -- Fold. -- -- Pre-release refoldMany :: (IsStream t, Monad m) => Refold m c a b -> m c -> t m a -> t m b -- | Apply a stream of folds to an input stream and emit the results in the -- output stream. -- -- Unimplemented foldSequence :: t m (Fold m a b) -> t m a -> t m b -- | Iterate a fold generator on a stream. The initial value b is -- used to generate the first fold, the fold is applied on the stream and -- the result of the fold is used to generate the next fold and so on. -- --
--   >>> import Data.Monoid (Sum(..))
--   >>> f x = return (Fold.take 2 (Fold.sconcat x))
--   >>> s = Stream.map Sum $ Stream.fromList [1..10]
--   >>> Stream.toList $ Stream.map getSum $ Stream.foldIterateM f (pure 0) s
--   [3,10,21,36,55,55]
--   
-- -- This is the streaming equivalent of monad like sequenced application -- of folds where next fold is dependent on the previous fold. -- -- Pre-release foldIterateM :: (IsStream t, Monad m) => (b -> m (Fold m a b)) -> m b -> t m a -> t m b -- | Like foldIterateM but using the Refold type instead. -- This could be much more efficient due to stream fusion. -- -- Internal refoldIterateM :: (IsStream t, Monad m) => Refold m b a b -> m b -> t m a -> t m b -- | Group the input stream into groups of n elements each and -- then fold each group using the provided fold function. -- --
--   >>> Stream.toList $ Stream.chunksOf 2 Fold.sum (Stream.enumerateFromTo 1 10)
--   [3,7,11,15,19]
--   
-- -- This can be considered as an n-fold version of take where we -- apply take repeatedly on the leftover stream until the stream -- exhausts. -- --
--   chunksOf n f = foldMany (FL.take n f)
--   
chunksOf :: (IsStream t, Monad m) => Int -> Fold m a b -> t m a -> t m b -- | arraysOf n stream groups the elements in the input stream -- into arrays of n elements each. -- -- Same as the following but may be more efficient: -- --
--   arraysOf n = Stream.foldMany (A.writeN n)
--   
-- -- Pre-release arraysOf :: (IsStream t, MonadIO m, Storable a) => Int -> t m a -> t m (Array a) -- | Group the input stream into windows of n second each and then -- fold each group using the provided fold function. -- --
--   >>> Stream.toList $ Stream.take 5 $ Stream.intervalsOf 1 Fold.sum $ Stream.constRate 2 $ Stream.enumerateFrom 1
--   [...,...,...,...,...]
--   
intervalsOf :: (IsStream t, MonadAsync m) => Double -> Fold m a b -> t m a -> t m b -- | Like chunksOf but if the chunk is not completed within the -- specified time interval then emit whatever we have collected till now. -- The chunk timeout is reset whenever a chunk is emitted. -- --
--   >>> s = Stream.delayPost 0.3 $ Stream.fromList [1..1000]
--   
--   >>> f = Stream.mapM_ print $ Stream.chunksOfTimeout 5 1 Fold.toList s
--   
-- -- Pre-release chunksOfTimeout :: (IsStream t, MonadAsync m, Functor (t m)) => Int -> Double -> Fold m a b -> t m a -> t m b -- | Split on an infixed separator element, dropping the separator. The -- supplied Fold is applied on the split segments. Splits the -- stream on separator elements determined by the supplied predicate, -- separator is considered as infixed between two segments: -- --
--   >>> splitOn' p xs = Stream.toList $ Stream.splitOn p Fold.toList (Stream.fromList xs)
--   
--   >>> splitOn' (== '.') "a.b"
--   ["a","b"]
--   
-- -- An empty stream is folded to the default value of the fold: -- --
--   >>> splitOn' (== '.') ""
--   [""]
--   
-- -- If one or both sides of the separator are missing then the empty -- segment on that side is folded to the default output of the fold: -- --
--   >>> splitOn' (== '.') "."
--   ["",""]
--   
-- --
--   >>> splitOn' (== '.') ".a"
--   ["","a"]
--   
-- --
--   >>> splitOn' (== '.') "a."
--   ["a",""]
--   
-- --
--   >>> splitOn' (== '.') "a..b"
--   ["a","","b"]
--   
-- -- splitOn is an inverse of intercalating single element: -- --
--   Stream.intercalate (Stream.fromPure '.') Unfold.fromList . Stream.splitOn (== '.') Fold.toList === id
--   
-- -- Assuming the input stream does not contain the separator: -- --
--   Stream.splitOn (== '.') Fold.toList . Stream.intercalate (Stream.fromPure '.') Unfold.fromList === id
--   
splitOn :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b -- | Split on a suffixed separator element, dropping the separator. The -- supplied Fold is applied on the split segments. -- --
--   >>> splitOnSuffix' p xs = Stream.toList $ Stream.splitOnSuffix p Fold.toList (Stream.fromList xs)
--   
--   >>> splitOnSuffix' (== '.') "a.b."
--   ["a","b"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a."
--   ["a"]
--   
-- -- An empty stream results in an empty output stream: -- --
--   >>> splitOnSuffix' (== '.') ""
--   []
--   
-- -- An empty segment consisting of only a suffix is folded to the default -- output of the fold: -- --
--   >>> splitOnSuffix' (== '.') "."
--   [""]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a..b.."
--   ["a","","b",""]
--   
-- -- A suffix is optional at the end of the stream: -- --
--   >>> splitOnSuffix' (== '.') "a"
--   ["a"]
--   
-- --
--   >>> splitOnSuffix' (== '.') ".a"
--   ["","a"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a.b"
--   ["a","b"]
--   
-- --
--   lines = splitOnSuffix (== '\n')
--   
-- -- splitOnSuffix is an inverse of intercalateSuffix with -- a single element: -- --
--   Stream.intercalateSuffix (Stream.fromPure '.') Unfold.fromList . Stream.splitOnSuffix (== '.') Fold.toList === id
--   
-- -- Assuming the input stream does not contain the separator: -- --
--   Stream.splitOnSuffix (== '.') Fold.toList . Stream.intercalateSuffix (Stream.fromPure '.') Unfold.fromList === id
--   
splitOnSuffix :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b -- | Split on a prefixed separator element, dropping the separator. The -- supplied Fold is applied on the split segments. -- --
--   > splitOnPrefix' p xs = Stream.toList $ Stream.splitOnPrefix p (Fold.toList) (Stream.fromList xs)
--   > splitOnPrefix' (== .) ".a.b"
--   ["a","b"]
--   
-- -- An empty stream results in an empty output stream: > -- splitOnPrefix' (== .) "" [] -- -- An empty segment consisting of only a prefix is folded to the default -- output of the fold: -- --
--   > splitOnPrefix' (== .) "."
--   [""]
--   
--   > splitOnPrefix' (== .) ".a.b."
--   ["a","b",""]
--   
--   > splitOnPrefix' (== .) ".a..b"
--   ["a","","b"]
--   
-- -- A prefix is optional at the beginning of the stream: -- --
--   > splitOnPrefix' (== .) "a"
--   ["a"]
--   
--   > splitOnPrefix' (== .) "a.b"
--   ["a","b"]
--   
-- -- splitOnPrefix is an inverse of intercalatePrefix with -- a single element: -- --
--   Stream.intercalatePrefix (Stream.fromPure '.') Unfold.fromList . Stream.splitOnPrefix (== '.') Fold.toList === id
--   
-- -- Assuming the input stream does not contain the separator: -- --
--   Stream.splitOnPrefix (== '.') Fold.toList . Stream.intercalatePrefix (Stream.fromPure '.') Unfold.fromList === id
--   
-- -- Unimplemented splitOnPrefix :: (a -> Bool) -> Fold m a b -> t m a -> t m b -- | Like splitOnSuffix but keeps the suffix attached to the -- resulting splits. -- --
--   >>> splitWithSuffix' p xs = Stream.toList $ splitWithSuffix p Fold.toList (Stream.fromList xs)
--   
-- --
--   >>> splitWithSuffix' (== '.') ""
--   []
--   
-- --
--   >>> splitWithSuffix' (== '.') "."
--   ["."]
--   
-- --
--   >>> splitWithSuffix' (== '.') "a"
--   ["a"]
--   
-- --
--   >>> splitWithSuffix' (== '.') ".a"
--   [".","a"]
--   
-- --
--   >>> splitWithSuffix' (== '.') "a."
--   ["a."]
--   
-- --
--   >>> splitWithSuffix' (== '.') "a.b"
--   ["a.","b"]
--   
-- --
--   >>> splitWithSuffix' (== '.') "a.b."
--   ["a.","b."]
--   
-- --
--   >>> splitWithSuffix' (== '.') "a..b.."
--   ["a.",".","b.","."]
--   
splitWithSuffix :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b -- | Like splitOnSeq but splits the separator as well, as an infix -- token. -- --
--   >>> splitOn'_ pat xs = Stream.toList $ Stream.splitBySeq (Array.fromList pat) Fold.toList (Stream.fromList xs)
--   
-- --
--   >>> splitOn'_ "" "hello"
--   ["h","","e","","l","","l","","o"]
--   
-- --
--   >>> splitOn'_ "hello" ""
--   [""]
--   
-- --
--   >>> splitOn'_ "hello" "hello"
--   ["","hello",""]
--   
-- --
--   >>> splitOn'_ "x" "hello"
--   ["hello"]
--   
-- --
--   >>> splitOn'_ "h" "hello"
--   ["","h","ello"]
--   
-- --
--   >>> splitOn'_ "o" "hello"
--   ["hell","o",""]
--   
-- --
--   >>> splitOn'_ "e" "hello"
--   ["h","e","llo"]
--   
-- --
--   >>> splitOn'_ "l" "hello"
--   ["he","l","","l","o"]
--   
-- --
--   >>> splitOn'_ "ll" "hello"
--   ["he","ll","o"]
--   
-- -- Pre-release splitBySeq :: (IsStream t, MonadAsync m, Storable a, Enum a, Eq a) => Array a -> Fold m a b -> t m a -> t m b -- | Like splitOn but the separator is a sequence of elements -- instead of a single element. -- -- For illustration, let's define a function that operates on pure lists: -- --
--   >>> splitOnSeq' pat xs = Stream.toList $ Stream.splitOnSeq (Array.fromList pat) Fold.toList (Stream.fromList xs)
--   
-- --
--   >>> splitOnSeq' "" "hello"
--   ["h","e","l","l","o"]
--   
-- --
--   >>> splitOnSeq' "hello" ""
--   [""]
--   
-- --
--   >>> splitOnSeq' "hello" "hello"
--   ["",""]
--   
-- --
--   >>> splitOnSeq' "x" "hello"
--   ["hello"]
--   
-- --
--   >>> splitOnSeq' "h" "hello"
--   ["","ello"]
--   
-- --
--   >>> splitOnSeq' "o" "hello"
--   ["hell",""]
--   
-- --
--   >>> splitOnSeq' "e" "hello"
--   ["h","llo"]
--   
-- --
--   >>> splitOnSeq' "l" "hello"
--   ["he","","o"]
--   
-- --
--   >>> splitOnSeq' "ll" "hello"
--   ["he","o"]
--   
-- -- splitOnSeq is an inverse of intercalate. The following -- law always holds: -- --
--   intercalate . splitOnSeq == id
--   
-- -- The following law holds when the separator is non-empty and contains -- none of the elements present in the input lists: -- --
--   splitOnSeq . intercalate == id
--   
-- -- Pre-release splitOnSeq :: (IsStream t, MonadIO m, Storable a, Enum a, Eq a) => Array a -> Fold m a b -> t m a -> t m b -- | Like splitSuffixBy but the separator is a sequence of -- elements, instead of a predicate for a single element. -- --
--   >>> splitOnSuffixSeq_ pat xs = Stream.toList $ Stream.splitOnSuffixSeq (Array.fromList pat) Fold.toList (Stream.fromList xs)
--   
-- --
--   >>> splitOnSuffixSeq_ "." ""
--   []
--   
-- --
--   >>> splitOnSuffixSeq_ "." "."
--   [""]
--   
-- --
--   >>> splitOnSuffixSeq_ "." "a"
--   ["a"]
--   
-- --
--   >>> splitOnSuffixSeq_ "." ".a"
--   ["","a"]
--   
-- --
--   >>> splitOnSuffixSeq_ "." "a."
--   ["a"]
--   
-- --
--   >>> splitOnSuffixSeq_ "." "a.b"
--   ["a","b"]
--   
-- --
--   >>> splitOnSuffixSeq_ "." "a.b."
--   ["a","b"]
--   
-- --
--   >>> splitOnSuffixSeq_ "." "a..b.."
--   ["a","","b",""]
--   
-- --
--   lines = splitOnSuffixSeq "\n"
--   
-- -- splitOnSuffixSeq is an inverse of intercalateSuffix. -- The following law always holds: -- --
--   intercalateSuffix . splitOnSuffixSeq == id
--   
-- -- The following law holds when the separator is non-empty and contains -- none of the elements present in the input lists: -- --
--   splitSuffixOn . intercalateSuffix == id
--   
-- -- Pre-release splitOnSuffixSeq :: (IsStream t, MonadIO m, Storable a, Enum a, Eq a) => Array a -> Fold m a b -> t m a -> t m b -- | Like splitOnSuffixSeq but keeps the suffix intact in the -- splits. -- --
--   >>> splitWithSuffixSeq' pat xs = Stream.toList $ Stream.splitWithSuffixSeq (Array.fromList pat) Fold.toList (Stream.fromList xs)
--   
-- --
--   >>> splitWithSuffixSeq' "." ""
--   []
--   
-- --
--   >>> splitWithSuffixSeq' "." "."
--   ["."]
--   
-- --
--   >>> splitWithSuffixSeq' "." "a"
--   ["a"]
--   
-- --
--   >>> splitWithSuffixSeq' "." ".a"
--   [".","a"]
--   
-- --
--   >>> splitWithSuffixSeq' "." "a."
--   ["a."]
--   
-- --
--   >>> splitWithSuffixSeq' "." "a.b"
--   ["a.","b"]
--   
-- --
--   >>> splitWithSuffixSeq' "." "a.b."
--   ["a.","b."]
--   
-- --
--   >>> splitWithSuffixSeq' "." "a..b.."
--   ["a.",".","b.","."]
--   
-- -- Pre-release splitWithSuffixSeq :: (IsStream t, MonadIO m, Storable a, Enum a, Eq a) => Array a -> Fold m a b -> t m a -> t m b -- | classifySessionsBy tick keepalive predicate timeout fold -- stream classifies an input event stream consisting of -- (timestamp, (key, value)) into sessions based on the -- key, folding all the values corresponding to the same key -- into a session using the supplied fold. -- -- When the fold terminates or a timeout occurs, a tuple -- consisting of the session key and the folded value is emitted in the -- output stream. The timeout is measured from the first event in the -- session. If the keepalive option is set to True the -- timeout is reset to 0 whenever an event is received. -- -- The timestamp in the input stream is an absolute time from -- some epoch, characterizing the time when the input event was -- generated. The notion of current time is maintained by a monotonic -- event time clock using the timestamps seen in the input stream. The -- latest timestamp seen till now is used as the base for the current -- time. When no new events are seen, a timer is started with a clock -- resolution of tick seconds. This timer is used to detect -- session timeouts in the absence of new events. -- -- To ensure an upper bound on the memory used the number of sessions can -- be limited to an upper bound. If the ejection predicate -- returns True, the oldest session is ejected before inserting a -- new session. -- --
--   >>> :{
--   Stream.mapM_ print
--       $ Stream.classifySessionsBy 1 False (const (return False)) 3 (Fold.take 3 Fold.toList)
--       $ Stream.timestamped
--       $ Stream.delay 0.1
--       $ (,) <$> Stream.fromList [1,2,3] <*> Stream.fromList ['a','b','c']
--   :}
--   (1,"abc")
--   (2,"abc")
--   (3,"abc")
--   
-- -- Pre-release classifySessionsBy :: (IsStream t, MonadAsync m, Ord k) => Double -> Bool -> (Int -> m Bool) -> Double -> Fold m a b -> t m (AbsTime, (k, a)) -> t m (k, b) -- | Same as classifySessionsBy with a timer tick of 1 second and -- keepalive option set to False. -- --
--   classifySessionsOf = classifySessionsBy 1 False
--   
-- -- Pre-release classifySessionsOf :: (IsStream t, MonadAsync m, Ord k) => (Int -> m Bool) -> Double -> Fold m a b -> t m (AbsTime, (k, a)) -> t m (k, b) -- | Same as classifySessionsBy with a timer tick of 1 second and -- keepalive option set to True. -- --
--   classifyKeepAliveSessions = classifySessionsBy 1 True
--   
-- -- Pre-release classifyKeepAliveSessions :: (IsStream t, MonadAsync m, Ord k) => (Int -> m Bool) -> Double -> Fold m a b -> t m (AbsTime, (k, a)) -> t m (k, b) -- | Apply a Parser repeatedly on a stream and emit the parsed -- values in the output stream. -- -- This is the streaming equivalent of the many parse combinator. -- --
--   >>> Stream.toList $ Stream.parseMany (Parser.takeBetween 0 2 Fold.sum) $ Stream.fromList [1..10]
--   [3,7,11,15,19]
--   
-- --
--   > Stream.toList $ Stream.parseMany (Parser.line Fold.toList) $ Stream.fromList "hello\nworld"
--   ["hello\n","world"]
--   
-- --
--   foldMany f = parseMany (fromFold f)
--   
-- -- Known Issues: When the parser fails there is no way to get the -- remaining stream. -- -- Pre-release parseMany :: (IsStream t, MonadThrow m) => Parser m a b -> t m a -> t m b parseManyD :: (IsStream t, MonadThrow m) => Parser m a b -> t m a -> t m b -- | parseManyTill collect test stream tries the parser -- test on the input, if test fails it backtracks and -- tries collect, after collect succeeds test -- is tried again and so on. The parser stops when test -- succeeds. The output of test is discarded and the output of -- collect is emitted in the output stream. The parser fails if -- collect fails. -- -- Unimplemented parseManyTill :: Parser m a b -> Parser m a x -> t m a -> t m b -- | Apply a stream of parsers to an input stream and emit the results in -- the output stream. -- -- Pre-release parseSequence :: t m (Parser m a b) -> t m a -> t m b -- | Iterate a parser generating function on a stream. The initial value -- b is used to generate the first parser, the parser is applied -- on the stream and the result is used to generate the next parser and -- so on. -- --
--   >>> import Data.Monoid (Sum(..))
--   
--   >>> Stream.toList $ Stream.map getSum $ Stream.parseIterate (\b -> Parser.takeBetween 0 2 (Fold.sconcat b)) 0 $ Stream.map Sum $ Stream.fromList [1..10]
--   [3,10,21,36,55,55]
--   
-- -- This is the streaming equivalent of monad like sequenced application -- of parsers where next parser is dependent on the previous parser. -- -- Pre-release parseIterate :: (IsStream t, MonadThrow m) => (b -> Parser m a b) -> b -> t m a -> t m b -- | Like splitOn after stripping leading, trailing, and repeated -- separators. Therefore, ".a..b." with . as the -- separator would be parsed as ["a","b"]. In other words, its -- like parsing words from whitespace separated text. -- --
--   >>> wordsBy' p xs = Stream.toList $ Stream.wordsBy p Fold.toList (Stream.fromList xs)
--   
-- --
--   >>> wordsBy' (== ',') ""
--   []
--   
-- --
--   >>> wordsBy' (== ',') ","
--   []
--   
-- --
--   >>> wordsBy' (== ',') ",a,,b,"
--   ["a","b"]
--   
-- --
--   words = wordsBy isSpace
--   
wordsBy :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b -- |
--   groups = groupsBy (==)
--   groups = groupsByRolling (==)
--   
-- -- Groups contiguous spans of equal elements together in individual -- groups. -- --
--   >>> Stream.toList $ Stream.groups Fold.toList $ Stream.fromList [1,1,2,2]
--   [[1,1],[2,2]]
--   
groups :: (IsStream t, Monad m, Eq a) => Fold m a b -> t m a -> t m b -- | groupsBy cmp f $ S.fromList [a,b,c,...] assigns the element -- a to the first group, if b `cmp` a is True -- then b is also assigned to the same group. If c `cmp` -- a is True then c is also assigned to the same -- group and so on. When the comparison fails a new group is started. -- Each group is folded using the fold f and the result of the -- fold is emitted in the output stream. -- --
--   >>> Stream.toList $ Stream.groupsBy (>) Fold.toList $ Stream.fromList [1,3,7,0,2,5]
--   [[1,3,7],[0,2,5]]
--   
groupsBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> Fold m a b -> t m a -> t m b -- | Unlike groupsBy this function performs a rolling comparison -- of two successive elements in the input stream. groupsByRolling -- cmp f $ S.fromList [a,b,c,...] assigns the element a to -- the first group, if a `cmp` b is True then b -- is also assigned to the same group. If b `cmp` c is -- True then c is also assigned to the same group and so -- on. When the comparison fails a new group is started. Each group is -- folded using the fold f. -- --
--   >>> Stream.toList $ Stream.groupsByRolling (\a b -> a + 1 == b) Fold.toList $ Stream.fromList [1,2,3,7,8,9]
--   [[1,2,3],[7,8,9]]
--   
groupsByRolling :: (IsStream t, Monad m) => (a -> a -> Bool) -> Fold m a b -> t m a -> t m b -- | splitInnerBy splitter joiner stream splits the inner -- containers f a of an input stream t m (f a) using -- the splitter function. Container elements f a are -- collected until a split occurs, then all the elements before the split -- are joined using the joiner function. -- -- For example, if we have a stream of Array Word8, we may want -- to split the stream into arrays representing lines separated by 'n' -- byte such that the resulting stream after a split would be one array -- for each line. -- -- CAUTION! This is not a true streaming function as the container size -- after the split and merge may not be bounded. -- -- Pre-release splitInnerBy :: (IsStream t, Monad m) => (f a -> m (f a, Maybe (f a))) -> (f a -> f a -> m (f a)) -> t m (f a) -> t m (f a) -- | Like splitInnerBy but splits assuming the separator joins the -- segment in a suffix style. -- -- Pre-release splitInnerBySuffix :: (IsStream t, Monad m, Eq (f a), Monoid (f a)) => (f a -> m (f a, Maybe (f a))) -> (f a -> f a -> m (f a)) -> t m (f a) -> t m (f a) -- | Most of the combinators in this module can be implemented as unfolds. -- Some of them however can only be expressed in terms StreamK e.g. -- cons/consM, fromFoldable, mfix. We can possibly remove those from this -- module which can be expressed as unfolds. Unless we want to use -- rewrite rules to rewrite them as StreamK when StreamK is used, -- avoiding conversion to StreamD. Will that help? Are there any other -- reasons to keep these and not use unfolds? module Streamly.Internal.Data.Stream.IsStream.Generate nil :: IsStream t => t m a nilM :: (IsStream t, Monad m) => m b -> t m a -- | Construct a stream by adding a pure value at the head of an existing -- stream. For serial streams this is the same as (return a) `consM` -- r but more efficient. For concurrent streams this is not -- concurrent whereas consM is concurrent. For example: -- --
--   > toList $ 1 `cons` 2 `cons` 3 `cons` nil
--   [1,2,3]
--   
cons :: IsStream t => a -> t m a -> t m a infixr 5 `cons` -- | Operator equivalent of cons. -- --
--   > toList $ 1 .: 2 .: 3 .: nil
--   [1,2,3]
--   
(.:) :: IsStream t => a -> t m a -> t m a infixr 5 .: -- | Constructs a stream by adding a monadic action at the head of an -- existing stream. For example: -- --
--   > toList $ getLine `consM` getLine `consM` nil
--   hello
--   world
--   ["hello","world"]
--   
-- -- Concurrent (do not use fromParallel to construct infinite -- streams) consM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 `consM` -- | Operator equivalent of consM. We can read it as "parallel -- colon" to remember that | comes before :. -- --
--   > toList $ getLine |: getLine |: nil
--   hello
--   world
--   ["hello","world"]
--   
-- --
--   let delay = threadDelay 1000000 >> print 1
--   drain $ fromSerial  $ delay |: delay |: delay |: nil
--   drain $ fromParallel $ delay |: delay |: delay |: nil
--   
-- -- Concurrent (do not use fromParallel to construct infinite -- streams) (|:) :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 |: -- | Convert an Unfold into a stream by supplying it an input seed. -- --
--   >>> Stream.drain $ Stream.unfold (Unfold.replicateM 3) (putStrLn "hello")
--   hello
--   hello
--   hello
--   
-- -- Since: 0.7.0 unfold :: (IsStream t, Monad m) => Unfold m a b -> a -> t m b -- | Convert an Unfold with a closed input end into a stream. -- -- Pre-release unfold0 :: (IsStream t, Monad m) => Unfold m Void b -> t m b -- |
--   >>> :{
--   unfoldr step s =
--       case step s of
--           Nothing -> Stream.nil
--           Just (a, b) -> a `Stream.cons` unfoldr step b
--   :}
--   
-- -- Build a stream by unfolding a pure step function step -- starting from a seed s. The step function returns the next -- element in the stream and the next seed value. When it is done it -- returns Nothing and the stream ends. For example, -- --
--   >>> :{
--   let f b =
--           if b > 2
--           then Nothing
--           else Just (b, b + 1)
--   in Stream.toList $ Stream.unfoldr f 0
--   :}
--   [0,1,2]
--   
unfoldr :: (Monad m, IsStream t) => (b -> Maybe (a, b)) -> b -> t m a -- | Build a stream by unfolding a monadic step function starting -- from a seed. The step function returns the next element in the stream -- and the next seed value. When it is done it returns Nothing and -- the stream ends. For example, -- --
--   >>> :{
--   let f b =
--           if b > 2
--           then return Nothing
--           else return (Just (b, b + 1))
--   in Stream.toList $ Stream.unfoldrM f 0
--   :}
--   [0,1,2]
--   
-- -- When run concurrently, the next unfold step can run concurrently with -- the processing of the output of the previous step. Note that more than -- one step cannot run concurrently as the next step depends on the -- output of the previous step. -- --
--   >>> :{
--   let f b =
--           if b > 2
--           then return Nothing
--           else threadDelay 1000000 >> return (Just (b, b + 1))
--   in Stream.toList $ Stream.delay 1 $ Stream.fromAsync $ Stream.unfoldrM f 0
--   :}
--   [0,1,2]
--   
-- -- Concurrent -- -- Since: 0.1.0 unfoldrM :: forall t m b a. (IsStream t, MonadAsync m) => (b -> m (Maybe (a, b))) -> b -> t m a -- |
--   fromPure a = a `cons` nil
--   
-- -- Create a singleton stream from a pure value. -- -- The following holds in monadic streams, but not in Zip streams: -- --
--   fromPure = pure
--   fromPure = fromEffect . pure
--   
-- -- In Zip applicative streams fromPure is not the same as -- pure because in that case pure is equivalent to -- repeat instead. fromPure and pure are equally -- efficient, in other cases fromPure may be slightly more -- efficient than the other equivalent definitions. -- -- Since: 0.8.0 (Renamed yield to fromPure) fromPure :: IsStream t => a -> t m a -- |
--   fromEffect m = m `consM` nil
--   
-- -- Create a singleton stream from a monadic action. -- --
--   > Stream.toList $ Stream.fromEffect getLine
--   hello
--   ["hello"]
--   
-- -- Since: 0.8.0 (Renamed yieldM to fromEffect) fromEffect :: (Monad m, IsStream t) => m a -> t m a -- | Generate an infinite stream by repeating a pure value. repeat :: (IsStream t, Monad m) => a -> t m a -- |
--   >>> repeatM = fix . consM
--   
--   >>> repeatM = cycle1 . fromEffect
--   
-- -- Generate a stream by repeatedly executing a monadic action forever. -- --
--   >>> :{
--   repeatAsync =
--          Stream.repeatM (threadDelay 1000000 >> print 1)
--        & Stream.take 10
--        & Stream.fromAsync
--        & Stream.drain
--   :}
--   
-- -- Concurrent, infinite (do not use with fromParallel) repeatM :: (IsStream t, MonadAsync m) => m a -> t m a -- |
--   >>> replicate n = Stream.take n . Stream.repeat
--   
-- -- Generate a stream of length n by repeating a value n -- times. replicate :: (IsStream t, Monad m) => Int -> a -> t m a -- |
--   >>> replicateM n = Stream.take n . Stream.repeatM
--   
-- -- Generate a stream by performing a monadic action n times. -- Same as: -- --
--   >>> pr n = threadDelay 1000000 >> print n
--   
-- -- This runs serially and takes 3 seconds: -- --
--   >>> Stream.drain $ Stream.fromSerial $ Stream.replicateM 3 $ pr 1
--   1
--   1
--   1
--   
-- -- This runs concurrently and takes just 1 second: -- --
--   >>> Stream.drain $ Stream.fromAsync  $ Stream.replicateM 3 $ pr 1
--   1
--   1
--   1
--   
-- -- Concurrent replicateM :: forall t m a. (IsStream t, MonadAsync m) => Int -> m a -> t m a -- | Types that can be enumerated as a stream. The operations in this type -- class are equivalent to those in the Enum type class, except -- that these generate a stream instead of a list. Use the functions in -- Streamly.Internal.Data.Stream.Enumeration module to define new -- instances. class Enum a => Enumerable a -- | enumerateFrom from generates a stream starting with the -- element from, enumerating up to maxBound when the type -- is Bounded or generating an infinite stream when the type is -- not Bounded. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFrom (0 :: Int)
--   [0,1,2,3]
--   
-- -- For Fractional types, enumeration is numerically stable. -- However, no overflow or underflow checks are performed. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFrom 1.1
--   [1.1,2.1,3.1,4.1]
--   
enumerateFrom :: (Enumerable a, IsStream t, Monad m) => a -> t m a -- | Generate a finite stream starting with the element from, -- enumerating the type up to the value to. If to is -- smaller than from then an empty stream is returned. -- --
--   >>> Stream.toList $ Stream.enumerateFromTo 0 4
--   [0,1,2,3,4]
--   
-- -- For Fractional types, the last element is equal to the -- specified to value after rounding to the nearest integral -- value. -- --
--   >>> Stream.toList $ Stream.enumerateFromTo 1.1 4
--   [1.1,2.1,3.1,4.1]
--   
--   >>> Stream.toList $ Stream.enumerateFromTo 1.1 4.6
--   [1.1,2.1,3.1,4.1,5.1]
--   
enumerateFromTo :: (Enumerable a, IsStream t, Monad m) => a -> a -> t m a -- | enumerateFromThen from then generates a stream whose first -- element is from, the second element is then and the -- successive elements are in increments of then - from. -- Enumeration can occur downwards or upwards depending on whether -- then comes before or after from. For Bounded -- types the stream ends when maxBound is reached, for unbounded -- types it keeps enumerating infinitely. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThen 0 2
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThen 0 (-2)
--   [0,-2,-4,-6]
--   
enumerateFromThen :: (Enumerable a, IsStream t, Monad m) => a -> a -> t m a -- | enumerateFromThenTo from then to generates a finite stream -- whose first element is from, the second element is -- then and the successive elements are in increments of -- then - from up to to. Enumeration can occur -- downwards or upwards depending on whether then comes before -- or after from. -- --
--   >>> Stream.toList $ Stream.enumerateFromThenTo 0 2 6
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.enumerateFromThenTo 0 (-2) (-6)
--   [0,-2,-4,-6]
--   
enumerateFromThenTo :: (Enumerable a, IsStream t, Monad m) => a -> a -> a -> t m a -- |
--   enumerate = enumerateFrom minBound
--   
-- -- Enumerate a Bounded type from its minBound to -- maxBound enumerate :: (IsStream t, Monad m, Bounded a, Enumerable a) => t m a -- |
--   enumerateTo = enumerateFromTo minBound
--   
-- -- Enumerate a Bounded type from its minBound to specified -- value. enumerateTo :: (IsStream t, Monad m, Bounded a, Enumerable a) => a -> t m a -- | times returns a stream of time value tuples with clock of 10 -- ms granularity. The first component of the tuple is an absolute time -- reference (epoch) denoting the start of the stream and the second -- component is a time relative to the reference. -- --
--   >>> Stream.mapM_ (\x -> print x >> threadDelay 1000000) $ Stream.take 3 $ Stream.times
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),RelTime64 (NanoSecond64 ...))
--   
-- -- Note: This API is not safe on 32-bit machines. -- -- Pre-release times :: (IsStream t, MonadAsync m) => t m (AbsTime, RelTime64) -- | absTimes returns a stream of absolute timestamps using a -- clock of 10 ms granularity. -- --
--   >>> Stream.mapM_ print $ Stream.delayPre 1 $ Stream.take 3 $ Stream.absTimes
--   AbsTime (TimeSpec {sec = ..., nsec = ...})
--   AbsTime (TimeSpec {sec = ..., nsec = ...})
--   AbsTime (TimeSpec {sec = ..., nsec = ...})
--   
-- -- Note: This API is not safe on 32-bit machines. -- -- Pre-release absTimes :: (IsStream t, MonadAsync m, Functor (t m)) => t m AbsTime -- | absTimesWith g returns a stream of absolute timestamps using -- a clock of granularity g specified in seconds. A low -- granularity clock is more expensive in terms of CPU usage. Any -- granularity lower than 1 ms is treated as 1 ms. -- --
--   >>> Stream.mapM_ print $ Stream.delayPre 1 $ Stream.take 3 $ absTimesWith 0.01
--   AbsTime (TimeSpec {sec = ..., nsec = ...})
--   AbsTime (TimeSpec {sec = ..., nsec = ...})
--   AbsTime (TimeSpec {sec = ..., nsec = ...})
--   
-- -- Note: This API is not safe on 32-bit machines. -- -- Pre-release absTimesWith :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m AbsTime -- | relTimes returns a stream of relative time values starting -- from 0, using a clock of granularity 10 ms. -- --
--   >>> Stream.mapM_ print $ Stream.delayPre 1 $ Stream.take 3 $ Stream.relTimes
--   RelTime64 (NanoSecond64 ...)
--   RelTime64 (NanoSecond64 ...)
--   RelTime64 (NanoSecond64 ...)
--   
-- -- Note: This API is not safe on 32-bit machines. -- -- Pre-release relTimes :: (IsStream t, MonadAsync m, Functor (t m)) => t m RelTime64 -- | relTimesWith g returns a stream of relative time values -- starting from 0, using a clock of granularity g specified in -- seconds. A low granularity clock is more expensive in terms of CPU -- usage. Any granularity lower than 1 ms is treated as 1 ms. -- --
--   >>> Stream.mapM_ print $ Stream.delayPre 1 $ Stream.take 3 $ Stream.relTimesWith 0.01
--   RelTime64 (NanoSecond64 ...)
--   RelTime64 (NanoSecond64 ...)
--   RelTime64 (NanoSecond64 ...)
--   
-- -- Note: This API is not safe on 32-bit machines. -- -- Pre-release relTimesWith :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m RelTime64 -- | durations g returns a stream of relative time values -- measuring the time elapsed since the immediate predecessor element of -- the stream was generated. The first element of the stream is always 0. -- durations uses a clock of granularity g specified in -- seconds. A low granularity clock is more expensive in terms of CPU -- usage. The minimum granularity is 1 millisecond. Durations lower than -- 1 ms will be 0. -- -- Note: This API is not safe on 32-bit machines. -- -- Unimplemented durations :: Double -> t m RelTime64 -- | Generate ticks at the specified rate. The rate is adaptive, the tick -- generation speed can be increased or decreased at different times to -- achieve the specified rate. The specific behavior for different styles -- of Rate specifications is documented under Rate. The -- effective maximum rate achieved by a stream is governed by the -- processor speed. -- -- Unimplemented ticks :: Rate -> t m () -- | Generate a singleton event at or after the specified absolute time. -- Note that this is different from a threadDelay, a threadDelay starts -- from the time when the action is evaluated, whereas if we use AbsTime -- based timeout it will immediately expire if the action is evaluated -- too late. -- -- Unimplemented timeout :: AbsTime -> t m () -- |
--   >>> fromIndices f = fmap f $ Stream.enumerateFrom 0
--   
--   >>> fromIndices f = let g i = f i `Stream.cons` g (i + 1) in g 0
--   
-- -- Generate an infinite stream, whose values are the output of a function -- f applied on the corresponding index. Index starts at 0. -- --
--   >>> Stream.toList $ Stream.take 5 $ Stream.fromIndices id
--   [0,1,2,3,4]
--   
fromIndices :: (IsStream t, Monad m) => (Int -> a) -> t m a -- |
--   >>> fromIndicesM f = Stream.mapM f $ Stream.enumerateFrom 0
--   
--   >>> fromIndicesM f = let g i = f i `Stream.consM` g (i + 1) in g 0
--   
-- -- Generate an infinite stream, whose values are the output of a monadic -- function f applied on the corresponding index. Index starts -- at 0. -- -- Concurrent fromIndicesM :: forall t m a. (IsStream t, MonadAsync m) => (Int -> m a) -> t m a -- |
--   >>> iterate f x = x `Stream.cons` iterate f x
--   
-- -- Generate an infinite stream with x as the first element and -- each successive element derived by applying the function f on -- the previous element. -- --
--   >>> Stream.toList $ Stream.take 5 $ Stream.iterate (+1) 1
--   [1,2,3,4,5]
--   
iterate :: (IsStream t, Monad m) => (a -> a) -> a -> t m a -- |
--   >>> iterateM f m = m >>= \a -> return a `Stream.consM` iterateM f (f a)
--   
-- -- Generate an infinite stream with the first element generated by the -- action m and each successive element derived by applying the -- monadic function f on the previous element. -- --
--   >>> pr n = threadDelay 1000000 >> print n
--   
--   >>> :{
--   Stream.iterateM (\x -> pr x >> return (x + 1)) (return 0)
--       & Stream.take 3
--       & Stream.fromSerial
--       & Stream.toList
--   :}
--   0
--   1
--   [0,1,2]
--   
-- -- When run concurrently, the next iteration can run concurrently with -- the processing of the previous iteration. Note that more than one -- iteration cannot run concurrently as the next iteration depends on the -- output of the previous iteration. -- --
--   >>> :{
--   Stream.iterateM (\x -> pr x >> return (x + 1)) (return 0)
--       & Stream.delay 1
--       & Stream.take 3
--       & Stream.fromAsync
--       & Stream.toList
--   :}
--   0
--   1
--   ...
--   
-- -- Concurrent -- -- Since: 0.1.2 -- -- Since: 0.7.0 (signature change) iterateM :: forall t m a. (IsStream t, MonadAsync m) => (a -> m a) -> m a -> t m a -- | We can define cyclic structures using let: -- --
--   >>> let (a, b) = ([1, b], head a) in (a, b)
--   ([1,1],1)
--   
-- -- The function fix defined as: -- --
--   >>> fix f = let x = f x in x
--   
-- -- ensures that the argument of a function and its output refer to the -- same lazy value x i.e. the same location in memory. Thus -- x can be defined in terms of itself, creating structures with -- cyclic references. -- --
--   >>> f ~(a, b) = ([1, b], head a)
--   
--   >>> fix f
--   ([1,1],1)
--   
-- -- mfix is essentially the same as fix but for monadic -- values. -- -- Using mfix for streams we can construct a stream in which each -- element of the stream is defined in a cyclic fashion. The argument of -- the function being fixed represents the current element of the stream -- which is being returned by the stream monad. Thus, we can use the -- argument to construct itself. -- -- In the following example, the argument action of the function -- f represents the tuple (x,y) returned by it in a -- given iteration. We define the first element of the tuple in terms of -- the second. -- --
--   >>> import Streamly.Internal.Data.Stream.IsStream as Stream
--   
--   >>> import System.IO.Unsafe (unsafeInterleaveIO)
--   
-- --
--   >>> :{
--   main = Stream.mapM_ print $ Stream.mfix f
--       where
--       f action = do
--           let incr n act = fmap ((+n) . snd) $ unsafeInterleaveIO act
--           x <- Stream.fromListM [incr 1 action, incr 2 action]
--           y <- Stream.fromList [4,5]
--           return (x, y)
--   :}
--   
-- -- Note: you cannot achieve this by just changing the order of the monad -- statements because that would change the order in which the stream -- elements are generated. -- -- Note that the function f must be lazy in its argument, that's -- why we use unsafeInterleaveIO on action because IO -- monad is strict. -- -- Pre-release mfix :: (IsStream t, Monad m) => (m a -> t m a) -> t m a -- |
--   fromList = foldr cons nil
--   
-- -- Construct a stream from a list of pure values. This is more efficient -- than fromFoldable for serial streams. fromList :: (Monad m, IsStream t) => [a] -> t m a -- |
--   >>> fromListM = Stream.fromFoldableM
--   
--   >>> fromListM = Stream.sequence . Stream.fromList
--   
--   >>> fromListM = Stream.mapM id . Stream.fromList
--   
--   >>> fromListM = Prelude.foldr Stream.consM Stream.nil
--   
-- -- Construct a stream from a list of monadic actions. This is more -- efficient than fromFoldableM for serial streams. fromListM :: (MonadAsync m, IsStream t) => [m a] -> t m a -- |
--   >>> fromFoldable = Prelude.foldr Stream.cons Stream.nil
--   
-- -- Construct a stream from a Foldable containing pure values: fromFoldable :: (IsStream t, Foldable f) => f a -> t m a -- |
--   >>> fromFoldableM = Prelude.foldr Stream.consM Stream.nil
--   
-- -- Construct a stream from a Foldable containing monadic actions. -- --
--   >>> pr n = threadDelay 1000000 >> print n
--   
--   >>> Stream.drain $ Stream.fromSerial $ Stream.fromFoldableM $ map pr [1,2,3]
--   1
--   2
--   3
--   
-- --
--   >>> Stream.drain $ Stream.fromAsync $ Stream.fromFoldableM $ map pr [1,2,3]
--   ...
--   ...
--   ...
--   
-- -- Concurrent (do not use with fromParallel on infinite -- containers) fromFoldableM :: (IsStream t, MonadAsync m, Foldable f) => f (m a) -> t m a -- | Takes a callback setter function and provides it with a callback. The -- callback when invoked adds a value at the tail of the stream. Returns -- a stream of values generated by the callback. -- -- Pre-release fromCallback :: MonadAsync m => ((a -> m ()) -> m ()) -> SerialT m a -- | Construct a stream by reading a Prim IORef repeatedly. -- -- Pre-release fromPrimIORef :: (IsStream t, MonadIO m, Prim a) => IORef a -> t m a -- | Same as fromEffect -- | Deprecated: Please use fromEffect instead. once :: (Monad m, IsStream t) => m a -> t m a -- | Same as fromPure -- | Deprecated: Please use fromPure instead. yield :: IsStream t => a -> t m a -- | Same as fromEffect -- | Deprecated: Please use fromEffect instead. yieldM :: (Monad m, IsStream t) => m a -> t m a -- | Same as fromFoldable. -- | Deprecated: Please use fromFoldable instead. each :: (IsStream t, Foldable f) => f a -> t m a -- | Read lines from an IO Handle into a stream of Strings. -- | Deprecated: Please use Streamly.FileSystem.Handle module (see the -- changelog) fromHandle :: (IsStream t, MonadIO m) => Handle -> t m String -- | Deprecated: Please use absTimes instead currentTime :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m AbsTime -- | Expand a stream by combining two or more streams or by combining -- streams with unfolds. module Streamly.Internal.Data.Stream.IsStream.Expand -- | Appends two streams sequentially, yielding all elements from the first -- stream, and then all elements from the second stream. -- --
--   >>> import Streamly.Prelude (serial)
--   
--   >>> stream1 = Stream.fromList [1,2]
--   
--   >>> stream2 = Stream.fromList [3,4]
--   
--   >>> Stream.toList $ stream1 `serial` stream2
--   [1,2,3,4]
--   
-- -- This operation can be used to fold an infinite lazy container of -- streams. -- -- Since: 0.2.0 (Streamly) serial :: IsStream t => t m a -> t m a -> t m a infixr 6 `serial` -- | Appends two streams, both the streams may be evaluated concurrently -- but the outputs are used in the same order as the corresponding -- actions in the original streams, side effects will happen in the order -- in which the streams are evaluated: -- --
--   >>> import Streamly.Prelude (ahead, SerialT)
--   
--   >>> stream1 = Stream.fromEffect (delay 4) :: SerialT IO Int
--   
--   >>> stream2 = Stream.fromEffect (delay 2) :: SerialT IO Int
--   
--   >>> Stream.toList $ stream1 `ahead` stream2 :: IO [Int]
--   2 sec
--   4 sec
--   [4,2]
--   
-- -- Multiple streams can be combined. With enough threads, all of them can -- be scheduled simultaneously: -- --
--   >>> stream3 = Stream.fromEffect (delay 1)
--   
--   >>> Stream.toList $ stream1 `ahead` stream2 `ahead` stream3
--   1 sec
--   2 sec
--   4 sec
--   [4,2,1]
--   
-- -- With 2 threads, only two can be scheduled at a time, when one of those -- finishes, the third one gets scheduled: -- --
--   >>> Stream.toList $ Stream.maxThreads 2 $ stream1 `ahead` stream2 `ahead` stream3
--   2 sec
--   1 sec
--   4 sec
--   [4,2,1]
--   
-- -- Only streams are scheduled for ahead evaluation, how actions within a -- stream are evaluated depends on the stream type. If it is a concurrent -- stream they will be evaluated concurrently. It may not make much sense -- combining serial streams using ahead. -- -- ahead can be safely used to fold an infinite lazy container of -- streams. -- -- Since: 0.3.0 (Streamly) ahead :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `ahead` -- | Merges two streams, both the streams may be evaluated concurrently, -- outputs from both are used as they arrive: -- --
--   >>> import Streamly.Prelude (async)
--   
--   >>> stream1 = Stream.fromEffect (delay 4)
--   
--   >>> stream2 = Stream.fromEffect (delay 2)
--   
--   >>> Stream.toList $ stream1 `async` stream2
--   2 sec
--   4 sec
--   [2,4]
--   
-- -- Multiple streams can be combined. With enough threads, all of them can -- be scheduled simultaneously: -- --
--   >>> stream3 = Stream.fromEffect (delay 1)
--   
--   >>> Stream.toList $ stream1 `async` stream2 `async` stream3
--   ...
--   [1,2,4]
--   
-- -- With 2 threads, only two can be scheduled at a time, when one of those -- finishes, the third one gets scheduled: -- --
--   >>> Stream.toList $ Stream.maxThreads 2 $ stream1 `async` stream2 `async` stream3
--   ...
--   [2,1,4]
--   
-- -- With a single thread, it becomes serial: -- --
--   >>> Stream.toList $ Stream.maxThreads 1 $ stream1 `async` stream2 `async` stream3
--   ...
--   [4,2,1]
--   
-- -- Only streams are scheduled for async evaluation, how actions within a -- stream are evaluated depends on the stream type. If it is a concurrent -- stream they will be evaluated concurrently. -- -- In the following example, both the streams are scheduled for -- concurrent evaluation but each individual stream is evaluated -- serially: -- --
--   >>> stream1 = Stream.fromListM $ Prelude.map delay [3,3] -- SerialT IO Int
--   
--   >>> stream2 = Stream.fromListM $ Prelude.map delay [1,1] -- SerialT IO Int
--   
--   >>> Stream.toList $ stream1 `async` stream2 -- IO [Int]
--   ...
--   [1,1,3,3]
--   
-- -- If total threads are 2, the third stream is scheduled only after one -- of the first two has finished: -- --
--   stream3 = Stream.fromListM $ Prelude.map delay [2,2] -- SerialT IO Int
--   Stream.toList $ Stream.maxThreads 2 $ stream1 `async` stream2 `async` stream3 -- IO [Int]
--   
-- -- ... [1,1,3,2,3,2] -- -- Thus async goes deep in first few streams rather than going -- wide in all streams. It prefers to evaluate the leftmost streams as -- much as possible. Because of this behavior, async can be safely -- used to fold an infinite lazy container of streams. -- -- Since: 0.2.0 (Streamly) async :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `async` -- | For singleton streams, wAsync is the same as async. See -- async for singleton stream behavior. For multi-element streams, -- while async is left biased i.e. it tries to evaluate the left -- side stream as much as possible, wAsync tries to schedule them -- both fairly. In other words, async goes deep while -- wAsync goes wide. However, outputs are always used as they -- arrive. -- -- With a single thread, async starts behaving like serial -- while wAsync starts behaving like wSerial. -- --
--   >>> import Streamly.Prelude (async, wAsync)
--   
--   >>> stream1 = Stream.fromList [1,2,3]
--   
--   >>> stream2 = Stream.fromList [4,5,6]
--   
--   >>> Stream.toList $ Stream.fromAsync $ Stream.maxThreads 1 $ stream1 `async` stream2
--   [1,2,3,4,5,6]
--   
-- --
--   >>> Stream.toList $ Stream.fromWAsync $ Stream.maxThreads 1 $ stream1 `wAsync` stream2
--   [1,4,2,5,3,6]
--   
-- -- With two threads available, and combining three streams: -- --
--   >>> stream3 = Stream.fromList [7,8,9]
--   
--   >>> Stream.toList $ Stream.fromAsync $ Stream.maxThreads 2 $ stream1 `async` stream2 `async` stream3
--   [1,2,3,4,5,6,7,8,9]
--   
-- --
--   >>> Stream.toList $ Stream.fromWAsync $ Stream.maxThreads 2 $ stream1 `wAsync` stream2 `wAsync` stream3
--   [1,4,2,7,5,3,8,6,9]
--   
-- -- This operation cannot be used to fold an infinite lazy container of -- streams, because it schedules all the streams in a round robin manner. -- -- Note that WSerialT and single threaded WAsyncT both -- interleave streams but the exact scheduling is slightly different in -- both cases. -- -- Since: 0.2.0 (Streamly) wAsync :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `wAsync` -- | Like async except that the execution is much more strict. There -- is no limit on the number of threads. While async may not -- schedule a stream if there is no demand from the consumer, -- parallel always evaluates both the streams immediately. The -- only limit that applies to parallel is maxBuffer. -- Evaluation may block if the output buffer becomes full. -- --
--   >>> import Streamly.Prelude (parallel)
--   
--   >>> stream = Stream.fromEffect (delay 2) `parallel` Stream.fromEffect (delay 1)
--   
--   >>> Stream.toList stream -- IO [Int]
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- parallel guarantees that all the streams are scheduled for -- execution immediately, therefore, we could use things like starting -- timers inside the streams and relying on the fact that all timers were -- started at the same time. -- -- Unlike async this operation cannot be used to fold an infinite -- lazy container of streams, because it schedules all the streams -- strictly concurrently. -- -- Since: 0.2.0 (Streamly) parallel :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `parallel` -- | Like parallel but stops the output as soon as the first -- stream stops. -- -- Pre-release parallelFst :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | Like parallel but stops the output as soon as any of the two -- streams stops. -- -- Pre-release parallelMin :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | Append the outputs of two streams, yielding all the elements from the -- first stream and then yielding all the elements from the second -- stream. -- -- IMPORTANT NOTE: This could be 100x faster than -- serial/<> for appending a few (say 100) streams because -- it can fuse via stream fusion. However, it does not scale for a large -- number of streams (say 1000s) and becomes qudartically slow. Therefore -- use this for custom appending of a few streams but use -- concatMap or 'concatMapWith serial' for appending n -- streams or infinite containers of streams. -- -- Pre-release append :: (IsStream t, Monad m) => t m b -> t m b -> t m b -- | Interleaves two streams, yielding one element from each stream -- alternately. When one stream stops the rest of the other stream is -- used in the output stream. -- --
--   >>> import Streamly.Prelude (wSerial)
--   
--   >>> stream1 = Stream.fromList [1,2]
--   
--   >>> stream2 = Stream.fromList [3,4]
--   
--   >>> Stream.toList $ Stream.fromWSerial $ stream1 `wSerial` stream2
--   [1,3,2,4]
--   
-- -- Note, for singleton streams wSerial and serial are -- identical. -- -- Note that this operation cannot be used to fold a container of -- infinite streams but it can be used for very large streams as the -- state that it needs to maintain is proportional to the logarithm of -- the number of streams. -- -- Since: 0.2.0 (Streamly) wSerial :: IsStream t => t m a -> t m a -> t m a infixr 6 `wSerial` wSerialFst :: WSerialT m a -> WSerialT m a -> WSerialT m a wSerialMin :: WSerialT m a -> WSerialT m a -> WSerialT m a -- | Interleaves the outputs of two streams, yielding elements from each -- stream alternately, starting from the first stream. If any of the -- streams finishes early the other stream continues alone until it too -- finishes. -- --
--   >>> :set -XOverloadedStrings
--   
--   >>> import Data.Functor.Identity (Identity)
--   
--   >>> Stream.interleave "ab" ",,,," :: Stream.SerialT Identity Char
--   fromList "a,b,,,"
--   
-- --
--   >>> Stream.interleave "abcd" ",," :: Stream.SerialT Identity Char
--   fromList "a,b,cd"
--   
-- -- interleave is dual to interleaveMin, it can be called -- interleaveMax. -- -- Do not use at scale in concatMapWith. -- -- Pre-release interleave :: (IsStream t, Monad m) => t m b -> t m b -> t m b -- | Interleaves the outputs of two streams, yielding elements from each -- stream alternately, starting from the first stream. The output stops -- as soon as any of the two streams finishes, discarding the remaining -- part of the other stream. The last element of the resulting stream -- would be from the longer stream. -- --
--   >>> :set -XOverloadedStrings
--   
--   >>> import Data.Functor.Identity (Identity)
--   
--   >>> Stream.interleaveMin "ab" ",,,," :: Stream.SerialT Identity Char
--   fromList "a,b,"
--   
--   >>> Stream.interleaveMin "abcd" ",," :: Stream.SerialT Identity Char
--   fromList "a,b,c"
--   
-- -- interleaveMin is dual to interleave. -- -- Do not use at scale in concatMapWith. -- -- Pre-release interleaveMin :: (IsStream t, Monad m) => t m b -> t m b -> t m b -- | Interleaves the outputs of two streams, yielding elements from each -- stream alternately, starting from the first stream. As soon as the -- first stream finishes, the output stops, discarding the remaining part -- of the second stream. In this case, the last element in the resulting -- stream would be from the second stream. If the second stream finishes -- early then the first stream still continues to yield elements until it -- finishes. -- --
--   >>> :set -XOverloadedStrings
--   
--   >>> import Data.Functor.Identity (Identity)
--   
--   >>> Stream.interleaveSuffix "abc" ",,,," :: Stream.SerialT Identity Char
--   fromList "a,b,c,"
--   
--   >>> Stream.interleaveSuffix "abc" "," :: Stream.SerialT Identity Char
--   fromList "a,bc"
--   
-- -- interleaveSuffix is a dual of interleaveInfix. -- -- Do not use at scale in concatMapWith. -- -- Pre-release interleaveSuffix :: (IsStream t, Monad m) => t m b -> t m b -> t m b -- | Interleaves the outputs of two streams, yielding elements from each -- stream alternately, starting from the first stream and ending at the -- first stream. If the second stream is longer than the first, elements -- from the second stream are infixed with elements from the first -- stream. If the first stream is longer then it continues yielding -- elements even after the second stream has finished. -- --
--   >>> :set -XOverloadedStrings
--   
--   >>> import Data.Functor.Identity (Identity)
--   
--   >>> Stream.interleaveInfix "abc" ",,,," :: Stream.SerialT Identity Char
--   fromList "a,b,c"
--   
--   >>> Stream.interleaveInfix "abc" "," :: Stream.SerialT Identity Char
--   fromList "a,bc"
--   
-- -- interleaveInfix is a dual of interleaveSuffix. -- -- Do not use at scale in concatMapWith. -- -- Pre-release interleaveInfix :: (IsStream t, Monad m) => t m b -> t m b -> t m b -- | Schedule the execution of two streams in a fair round-robin manner, -- executing each stream once, alternately. Execution of a stream may not -- necessarily result in an output, a stream may chose to Skip -- producing an element until later giving the other stream a chance to -- run. Therefore, this combinator fairly interleaves the execution of -- two streams rather than fairly interleaving the output of the two -- streams. This can be useful in co-operative multitasking without using -- explicit threads. This can be used as an alternative to async. -- -- Do not use at scale in concatMapWith. -- -- Pre-release roundrobin :: (IsStream t, Monad m) => t m b -> t m b -> t m b -- | Stream a is evaluated first, followed by stream b, -- the resulting elements a and b are then zipped using -- the supplied zip function and the result c is yielded to the -- consumer. -- -- If stream a or stream b ends, the zipped stream -- ends. If stream b ends first, the element a from -- previous evaluation of stream a is discarded. -- --
--   > S.toList $ S.zipWith (+) (S.fromList [1,2,3]) (S.fromList [4,5,6])
--   [5,7,9]
--   
zipWith :: (IsStream t, Monad m) => (a -> b -> c) -> t m a -> t m b -> t m c -- | Like zipWith but using a monadic zipping function. zipWithM :: (IsStream t, Monad m) => (a -> b -> m c) -> t m a -> t m b -> t m c -- | Like zipWith but zips concurrently i.e. both the streams being -- zipped are evaluated concurrently using the ParallelT -- concurrent evaluation style. The maximum number of elements of each -- stream evaluated in advance can be controlled by maxBuffer. -- -- The stream ends if stream a or stream b ends. -- However, if stream b ends while we are still evaluating -- stream a and waiting for a result then stream will not end -- until after the evaluation of stream a finishes. This -- behavior can potentially be changed in future to end the stream -- immediately as soon as any of the stream end is detected. zipAsyncWith :: (IsStream t, MonadAsync m) => (a -> b -> c) -> t m a -> t m b -> t m c -- | Like zipAsyncWith but with a monadic zipping function. zipAsyncWithM :: (IsStream t, MonadAsync m) => (a -> b -> m c) -> t m a -> t m b -> t m c -- | Merge two streams using a comparison function. The head elements of -- both the streams are compared and the smaller of the two elements is -- emitted, if both elements are equal then the element from the first -- stream is used first. -- -- If the streams are sorted in ascending order, the resulting stream -- would also remain sorted in ascending order. -- --
--   >>> Stream.toList $ Stream.mergeBy compare (Stream.fromList [1,3,5]) (Stream.fromList [2,4,6,8])
--   [1,2,3,4,5,6,8]
--   
-- -- See also: mergeByMFused mergeBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> t m a -> t m a -> t m a -- | Like mergeBy but with a monadic comparison function. -- -- Merge two streams randomly: -- --
--   > randomly _ _ = randomIO >>= x -> return $ if x then LT else GT
--   > Stream.toList $ Stream.mergeByM randomly (Stream.fromList [1,1,1,1]) (Stream.fromList [2,2,2,2])
--   [2,1,2,2,2,1,1,1]
--   
-- -- Merge two streams in a proportion of 2:1: -- --
--   >>> :{
--   do
--    let proportionately m n = do
--         ref <- newIORef $ cycle $ Prelude.concat [Prelude.replicate m LT, Prelude.replicate n GT]
--         return $ _ _ -> do
--            r <- readIORef ref
--            writeIORef ref $ Prelude.tail r
--            return $ Prelude.head r
--    f <- proportionately 2 1
--    xs <- Stream.toList $ Stream.mergeByM f (Stream.fromList [1,1,1,1,1,1]) (Stream.fromList [2,2,2])
--    print xs
--   :}
--   [1,1,2,1,1,2,1,1,2]
--   
-- -- See also: mergeByMFused mergeByM :: (IsStream t, Monad m) => (a -> a -> m Ordering) -> t m a -> t m a -> t m a -- | Like mergeByM but much faster, works best when merging -- statically known number of streams. When merging more than two streams -- try to merge pairs and pair pf pairs in a tree like -- structure.mergeByM works better with variable number of streams -- being merged using concatPairsWith. -- -- Internal mergeByMFused :: (IsStream t, Monad m) => (a -> a -> m Ordering) -> t m a -> t m a -> t m a -- | Like mergeBy but merges concurrently (i.e. both the elements -- being merged are generated concurrently). mergeAsyncBy :: (IsStream t, MonadAsync m) => (a -> a -> Ordering) -> t m a -> t m a -> t m a -- | Like mergeByM but merges concurrently (i.e. both the elements -- being merged are generated concurrently). mergeAsyncByM :: (IsStream t, MonadAsync m) => (a -> a -> m Ordering) -> t m a -> t m a -> t m a -- | Like concatMap but uses an Unfold for stream generation. -- Unlike concatMap this can fuse the Unfold code with the -- inner loop and therefore provide many times better performance. unfoldMany :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b -- | Like unfoldMany but interleaves the streams in the same way as -- interleave behaves instead of appending them. -- -- Pre-release unfoldManyInterleave :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b -- | Like unfoldMany but executes the streams in the same way as -- roundrobin. -- -- Pre-release unfoldManyRoundRobin :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b -- | Unfold the elements of a stream, intersperse the given element between -- the unfolded streams and then concat them into a single stream. -- --
--   unwords = S.interpose ' '
--   
-- -- Pre-release interpose :: (IsStream t, Monad m) => c -> Unfold m b c -> t m b -> t m c -- | Unfold the elements of a stream, append the given element after each -- unfolded stream and then concat them into a single stream. -- --
--   unlines = S.interposeSuffix '\n'
--   
-- -- Pre-release interposeSuffix :: (IsStream t, Monad m) => c -> Unfold m b c -> t m b -> t m c -- | intersperse followed by unfold and concat. -- --
--   intercalate unf a str = unfoldMany unf $ intersperse a str
--   intersperse = intercalate (Unfold.function id)
--   unwords = intercalate Unfold.fromList " "
--   
-- --
--   >>> Stream.toList $ Stream.intercalate Unfold.fromList " " $ Stream.fromList ["abc", "def", "ghi"]
--   "abc def ghi"
--   
intercalate :: (IsStream t, Monad m) => Unfold m b c -> b -> t m b -> t m c -- | intersperseSuffix followed by unfold and concat. -- --
--   intercalateSuffix unf a str = unfoldMany unf $ intersperseSuffix a str
--   intersperseSuffix = intercalateSuffix (Unfold.function id)
--   unlines = intercalateSuffix Unfold.fromList "\n"
--   
-- --
--   >>> Stream.toList $ Stream.intercalateSuffix Unfold.fromList "\n" $ Stream.fromList ["abc", "def", "ghi"]
--   "abc\ndef\nghi\n"
--   
intercalateSuffix :: (IsStream t, Monad m) => Unfold m b c -> b -> t m b -> t m c -- | interleaveInfix followed by unfold and concat. -- -- Pre-release gintercalate :: (IsStream t, Monad m) => Unfold m a c -> t m a -> Unfold m b c -> t m b -> t m c -- | interleaveSuffix followed by unfold and concat. -- -- Pre-release gintercalateSuffix :: (IsStream t, Monad m) => Unfold m a c -> t m a -> Unfold m b c -> t m b -> t m c -- | Map a stream producing monadic function on each element of the stream -- and then flatten the results into a single stream. Since the stream -- generation function is monadic, unlike concatMap, it can -- produce an effect at the beginning of each iteration of the inner -- loop. concatMapM :: (IsStream t, Monad m) => (a -> m (t m b)) -> t m a -> t m b -- | Map a stream producing function on each element of the stream and then -- flatten the results into a single stream. -- --
--   >>> concatMap f = Stream.concatMapM (return . f)
--   
--   >>> concatMap f = Stream.concatMapWith Stream.serial f
--   
--   >>> concatMap f = Stream.concat . Stream.map f
--   
--   >>> concatMap f = Stream.unfoldMany (Unfold.lmap f Unfold.fromStream)
--   
concatMap :: (IsStream t, Monad m) => (a -> t m b) -> t m a -> t m b -- | Given a stream value in the underlying monad, lift and join the -- underlying monad with the stream monad. -- --
--   >>> concatM = Stream.concat . Stream.fromEffect
--   
--   >>> concatM = Stream.concat . lift    -- requires (MonadTrans t)
--   
--   >>> concatM = join . lift             -- requires (MonadTrans t, Monad (t m))
--   
-- -- See also: concat, sequence -- -- Internal concatM :: (IsStream t, Monad m) => m (t m a) -> t m a -- | Flatten a stream of streams to a single stream. -- --
--   concat = concatMap id
--   
-- -- Pre-release concat :: (IsStream t, Monad m) => t m (t m a) -> t m a -- | A variant of fold that allows you to fold a Foldable -- container of streams using the specified stream sum operation. -- --
--   concatFoldableWith async $ map return [1..3]
--   
-- -- Equivalent to: -- --
--   concatFoldableWith f = Prelude.foldr f S.nil
--   concatFoldableWith f = S.concatMapFoldableWith f id
--   
-- -- Since: 0.8.0 (Renamed foldWith to concatFoldableWith) -- -- Since: 0.1.0 (Streamly) concatFoldableWith :: (IsStream t, Foldable f) => (t m a -> t m a -> t m a) -> f (t m a) -> t m a -- | A variant of foldMap that allows you to map a monadic streaming -- action on a Foldable container and then fold it using the -- specified stream merge operation. -- --
--   concatMapFoldableWith async return [1..3]
--   
-- -- Equivalent to: -- --
--   concatMapFoldableWith f g = Prelude.foldr (f . g) S.nil
--   concatMapFoldableWith f g xs = S.concatMapWith f g (S.fromFoldable xs)
--   
-- -- Since: 0.8.0 (Renamed foldMapWith to concatMapFoldableWith) -- -- Since: 0.1.0 (Streamly) concatMapFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b -- | Like concatMapFoldableWith but with the last two arguments -- reversed i.e. the monadic streaming function is the last argument. -- -- Equivalent to: -- --
--   concatForFoldableWith f xs g = Prelude.foldr (f . g) S.nil xs
--   concatForFoldableWith f = flip (S.concatMapFoldableWith f)
--   
-- -- Since: 0.8.0 (Renamed forEachWith to concatForFoldableWith) -- -- Since: 0.1.0 (Streamly) concatForFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b -- | concatMapWith mixer generator stream is a two dimensional -- looping combinator. The generator function is used to -- generate streams from the elements in the input stream and -- the mixer function is used to merge those streams. -- -- Note we can merge streams concurrently by using a concurrent merge -- function. -- -- Since: 0.7.0 -- -- Since: 0.8.0 (signature change) concatMapWith :: IsStream t => (t m b -> t m b -> t m b) -> (a -> t m b) -> t m a -> t m b bindWith :: IsStream t => (t m b -> t m b -> t m b) -> t m a -> (a -> t m b) -> t m b -- | Like concatMapWith but carries a state which can be used to -- share information across multiple steps of concat. -- --
--   concatSmapMWith combine f initial = concatMapWith combine id . smapM f initial
--   
-- -- Pre-release concatSmapMWith :: (IsStream t, Monad m) => (t m b -> t m b -> t m b) -> (s -> a -> m (s, t m b)) -> m s -> t m a -> t m b -- | Combine streams in pairs using a binary stream combinator, then -- combine the resulting streams in pairs recursively until we get to a -- single combined stream. -- -- For example, you can sort a stream using merge sort like this: -- --
--   >>> Stream.toList $ Stream.concatPairsWith (Stream.mergeBy compare) Stream.fromPure $ Stream.fromList [5,1,7,9,2]
--   [1,2,5,7,9]
--   
-- -- Caution: the stream of streams must be finite -- -- Pre-release concatPairsWith :: IsStream t => (t m b -> t m b -> t m b) -> (a -> t m b) -> t m a -> t m b -- | Like iterateM but iterates after mapping a stream generator -- on the output. -- -- Yield an input element in the output stream, map a stream generator on -- it and then do the same on the resulting stream. This can be used for -- a depth first traversal of a tree like structure. -- -- Note that iterateM is a special case of -- iterateMapWith: -- --
--   iterateM f = iterateMapWith serial (fromEffect . f) . fromEffect
--   
-- -- It can be used to traverse a tree structure. For example, to list a -- directory tree: -- --
--   Stream.iterateMapWith Stream.serial
--       (either Dir.toEither (const nil))
--       (fromPure (Left "tmp"))
--   
-- -- Pre-release iterateMapWith :: IsStream t => (t m a -> t m a -> t m a) -> (a -> t m a) -> t m a -> t m a -- | Like iterateMap but carries a state in the stream generation -- function. This can be used to traverse graph like structures, we can -- remember the visited nodes in the state to avoid cycles. -- -- Note that a combination of iterateMap and usingState -- can also be used to traverse graphs. However, this function provides a -- more localized state instead of using a global state. -- -- See also: mfix -- -- Pre-release iterateSmapMWith :: (IsStream t, Monad m) => (t m a -> t m a -> t m a) -> (b -> a -> m (b, t m a)) -> m b -> t m a -> t m a -- | In an Either stream iterate on Lefts. This is a special -- case of iterateMapWith: -- --
--   iterateMapLeftsWith combine f = iterateMapWith combine (either f (const nil))
--   
-- -- To traverse a directory tree: -- --
--   iterateMapLeftsWith serial Dir.toEither (fromPure (Left "tmp"))
--   
-- -- Pre-release iterateMapLeftsWith :: IsStream t => (t m (Either a b) -> t m (Either a b) -> t m (Either a b)) -> (a -> t m (Either a b)) -> t m (Either a b) -> t m (Either a b) -- | Deprecated: Please use unfoldMany instead. concatUnfold :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b -- | Same as wSerial. -- | Deprecated: Please use wSerial instead. (<=>) :: IsStream t => t m a -> t m a -> t m a infixr 5 <=> -- | Same as async. -- | Deprecated: Please use async instead. (<|) :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | This module contains functions ending in the shape: -- --
--   t m a -> m b
--   
-- -- We call them stream folding functions, they reduce a stream t m -- a to a monadic value m b. module Streamly.Internal.Data.Stream.IsStream.Eliminate -- | Fold a stream using the supplied left Fold and reducing the -- resulting expression strictly at each step. The behavior is similar to -- foldl'. A Fold can terminate early without consuming -- the full stream. See the documentation of individual Folds for -- termination behavior. -- --
--   >>> Stream.fold Fold.sum (Stream.enumerateFromTo 1 100)
--   5050
--   
-- -- Folds never fail, therefore, they produce a default value even when no -- input is provided. It means we can always fold an empty stream and get -- a valid result. For example: -- --
--   >>> Stream.fold Fold.sum Stream.nil
--   0
--   
-- -- However, foldMany on an empty stream results in an empty -- stream. Therefore, Stream.fold f is not the same as -- Stream.head . Stream.foldMany f. -- --
--   fold f = Stream.parse (Parser.fromFold f)
--   
fold :: Monad m => Fold m a b -> SerialT m a -> m b fold_ :: Monad m => Fold m a b -> SerialT m a -> m (b, SerialT m a) -- | We can create higher order folds using foldOn. We can fold a -- number of streams to a given fold efficiently with full stream fusion. -- For example, to fold a list of streams on the same sum fold: -- --
--   >>> concatFold = Prelude.foldl Stream.foldOn Fold.sum
--   
-- --
--   >>> fold f = Fold.finish . Stream.foldOn f
--   
-- -- Internal foldOn :: Monad m => Fold m a b -> SerialT m a -> Fold m a b -- | Parse a stream using the supplied Parser. -- -- Unlike folds, parsers may not always result in a valid output, they -- may result in an error. For example: -- --
--   >>> Stream.parse (Parser.takeEQ 1 Fold.drain) Stream.nil
--   *** Exception: ParseError "takeEQ: Expecting exactly 1 elements, input terminated on 0"
--   
-- -- Note: -- --
--   fold f = Stream.parse (Parser.fromFold f)
--   
-- -- parse p is not the same as head . parseMany p on an -- empty stream. -- -- Pre-release parse :: MonadThrow m => Parser m a b -> SerialT m a -> m b -- | Parse a stream using the supplied ParserK Parser. -- -- Internal parseK :: MonadThrow m => Parser m a b -> SerialT m a -> m b -- | Parse a stream using the supplied ParserD Parser. -- -- Internal parseD :: MonadThrow m => Parser m a b -> SerialT m a -> m b -- | Parse a stream using the supplied Parser. -- -- Internal parse_ :: MonadThrow m => Parser m a b -> SerialT m a -> m (b, SerialT m a) parseD_ :: MonadThrow m => Parser m a b -> SerialT m a -> m (b, SerialT m a) -- | Decompose a stream into its head and tail. If the stream is empty, -- returns Nothing. If the stream is non-empty, returns Just -- (a, ma), where a is the head of the stream and -- ma its tail. -- -- This is a brute force primitive. Avoid using it as long as possible, -- use it when no other combinator can do the job. This can be used to do -- pretty much anything in an imperative manner, as it just breaks down -- the stream into individual elements and we can loop over them as we -- deem fit. For example, this can be used to convert a streamly stream -- into other stream types. -- -- All the folds in this module can be expressed in terms of -- uncons, however the specific implementations are generally more -- efficient. uncons :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (a, t m a)) -- | Right associative/lazy pull fold. foldrM build final stream -- constructs an output structure using the step function build. -- build is invoked with the next input element and the -- remaining (lazy) tail of the output structure. It builds a lazy output -- expression using the two. When the "tail structure" in the output -- expression is evaluated it calls build again thus lazily -- consuming the input stream until either the output expression -- built by build is free of the "tail" or the input is -- exhausted in which case final is used as the terminating case -- for the output structure. For more details see the description in the -- previous section. -- -- Example, determine if any element is odd in a stream: -- --
--   >>> Stream.foldrM (\x xs -> if odd x then return True else xs) (return False) $ Stream.fromList (2:4:5:undefined)
--   True
--   
-- -- Since: 0.7.0 (signature changed) -- -- Since: 0.2.0 (signature changed) -- -- Since: 0.1.0 foldrM :: Monad m => (a -> m b -> m b) -> m b -> SerialT m a -> m b -- | Right fold, lazy for lazy monads and pure streams, and strict for -- strict monads. -- -- Please avoid using this routine in strict monads like IO unless you -- need a strict right fold. This is provided only for use in lazy monads -- (e.g. Identity) or pure streams. Note that with this signature it is -- not possible to implement a lazy foldr when the monad m is -- strict. In that case it would be strict in its accumulator and -- therefore would necessarily consume all its input. foldr :: Monad m => (a -> b -> b) -> b -> SerialT m a -> m b -- | Lazy left fold to a stream. foldlS :: IsStream t => (t m b -> a -> t m b) -> t m b -> t m a -> t m b -- | Lazy left fold to a transformer monad. -- -- For example, to reverse a stream: -- --
--   S.toList $ S.foldlT (flip S.cons) S.nil $ (S.fromList [1..5] :: SerialT IO Int)
--   
foldlT :: (Monad m, IsStream t, Monad (s m), MonadTrans s) => (s m b -> a -> s m b) -> s m b -> t m a -> s m b -- | Left associative/strict push fold. foldl' reduce initial -- stream invokes reduce with the accumulator and the next -- input in the input stream, using initial as the initial value -- of the current value of the accumulator. When the input is exhausted -- the current value of the accumulator is returned. Make sure to use a -- strict data structure for accumulator to not build unnecessary lazy -- expressions unless that's what you want. See the previous section for -- more details. foldl' :: Monad m => (b -> a -> b) -> b -> SerialT m a -> m b -- | Strict left fold, for non-empty streams, using first element as the -- starting value. Returns Nothing if the stream is empty. foldl1' :: Monad m => (a -> a -> a) -> SerialT m a -> m (Maybe a) -- | Like foldl' but with a monadic step function. -- -- Since: 0.2.0 -- -- Since: 0.8.0 (signature change) foldlM' :: Monad m => (b -> a -> m b) -> m b -> SerialT m a -> m b -- |
--   mapM_ = Stream.drain . Stream.mapM
--   
-- -- Apply a monadic action to each element of the stream and discard the -- output of the action. This is not really a pure transformation -- operation but a transformation followed by fold. mapM_ :: Monad m => (a -> m b) -> SerialT m a -> m () -- |
--   drain = mapM_ (\_ -> return ())
--   drain = Stream.fold Fold.drain
--   
-- -- Run a stream, discarding the results. By default it interprets the -- stream as SerialT, to run other types of streams use the type -- adapting combinators for example Stream.drain . -- fromAsync. drain :: Monad m => SerialT m a -> m () -- | Extract the last element of the stream, if any. -- --
--   last xs = xs !! (Stream.length xs - 1)
--   last = Stream.fold Fold.last
--   
last :: Monad m => SerialT m a -> m (Maybe a) -- | Determine the length of the stream. length :: Monad m => SerialT m a -> m Int -- | Determine the sum of all elements of a stream of numbers. Returns -- 0 when the stream is empty. Note that this is not numerically -- stable for floating point numbers. -- --
--   sum = Stream.fold Fold.sum
--   
sum :: (Monad m, Num a) => SerialT m a -> m a -- | Determine the product of all elements of a stream of numbers. Returns -- 1 when the stream is empty. -- --
--   product = Stream.fold Fold.product
--   
product :: (Monad m, Num a) => SerialT m a -> m a -- | Fold a stream of monoid elements by appending them. -- --
--   mconcat = Stream.fold Fold.mconcat
--   
-- -- Pre-release mconcat :: (Monad m, Monoid a) => SerialT m a -> m a -- | Determine the maximum element in a stream using the supplied -- comparison function. -- --
--   maximumBy = Stream.fold Fold.maximumBy
--   
maximumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) -- |
--   maximum = maximumBy compare
--   maximum = Stream.fold Fold.maximum
--   
-- -- Determine the maximum element in a stream. maximum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a) -- | Determine the minimum element in a stream using the supplied -- comparison function. -- --
--   minimumBy = Stream.fold Fold.minimumBy
--   
minimumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) -- |
--   minimum = minimumBy compare
--   minimum = Stream.fold Fold.minimum
--   
-- -- Determine the minimum element in a stream. minimum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a) -- | Ensures that all the elements of the stream are identical and then -- returns that unique element. the :: (Eq a, Monad m) => SerialT m a -> m (Maybe a) -- |
--   drainN n = Stream.drain . Stream.take n
--   drainN n = Stream.fold (Fold.take n Fold.drain)
--   
-- -- Run maximum up to n iterations of a stream. drainN :: Monad m => Int -> SerialT m a -> m () -- |
--   drainWhile p = Stream.drain . Stream.takeWhile p
--   
-- -- Run a stream as long as the predicate holds true. drainWhile :: Monad m => (a -> Bool) -> SerialT m a -> m () -- | Lookup the element at the given index. (!!) :: Monad m => SerialT m a -> Int -> m (Maybe a) -- | Extract the first element of the stream, if any. -- --
--   head = (!! 0)
--   head = Stream.fold Fold.head
--   
head :: Monad m => SerialT m a -> m (Maybe a) -- | Extract the first element of the stream, if any, otherwise use the -- supplied default value. It can help avoid one branch in high -- performance code. -- -- Pre-release headElse :: Monad m => a -> SerialT m a -> m a -- |
--   tail = fmap (fmap snd) . Stream.uncons
--   
-- -- Extract all but the first element of the stream, if any. tail :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (t m a)) -- | Extract all but the last element of the stream, if any. init :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (t m a)) -- | Returns the first element that satisfies the given predicate. -- --
--   findM = Stream.fold Fold.findM
--   
findM :: Monad m => (a -> m Bool) -> SerialT m a -> m (Maybe a) -- | Like findM but with a non-monadic predicate. -- --
--   find p = findM (return . p)
--   find = Stream.fold Fold.find
--   
find :: Monad m => (a -> Bool) -> SerialT m a -> m (Maybe a) -- | Returns the first index that satisfies the given predicate. -- --
--   findIndex = Stream.fold Fold.findIndex
--   
findIndex :: Monad m => (a -> Bool) -> SerialT m a -> m (Maybe Int) -- | Returns the first index where a given value is found in the stream. -- --
--   elemIndex a = Stream.findIndex (== a)
--   
elemIndex :: (Monad m, Eq a) => a -> SerialT m a -> m (Maybe Int) -- | In a stream of (key-value) pairs (a, b), return the value -- b of the first pair where the key equals the given value -- a. -- --
--   lookup = snd <$> Stream.find ((==) . fst)
--   lookup = Stream.fold Fold.lookup
--   
lookup :: (Monad m, Eq a) => a -> SerialT m (a, b) -> m (Maybe b) -- | Determine whether the stream is empty. -- --
--   null = Stream.fold Fold.null
--   
null :: Monad m => SerialT m a -> m Bool -- | Determine whether an element is present in the stream. -- --
--   elem = Stream.fold Fold.elem
--   
elem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool -- | Determine whether an element is not present in the stream. -- --
--   notElem = Stream.fold Fold.length
--   
notElem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool -- | Determine whether all elements of a stream satisfy a predicate. -- --
--   all = Stream.fold Fold.all
--   
all :: Monad m => (a -> Bool) -> SerialT m a -> m Bool -- | Determine whether any of the elements of a stream satisfy a predicate. -- --
--   any = Stream.fold Fold.any
--   
any :: Monad m => (a -> Bool) -> SerialT m a -> m Bool -- | Determines if all elements of a boolean stream are True. -- --
--   and = Stream.fold Fold.and
--   
and :: Monad m => SerialT m Bool -> m Bool -- | Determines whether at least one element of a boolean stream is True. -- --
--   or = Stream.fold Fold.or
--   
or :: Monad m => SerialT m Bool -> m Bool -- |
--   toList = Stream.foldr (:) []
--   
-- -- Convert a stream into a list in the underlying monad. The list can be -- consumed lazily in a lazy monad (e.g. Identity). In a strict -- monad (e.g. IO) the whole list is generated and buffered before it can -- be consumed. -- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using Streamly.Array -- instead. toList :: Monad m => SerialT m a -> m [a] -- |
--   toListRev = Stream.foldl' (flip (:)) []
--   
-- -- Convert a stream into a list in reverse order in the underlying monad. -- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using Streamly.Array -- instead. -- -- Pre-release toListRev :: Monad m => SerialT m a -> m [a] -- | Convert a stream to a pure stream. -- --
--   toStream = Stream.foldr Stream.cons Stream.nil
--   
-- -- Pre-release toStream :: Monad m => SerialT m a -> m (SerialT n a) -- | Convert a stream to a pure stream in reverse order. -- --
--   toStreamRev = Stream.foldl' (flip Stream.cons) Stream.nil
--   
-- -- Pre-release toStreamRev :: Monad m => SerialT m a -> m (SerialT n a) -- | Same as |$.. -- -- Internal foldAsync :: (IsStream t, MonadAsync m) => (t m a -> m b) -> t m a -> m b -- | Parallel fold application operator; applies a fold function t m a -- -> m b to a stream t m a concurrently; The the input -- stream is evaluated asynchronously in an independent thread yielding -- elements to a buffer and the folding action runs in another thread -- consuming the input from the buffer. -- -- If you read the signature as (t m a -> m b) -> (t m a -> -- m b) you can look at it as a transformation that converts a fold -- function to a buffered concurrent fold function. -- -- The . at the end of the operator is a mnemonic for -- termination of the stream. -- -- In the example below, each stage introduces a delay of 1 sec but -- output is printed every second because both stages are concurrent. -- --
--   >>> import Control.Concurrent (threadDelay)
--   
--   >>> import Streamly.Prelude ((|$.))
--   
--   >>> :{
--    Stream.foldlM' (\_ a -> threadDelay 1000000 >> print a) (return ())
--        |$. Stream.replicateM 3 (threadDelay 1000000 >> return 1)
--   :}
--   1
--   1
--   1
--   
-- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|$.) :: (IsStream t, MonadAsync m) => (t m a -> m b) -> t m a -> m b infixr 0 |$. -- | Same as |$. but with arguments reversed. -- --
--   (|&.) = flip (|$.)
--   
-- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|&.) :: (IsStream t, MonadAsync m) => t m a -> (t m a -> m b) -> m b infixl 1 |&. -- | Compare two streams for equality using an equality function. eqBy :: (IsStream t, Monad m) => (a -> b -> Bool) -> t m a -> t m b -> m Bool -- | Compare two streams lexicographically using a comparison function. cmpBy :: (IsStream t, Monad m) => (a -> b -> Ordering) -> t m a -> t m b -> m Ordering -- | Returns True if the first stream is the same as or a prefix of -- the second. A stream is a prefix of itself. -- --
--   >>> Stream.isPrefixOf (Stream.fromList "hello") (Stream.fromList "hello" :: SerialT IO Char)
--   True
--   
isPrefixOf :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m Bool -- | Returns True if the first stream is an infix of the second. A -- stream is considered an infix of itself. -- --
--   Stream.isInfixOf (Stream.fromList "hello") (Stream.fromList "hello" :: SerialT IO Char)
--   
-- -- True -- -- Space: O(n) worst case where n is the length of the -- infix. -- -- Pre-release -- -- Requires Storable constraint isInfixOf :: (MonadIO m, Eq a, Enum a, Storable a) => SerialT m a -> SerialT m a -> m Bool -- | Returns True if the first stream is a suffix of the second. A -- stream is considered a suffix of itself. -- --
--   >>> Stream.isSuffixOf (Stream.fromList "hello") (Stream.fromList "hello" :: SerialT IO Char)
--   True
--   
-- -- Space: O(n), buffers entire input stream and the suffix. -- -- Pre-release -- -- Suboptimal - Help wanted. isSuffixOf :: (Monad m, Eq a) => SerialT m a -> SerialT m a -> m Bool -- | Returns True if all the elements of the first stream occur, in -- order, in the second stream. The elements do not have to occur -- consecutively. A stream is a subsequence of itself. -- --
--   >>> Stream.isSubsequenceOf (Stream.fromList "hlo") (Stream.fromList "hello" :: SerialT IO Char)
--   True
--   
isSubsequenceOf :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m Bool -- | stripPrefix prefix stream strips prefix from -- stream if it is a prefix of stream. Returns Nothing if -- the stream does not start with the given prefix, stripped stream -- otherwise. Returns Just nil when the prefix is the same as -- the stream. -- -- See also "Streamly.Internal.Data.Stream.IsStream.Nesting.dropPrefix". -- -- Space: O(1) stripPrefix :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m (Maybe (t m a)) -- | Drops the given suffix from a stream. Returns Nothing if the -- stream does not end with the given suffix. Returns Just nil -- when the suffix is the same as the stream. -- -- It may be more efficient to convert the stream to an Array and use -- stripSuffix on that especially if the elements have a Storable or Prim -- instance. -- -- See also "Streamly.Internal.Data.Stream.IsStream.Nesting.dropSuffix". -- -- Space: O(n), buffers the entire input stream as well as the -- suffix -- -- Pre-release stripSuffix :: (Monad m, Eq a) => SerialT m a -> SerialT m a -> m (Maybe (SerialT m a)) -- | Strict left fold with an extraction function. Like the standard strict -- left fold, but applies a user supplied extraction function (the third -- argument) to the folded value at the end. This is designed to work -- with the foldl library. The suffix x is a mnemonic -- for extraction. -- | Deprecated: Please use foldl' followed by fmap instead. foldx :: Monad m => (x -> a -> x) -> x -> (x -> b) -> SerialT m a -> m b -- | Like foldx, but with a monadic step function. -- | Deprecated: Please use foldlM' followed by fmap instead. foldxM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> SerialT m a -> m b -- | Lazy right fold for non-empty streams, using first element as the -- starting value. Returns Nothing if the stream is empty. -- | Deprecated: Use foldrM instead. foldr1 :: Monad m => (a -> a -> a) -> SerialT m a -> m (Maybe a) -- | Run a stream, discarding the results. By default it interprets the -- stream as SerialT, to run other types of streams use the type -- adapting combinators for example runStream . -- fromAsync. -- | Deprecated: Please use "drain" instead runStream :: Monad m => SerialT m a -> m () -- |
--   runN n = runStream . take n
--   
-- -- Run maximum up to n iterations of a stream. -- | Deprecated: Please use "drainN" instead runN :: Monad m => Int -> SerialT m a -> m () -- |
--   runWhile p = runStream . takeWhile p
--   
-- -- Run a stream as long as the predicate holds true. -- | Deprecated: Please use "drainWhile" instead runWhile :: Monad m => (a -> Bool) -> SerialT m a -> m () -- |
--   toHandle h = S.mapM_ $ hPutStrLn h
--   
-- -- Write a stream of Strings to an IO Handle. -- | Deprecated: Please use Streamly.FileSystem.Handle module (see the -- changelog) toHandle :: MonadIO m => Handle -> SerialT m String -> m () -- | Top level IsStream module that can use all other lower level IsStream -- modules. module Streamly.Internal.Data.Stream.IsStream.Top -- | sampleFromthen offset stride samples the element at -- offset index and then every element at strides of -- stride. -- --
--   >>> Stream.toList $ Stream.sampleFromThen 2 3 $ Stream.enumerateFromTo 0 10
--   [2,5,8]
--   
-- -- Pre-release sampleFromThen :: (IsStream t, Monad m, Functor (t m)) => Int -> Int -> t m a -> t m a -- | Like sampleInterval but samples at the beginning of the time -- window. -- --
--   sampleIntervalStart n = Stream.catMaybes . Stream.intervalsOf n Fold.head
--   
-- -- Pre-release sampleIntervalStart :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m a -> t m a -- | Continuously evaluate the input stream and sample the last event in -- time window of n seconds. -- -- This is also known as throttle in some libraries. -- --
--   sampleIntervalEnd n = Stream.catMaybes . Stream.intervalsOf n Fold.last
--   
-- -- Pre-release sampleIntervalEnd :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m a -> t m a -- | Like sampleBurstEnd but samples the event at the beginning of -- the burst instead of at the end of it. -- -- Pre-release sampleBurstStart :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m a -> t m a -- | Sample one event at the end of each burst of events. A burst is a -- group of events close together in time, it ends when an event is -- spaced by more than the specified time interval from the previous -- event. -- -- This is known as debounce in some libraries. -- -- The clock granularity is 10 ms. -- -- Pre-release sampleBurstEnd :: (IsStream t, MonadAsync m, Functor (t m)) => Double -> t m a -> t m a -- | Sort the input stream using a supplied comparison function. -- -- O(n) space -- -- Note: this is not the fastest possible implementation as of now. -- -- Pre-release sortBy :: MonadCatch m => (a -> a -> Ordering) -> SerialT m a -> SerialT m a -- | intersectBy is essentially a filtering operation that retains -- only those elements in the first stream that are present in the second -- stream. -- --
--   >>> Stream.toList $ Stream.intersectBy (==) (Stream.fromList [1,2,2,4]) (Stream.fromList [2,1,1,3])
--   [1,2,2]
--   
-- --
--   >>> Stream.toList $ Stream.intersectBy (==) (Stream.fromList [2,1,1,3]) (Stream.fromList [1,2,2,4])
--   [2,1,1]
--   
-- -- intersectBy is similar to but not the same as innerJoin: -- --
--   >>> Stream.toList $ fmap fst $ Stream.innerJoin (==) (Stream.fromList [1,2,2,4]) (Stream.fromList [2,1,1,3])
--   [1,1,2,2]
--   
-- -- Space: O(n) where n is the number of elements in the second -- stream. -- -- Time: O(m x n) where m is the number of elements in the first -- stream and n is the number of elements in the second stream. -- -- Pre-release intersectBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> t m a -> t m a -> t m a -- | Like intersectBy but works only on sorted streams. -- -- Space: O(1) -- -- Time: O(m+n) -- -- Unimplemented mergeIntersectBy :: (a -> a -> Ordering) -> t m a -> t m a -> t m a -- | Delete first occurrences of those elements from the first stream that -- are present in the second stream. If an element occurs multiple times -- in the second stream as many occurrences of it are deleted from the -- first stream. -- --
--   >>> Stream.toList $ Stream.differenceBy (==) (Stream.fromList [1,2,2]) (Stream.fromList [1,2,3])
--   [2]
--   
-- -- The following laws hold: -- --
--   (s1 serial s2) `differenceBy eq` s1 === s2
--   (s1 wSerial s2) `differenceBy eq` s1 === s2
--   
-- -- Same as the list // operation. -- -- Space: O(m) where m is the number of elements in the first -- stream. -- -- Time: O(m x n) where m is the number of elements in the first -- stream and n is the number of elements in the second stream. -- -- Pre-release differenceBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> t m a -> t m a -> t m a -- | Like differenceBy but works only on sorted streams. -- -- Space: O(1) -- -- Unimplemented mergeDifferenceBy :: (a -> a -> Ordering) -> t m a -> t m a -> t m a -- | This is essentially an append operation that appends all the extra -- occurrences of elements from the second stream that are not already -- present in the first stream. -- --
--   >>> Stream.toList $ Stream.unionBy (==) (Stream.fromList [1,2,2,4]) (Stream.fromList [1,1,2,3])
--   [1,2,2,4,3]
--   
-- -- Equivalent to the following except that s1 is evaluated only -- once: -- --
--   unionBy eq s1 s2 = s1 `serial` (s2 `differenceBy eq` s1)
--   
-- -- Similar to outerJoin but not the same. -- -- Space: O(n) -- -- Time: O(m x n) -- -- Pre-release unionBy :: (IsStream t, MonadAsync m, Semigroup (t m a)) => (a -> a -> Bool) -> t m a -> t m a -> t m a -- | Like unionBy but works only on sorted streams. -- -- Space: O(1) -- -- Unimplemented mergeUnionBy :: (a -> a -> Ordering) -> t m a -> t m a -> t m a -- | This is the same as outerProduct but less efficient. -- -- The second stream is evaluated multiple times. If the second stream is -- consume-once stream then it can be cached in an Array before -- calling this function. Caching may also improve performance if the -- stream is expensive to evaluate. -- -- Time: O(m x n) -- -- Pre-release crossJoin :: Monad (t m) => t m a -> t m b -> t m (a, b) -- | For all elements in t m a, for all elements in t m b -- if a and b are equal by the given equality pedicate -- then return the tuple (a, b). -- -- The second stream is evaluated multiple times. If the stream is a -- consume-once stream then the caller should cache it in an Array -- before calling this function. Caching may also improve performance if -- the stream is expensive to evaluate. -- -- For space efficiency use the smaller stream as the second stream. -- -- Space: O(n) assuming the second stream is cached in memory. -- -- Time: O(m x n) -- -- Pre-release innerJoin :: forall (t :: (Type -> Type) -> Type -> Type) m a b. (IsStream t, Monad (t m)) => (a -> b -> Bool) -> t m a -> t m b -> t m (a, b) -- | Like innerJoin but works only on sorted streams. -- -- Space: O(1) -- -- Time: O(m + n) -- -- Unimplemented mergeInnerJoin :: (a -> b -> Ordering) -> t m a -> t m b -> t m (a, b) -- | Like innerJoin but uses a hashmap for efficiency. -- -- For space efficiency use the smaller stream as the second stream. -- -- Space: O(n) -- -- Time: O(m + n) -- -- Unimplemented hashInnerJoin :: (a -> b -> Bool) -> t m a -> t m b -> t m (a, b) -- | For all elements in t m a, for all elements in t m b -- if a and b are equal then return the tuple (a, -- Just b). If a is not present in t m b then -- return (a, Nothing). -- -- The second stream is evaluated multiple times. If the stream is a -- consume-once stream then the caller should cache it in an Array -- before calling this function. Caching may also improve performance if -- the stream is expensive to evaluate. -- --
--   rightJoin = flip leftJoin
--   
-- -- Space: O(n) assuming the second stream is cached in memory. -- -- Time: O(m x n) -- -- Unimplemented leftJoin :: Monad m => (a -> b -> Bool) -> SerialT m a -> SerialT m b -> SerialT m (a, Maybe b) -- | Like leftJoin but works only on sorted streams. -- -- Space: O(1) -- -- Time: O(m + n) -- -- Unimplemented mergeLeftJoin :: (a -> b -> Ordering) -> t m a -> t m b -> t m (a, Maybe b) -- | Like outerJoin but uses a hashmap for efficiency. -- -- Space: O(n) -- -- Time: O(m + n) -- -- Unimplemented hashLeftJoin :: (a -> b -> Bool) -> t m a -> t m b -> t m (a, Maybe b) -- | For all elements in t m a, for all elements in t m b -- if a and b are equal by the given equality pedicate -- then return the tuple (Just a, Just b). If a is not found in -- t m b then return (a, Nothing), return (Nothing, b) for -- vice-versa. -- -- For space efficiency use the smaller stream as the second stream. -- -- Space: O(n) -- -- Time: O(m x n) -- -- Unimplemented outerJoin :: MonadIO m => (a -> b -> Bool) -> SerialT m a -> SerialT m b -> SerialT m (Maybe a, Maybe b) -- | Like outerJoin but works only on sorted streams. -- -- Space: O(1) -- -- Time: O(m + n) -- -- Unimplemented mergeOuterJoin :: (a -> b -> Ordering) -> t m a -> t m b -> t m (Maybe a, Maybe b) -- | Like outerJoin but uses a hashmap for efficiency. -- -- For space efficiency use the smaller stream as the second stream. -- -- Space: O(n) -- -- Time: O(m + n) -- -- Unimplemented hashOuterJoin :: (a -> b -> Ordering) -> t m a -> t m b -> t m (Maybe a, Maybe b) -- | This is an internal module which is a superset of the corresponding -- released module Streamly.Prelude. It contains some additional -- unreleased or experimental APIs. module Streamly.Internal.Data.Stream.IsStream -- | The type Stream m a represents a monadic stream of values of -- type a constructed using actions in monad m. It uses -- stop, singleton and yield continuations equivalent to the following -- direct style type: -- --
--   data Stream m a = Stop | Singleton a | Yield a (Stream m a)
--   
-- -- To facilitate parallel composition we maintain a local state in an -- SVar that is shared across and is used for synchronization of -- the streams being composed. -- -- The singleton case can be expressed in terms of stop and yield but we -- have it as a separate case to optimize composition operations for -- streams with single element. We build singleton streams in the -- implementation of pure for Applicative and Monad, and in -- lift for MonadTrans. newtype Stream m a MkStream :: (forall r. State Stream m a -> (a -> Stream m a -> m r) -> (a -> m r) -> m r -> m r) -> Stream m a -- | An interleaving serial IO stream of elements of type a. See -- WSerialT documentation for more details. -- -- Since: 0.2.0 (Streamly) type WSerial = WSerialT IO -- | For WSerialT streams: -- --
--   (<>) = wSerial                       -- Semigroup
--   (>>=) = flip . concatMapWith wSerial -- Monad
--   
-- -- Note that <> is associative only if we disregard the -- ordering of elements in the resulting stream. -- -- A single Monad bind behaves like a for loop: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWSerial $ do
--        x <- Stream.fromList [1,2] -- foreach x in stream
--        return x
--   :}
--   [1,2]
--   
-- -- Nested monad binds behave like interleaved nested for loops: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWSerial $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [3,4] -- foreach y in stream
--       return (x, y)
--   :}
--   [(1,3),(2,3),(1,4),(2,4)]
--   
-- -- It is a result of interleaving all the nested iterations corresponding -- to element 1 in the first stream with all the nested -- iterations of element 2: -- --
--   >>> import Streamly.Prelude (wSerial)
--   
--   >>> Stream.toList $ Stream.fromList [(1,3),(1,4)] `Stream.wSerial` Stream.fromList [(2,3),(2,4)]
--   [(1,3),(2,3),(1,4),(2,4)]
--   
-- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- SerialT. -- -- Since: 0.2.0 (Streamly) data WSerialT m a -- | A serial IO stream of elements of type a. See SerialT -- documentation for more details. -- -- Since: 0.2.0 (Streamly) type Serial = SerialT IO -- | For SerialT streams: -- --
--   (<>) = serial                       -- Semigroup
--   (>>=) = flip . concatMapWith serial -- Monad
--   
-- -- A single Monad bind behaves like a for loop: -- --
--   >>> :{
--   Stream.toList $ do
--        x <- Stream.fromList [1,2] -- foreach x in stream
--        return x
--   :}
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops: -- --
--   >>> :{
--   Stream.toList $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [3,4] -- foreach y in stream
--       return (x, y)
--   :}
--   [(1,3),(1,4),(2,3),(2,4)]
--   
-- -- Since: 0.2.0 (Streamly) data SerialT m a -- | A round robin parallely composing IO stream of elements of type -- a. See WAsyncT documentation for more details. -- -- Since: 0.2.0 (Streamly) type WAsync = WAsyncT IO -- | For WAsyncT streams: -- --
--   (<>) = wAsync
--   (>>=) = flip . concatMapWith wAsync
--   
-- -- A single Monad bind behaves like a for loop with -- iterations of the loop executed concurrently a la the wAsync -- combinator, producing results and side effects of iterations out of -- order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWAsync $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, a la the wAsync combinator: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWAsync $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,4,5,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one WAsyncT output stream and all the iterations corresponding -- to 2 constitute another WAsyncT output stream and -- these two output streams are merged using wAsync. -- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- AsyncT. -- -- Since: 0.2.0 (Streamly) data WAsyncT m a -- | A demand driven left biased parallely composing IO stream of elements -- of type a. See AsyncT documentation for more details. -- -- Since: 0.2.0 (Streamly) type Async = AsyncT IO -- | For AsyncT streams: -- --
--   (<>) = async
--   (>>=) = flip . concatMapWith async
--   
-- -- A single Monad bind behaves like a for loop with -- iterations of the loop executed concurrently a la the async -- combinator, producing results and side effects of iterations out of -- order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAsync $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, a la the async combinator: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAsync $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,4,5,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one output stream and all the iterations corresponding to 2 -- constitute another output stream and these two output streams are -- merged using async. -- -- Since: 0.1.0 (Streamly) data AsyncT m a -- | A serial IO stream of elements of type a with concurrent -- lookahead. See AheadT documentation for more details. -- -- Since: 0.3.0 (Streamly) type Ahead = AheadT IO -- | For AheadT streams: -- --
--   (<>) = ahead
--   (>>=) = flip . concatMapWith ahead
--   
-- -- A single Monad bind behaves like a for loop with -- iterations executed concurrently, ahead of time, producing side -- effects of iterations out of order, but results in order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAhead $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [2,1]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, ahead of time: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAhead $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,5,4,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one output stream and all the iterations corresponding to 2 -- constitute another output stream and these two output streams are -- merged using ahead. -- -- Since: 0.3.0 (Streamly) data AheadT m a -- | A parallely composing IO stream of elements of type a. See -- ParallelT documentation for more details. -- -- Since: 0.2.0 (Streamly) type Parallel = ParallelT IO -- | For ParallelT streams: -- --
--   (<>) = parallel
--   (>>=) = flip . concatMapWith parallel
--   
-- -- See AsyncT, ParallelT is similar except that all -- iterations are strictly concurrent while in AsyncT it depends -- on the consumer demand and available threads. See parallel -- for more details. -- -- Since: 0.1.0 (Streamly) -- -- Since: 0.7.0 (maxBuffer applies to ParallelT streams) data ParallelT m a -- | An IO stream whose applicative instance zips streams wAsyncly. -- -- Since: 0.2.0 (Streamly) type ZipAsync = ZipAsyncM IO -- | For ZipAsyncM streams: -- --
--   (<>) = serial
--   (*) = 'Streamly.Prelude.serial.zipAsyncWith' id
--   
-- -- Applicative evaluates the streams being zipped concurrently, the -- following would take half the time that it would take in serial -- zipping: -- --
--   >>> s = Stream.fromFoldableM $ Prelude.map delay [1, 1, 1]
--   
--   >>> Stream.toList $ Stream.fromZipAsync $ (,) <$> s <*> s
--   ...
--   [(1,1),(1,1),(1,1)]
--   
-- -- Since: 0.2.0 (Streamly) data ZipAsyncM m a -- | An IO stream whose applicative instance zips streams serially. -- -- Since: 0.2.0 (Streamly) type ZipSerial = ZipSerialM IO -- | For ZipSerialM streams: -- --
--   (<>) = serial
--   (*) = 'Streamly.Prelude.serial.zipWith' id
--   
-- -- Applicative evaluates the streams being zipped serially: -- --
--   >>> s1 = Stream.fromFoldable [1, 2]
--   
--   >>> s2 = Stream.fromFoldable [3, 4]
--   
--   >>> s3 = Stream.fromFoldable [5, 6]
--   
--   >>> Stream.toList $ Stream.fromZipSerial $ (,,) <$> s1 <*> s2 <*> s3
--   [(1,3,5),(2,4,6)]
--   
-- -- Since: 0.2.0 (Streamly) data ZipSerialM m a -- | Same as IsStream. -- | Deprecated: Please use IsStream instead. type Streaming = IsStream -- | Class of types that can represent a stream of elements of some type -- a in some monad m. -- -- Since: 0.2.0 (Streamly) class (forall m a. MonadAsync m => Semigroup (t m a), forall m a. MonadAsync m => Monoid (t m a), forall m. Monad m => Functor (t m), forall m. MonadAsync m => Applicative (t m)) => IsStream t fromStream :: IsStream t => Stream m a -> t m a -- | Constructs a stream by adding a monadic action at the head of an -- existing stream. For example: -- --
--   > toList $ getLine `consM` getLine `consM` nil
--   hello
--   world
--   ["hello","world"]
--   
-- -- Concurrent (do not use fromParallel to construct infinite -- streams) consM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a -- | Operator equivalent of consM. We can read it as "parallel -- colon" to remember that | comes before :. -- --
--   > toList $ getLine |: getLine |: nil
--   hello
--   world
--   ["hello","world"]
--   
-- --
--   let delay = threadDelay 1000000 >> print 1
--   drain $ fromSerial  $ delay |: delay |: delay |: nil
--   drain $ fromParallel $ delay |: delay |: delay |: nil
--   
-- -- Concurrent (do not use fromParallel to construct infinite -- streams) (|:) :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 `consM` infixr 5 |: fromStreamS :: (IsStream t, Monad m) => Stream m a -> t m a toStreamS :: (IsStream t, Monad m) => t m a -> Stream m a toStreamD :: (IsStream t, Monad m) => t m a -> Stream m a -- |
--   fromList = foldr cons nil
--   
-- -- Construct a stream from a list of pure values. This is more efficient -- than fromFoldable for serial streams. fromList :: (Monad m, IsStream t) => [a] -> t m a foldrMx :: (IsStream t, Monad m) => (a -> m x -> m x) -> m x -> (m x -> m b) -> t m a -> m b -- | Like foldlx', but with a monadic step function. foldlMx' :: (IsStream t, Monad m) => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> m b -- | Strict left fold with an extraction function. Like the standard strict -- left fold, but applies a user supplied extraction function (the third -- argument) to the folded value at the end. This is designed to work -- with the foldl library. The suffix x is a mnemonic -- for extraction. foldlx' :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> m b -- | Adapt any specific stream type to any other specific stream type. -- -- Since: 0.1.0 (Streamly) adapt :: (IsStream t1, IsStream t2) => t1 m a -> t2 m a fromStreamD :: (IsStream t, Monad m) => Stream m a -> t m a -- | Adapt a polymorphic consM operation to a StreamK cons operation toConsK :: IsStream t => (m a -> t m a -> t m a) -> m a -> Stream m a -> Stream m a -- | Build a stream from an SVar, a stop continuation, a singleton -- stream continuation and a yield continuation. mkStream :: IsStream t => (forall r. State Stream m a -> (a -> t m a -> m r) -> (a -> m r) -> m r -> m r) -> t m a -- | Fold a stream by providing an SVar, a stop continuation, a singleton -- continuation and a yield continuation. The stream would share the -- current SVar passed via the State. foldStreamShared :: IsStream t => State Stream m a -> (a -> t m a -> m r) -> (a -> m r) -> m r -> t m a -> m r -- | Fold a stream by providing a State, stop continuation, a singleton -- continuation and a yield continuation. The stream will not use the -- SVar passed via State. foldStream :: IsStream t => State Stream m a -> (a -> t m a -> m r) -> (a -> m r) -> m r -> t m a -> m r -- | Fix the type of a polymorphic stream as SerialT. -- -- Since: 0.1.0 (Streamly) fromSerial :: IsStream t => SerialT m a -> t m a -- | Fix the type of a polymorphic stream as WSerialT. -- -- Since: 0.2.0 (Streamly) fromWSerial :: IsStream t => WSerialT m a -> t m a -- | Same as fromWSerial. -- | Deprecated: Please use fromWSerial instead. interleaving :: IsStream t => WSerialT m a -> t m a -- | Fix the type of a polymorphic stream as AsyncT. -- -- Since: 0.1.0 (Streamly) fromAsync :: IsStream t => AsyncT m a -> t m a -- | Fix the type of a polymorphic stream as WAsyncT. -- -- Since: 0.2.0 (Streamly) fromWAsync :: IsStream t => WAsyncT m a -> t m a -- | Fix the type of a polymorphic stream as AheadT. -- -- Since: 0.3.0 (Streamly) fromAhead :: IsStream t => AheadT m a -> t m a -- | Fix the type of a polymorphic stream as ParallelT. -- -- Since: 0.1.0 (Streamly) fromParallel :: IsStream t => ParallelT m a -> t m a -- | Fix the type of a polymorphic stream as ZipSerialM. -- -- Since: 0.2.0 (Streamly) fromZipSerial :: IsStream t => ZipSerialM m a -> t m a -- | Same as fromZipSerial. -- | Deprecated: Please use fromZipSerial instead. zipping :: IsStream t => ZipSerialM m a -> t m a -- | Fix the type of a polymorphic stream as ZipAsyncM. -- -- Since: 0.2.0 (Streamly) fromZipAsync :: IsStream t => ZipAsyncM m a -> t m a -- | Same as fromZipAsync. -- | Deprecated: Please use fromZipAsync instead. zippingAsync :: IsStream t => ZipAsyncM m a -> t m a -- | Construct a stream by adding a pure value at the head of an existing -- stream. For serial streams this is the same as (return a) `consM` -- r but more efficient. For concurrent streams this is not -- concurrent whereas consM is concurrent. For example: -- --
--   > toList $ 1 `cons` 2 `cons` 3 `cons` nil
--   [1,2,3]
--   
cons :: IsStream t => a -> t m a -> t m a infixr 5 `cons` -- | Operator equivalent of cons. -- --
--   > toList $ 1 .: 2 .: 3 .: nil
--   [1,2,3]
--   
(.:) :: IsStream t => a -> t m a -> t m a infixr 5 .: nil :: IsStream t => t m a nilM :: (IsStream t, Monad m) => m b -> t m a bindWith :: IsStream t => (t m b -> t m b -> t m b) -> t m a -> (a -> t m b) -> t m b -- | concatMapWith mixer generator stream is a two dimensional -- looping combinator. The generator function is used to -- generate streams from the elements in the input stream and -- the mixer function is used to merge those streams. -- -- Note we can merge streams concurrently by using a concurrent merge -- function. -- -- Since: 0.7.0 -- -- Since: 0.8.0 (signature change) concatMapWith :: IsStream t => (t m b -> t m b -> t m b) -> (a -> t m b) -> t m a -> t m b -- | A variant of foldMap that allows you to map a monadic streaming -- action on a Foldable container and then fold it using the -- specified stream merge operation. -- --
--   concatMapFoldableWith async return [1..3]
--   
-- -- Equivalent to: -- --
--   concatMapFoldableWith f g = Prelude.foldr (f . g) S.nil
--   concatMapFoldableWith f g xs = S.concatMapWith f g (S.fromFoldable xs)
--   
-- -- Since: 0.8.0 (Renamed foldMapWith to concatMapFoldableWith) -- -- Since: 0.1.0 (Streamly) concatMapFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b -- | Like concatMapFoldableWith but with the last two arguments -- reversed i.e. the monadic streaming function is the last argument. -- -- Equivalent to: -- --
--   concatForFoldableWith f xs g = Prelude.foldr (f . g) S.nil xs
--   concatForFoldableWith f = flip (S.concatMapFoldableWith f)
--   
-- -- Since: 0.8.0 (Renamed forEachWith to concatForFoldableWith) -- -- Since: 0.1.0 (Streamly) concatForFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b -- | A variant of fold that allows you to fold a Foldable -- container of streams using the specified stream sum operation. -- --
--   concatFoldableWith async $ map return [1..3]
--   
-- -- Equivalent to: -- --
--   concatFoldableWith f = Prelude.foldr f S.nil
--   concatFoldableWith f = S.concatMapFoldableWith f id
--   
-- -- Since: 0.8.0 (Renamed foldWith to concatFoldableWith) -- -- Since: 0.1.0 (Streamly) concatFoldableWith :: (IsStream t, Foldable f) => (t m a -> t m a -> t m a) -> f (t m a) -> t m a module Streamly.Internal.FileSystem.Dir read :: MonadIO m => Unfold m String String -- | Read files only. -- -- Internal readFiles :: MonadIO m => Unfold m String String -- | Read directories only. Filter out "." and ".." entries. -- -- Internal readDirs :: MonadIO m => Unfold m String String -- | Read directories as Left and files as Right. Filter out "." and ".." -- entries. -- -- Internal readEither :: MonadIO m => Unfold m String (Either String String) -- | Raw read of a directory. -- -- Pre-release toStream :: (IsStream t, MonadIO m) => String -> t m String -- | Read directories as Left and files as Right. Filter out "." and ".." -- entries. -- -- Pre-release toEither :: (IsStream t, MonadIO m) => String -> t m (Either String String) -- | Read files only. -- -- Internal toFiles :: (IsStream t, MonadIO m) => String -> t m String -- | Read directories only. -- -- Internal toDirs :: (IsStream t, MonadIO m) => String -> t m String -- | Unboxed pinned mutable array type for Storable types with an -- option to use foreign (non-GHC) memory allocators. Fulfils the -- following goals: -- -- -- -- Stream and Fold APIs allow easy, efficient and convenient operations -- on arrays. module Streamly.Internal.Data.Array.Foreign.Mut -- | Split the array into a stream of slices using a predicate. The element -- matching the predicate is dropped. -- -- Pre-release splitOn :: (MonadIO m, Storable a) => (a -> Bool) -> Array a -> SerialT m (Array a) -- | Generate a stream of array slice descriptors ((index, len)) of -- specified length from an array, starting from the supplied array -- index. The last slice may be shorter than the requested length -- depending on the array length. -- -- Pre-release genSlicesFromLen :: forall m a. (Monad m, Storable a) => Int -> Int -> Unfold m (Array a) (Int, Int) -- | Generate a stream of slices of specified length from an array, -- starting from the supplied array index. The last slice may be shorter -- than the requested length depending on the array length. -- -- Pre-release getSlicesFromLen :: forall m a. (Monad m, Storable a) => Int -> Int -> Unfold m (Array a) (Array a) -- | To summarize: -- -- -- -- Foldable instance is not provided because the implementation -- would be much less efficient compared to folding via streams. -- Semigroup and Monoid instances should be used with care; -- concatenating arrays using binary operations can be highly -- inefficient. Instead, use toArray to concatenate N arrays at -- once. -- -- Each array is one pointer visible to the GC. Too many small arrays -- (e.g. single byte) are only as good as holding those elements in a -- Haskell list. However, small arrays can be compacted into large ones -- to reduce the overhead. To hold 32GB memory in 32k sized buffers we -- need 1 million arrays if we use one array for each chunk. This is -- still significant to add pressure to GC. module Streamly.Internal.Data.Array.Foreign data Array a -- | Create an Array of the given number of elements of type -- a from a read only pointer Ptr a. The pointer is not -- freed when the array is garbage collected. This API is unsafe for the -- following reasons: -- --
    --
  1. The pointer must point to static pinned memory or foreign memory -- that does not require freeing..
  2. --
  3. The pointer must be legally accessible upto the given length.
  4. --
  5. To guarantee that the array is immutable, the contents of the -- address must be guaranteed to not change.
  6. --
-- -- Unsafe -- -- Pre-release fromPtr :: Int -> Ptr a -> Array a -- | Create an Array Word8 of the given length from a static, read -- only machine address Addr#. See fromPtr for safety -- caveats. -- -- A common use case for this API is to create an array from a static -- unboxed string literal. GHC string literals are of type Addr#, -- and must contain characters that can be encoded in a byte i.e. -- characters or literal bytes in the range from 0-255. -- --
--   >>> import Data.Word (Word8)
--   
--   >>> Array.fromAddr# 5 "hello world!"# :: Array Word8
--   [104,101,108,108,111]
--   
-- --
--   >>> Array.fromAddr# 3 "\255\NUL\255"# :: Array Word8
--   [255,0,255]
--   
-- -- See also: fromString# -- -- Unsafe -- -- Time complexity: O(1) -- -- Pre-release fromAddr# :: Int -> Addr# -> Array a -- | Generate a byte array from an Addr# that contains a sequence of -- NUL (0) terminated bytes. The array would not include the NUL -- byte. The address must be in static read-only memory and must be -- legally accessible up to and including the first NUL byte. -- -- An unboxed string literal (e.g. "hello"#) is a common example -- of an Addr# in static read only memory. It represents the UTF8 -- encoded sequence of bytes terminated by a NUL byte (a CString) -- corresponding to the given unicode string. -- --
--   >>> Array.fromCString# "hello world!"#
--   [104,101,108,108,111,32,119,111,114,108,100,33]
--   
-- --
--   >>> Array.fromCString# "\255\NUL\255"#
--   [255]
--   
-- -- See also: fromAddr# -- -- Unsafe -- -- Time complexity: O(n) (computes the length of the string) -- -- Pre-release fromCString# :: Addr# -> Array Word8 -- | Create an Array from the first N elements of a list. The array -- is allocated to size N, if the list terminates before N elements then -- the array may hold less than N elements. -- -- Since 0.7.0 (Streamly.Memory.Array) fromListN :: Storable a => Int -> [a] -> Array a -- | Create an Array from a list. The list must be of finite size. -- -- Since 0.7.0 (Streamly.Memory.Array) fromList :: Storable a => [a] -> Array a -- | Create an Array from the first N elements of a stream. The -- array is allocated to size N, if the stream terminates before N -- elements then the array may hold less than N elements. -- -- Pre-release fromStreamN :: (MonadIO m, Storable a) => Int -> SerialT m a -> m (Array a) -- | Create an Array from a stream. This is useful when we want to -- create a single array from a stream of unknown size. writeN -- is at least twice as efficient when the size is already known. -- -- Note that if the input stream is too large memory allocation for the -- array may fail. When the stream size is not known, arraysOf -- followed by processing of indvidual arrays in the resulting stream -- should be preferred. -- -- Pre-release fromStream :: (MonadIO m, Storable a) => SerialT m a -> m (Array a) -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- -- Since 0.7.0 (Streamly.Memory.Array) writeN :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) -- | writeNAligned alignment n folds a maximum of n -- elements from the input stream to an Array aligned to the given -- size. -- -- Pre-release writeNAligned :: forall m a. (MonadIO m, Storable a) => Int -> Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Caution! Do not use this on infinite streams. -- -- Since 0.7.0 (Streamly.Memory.Array) write :: forall m a. (MonadIO m, Storable a) => Fold m a (Array a) -- | writeLastN n folds a maximum of n elements from the -- end of the input stream to an Array. writeLastN :: (Storable a, MonadIO m) => Int -> Fold m a (Array a) -- | Convert an Array into a list. -- -- Since 0.7.0 (Streamly.Memory.Array) toList :: Storable a => Array a -> [a] -- | Convert an Array into a stream. -- -- Pre-release toStream :: (Monad m, Storable a) => Array a -> SerialT m a -- | Convert an Array into a stream in reverse order. -- -- Pre-release toStreamRev :: (Monad m, Storable a) => Array a -> SerialT m a -- | Unfold an array into a stream. -- -- Since 0.7.0 (Streamly.Memory.Array) read :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a -- | Unfold an array into a stream, does not check the end of the array, -- the user is responsible for terminating the stream within the array -- bounds. For high performance application where the end condition can -- be determined by a terminating fold. -- -- Written in the hope that it may be faster than "read", however, in the -- case for which this was written, "read" proves to be faster even -- though the core generated with unsafeRead looks simpler. -- -- Pre-release unsafeRead :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a -- | Unfold an array into a stream in reverse order. readRev :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a producer :: forall m a. (Monad m, Storable a) => Producer m (Array a) a -- | O(1) Lookup the element at the given index. Index starts from -- 0. getIndex :: forall a. Storable a => Array a -> Int -> Maybe a -- | Return element at the specified index without checking the bounds. unsafeIndex :: forall a. Storable a => Array a -> Int -> a -- | Like getIndex but indexes the array in reverse from the end. -- -- Pre-release getIndexRev :: forall a. Storable a => Array a -> Int -> Maybe a -- |
--   >>> import qualified Streamly.Internal.Data.Array.Foreign as Array
--   
--   >>> last arr = Array.getIndexRev arr 0
--   
-- -- Pre-release last :: Storable a => Array a -> Maybe a -- | Given a stream of array indices, read the elements on those indices -- from the supplied Array. An exception is thrown if an index is out of -- bounds. -- -- This is the most general operation. We can implement other operations -- in terms of this: -- --
--   read =
--        let u = lmap (arr -> (0, length arr - 1)) Unfold.enumerateFromTo
--         in Unfold.lmap f (getIndices arr)
--   
--   readRev =
--        let i = length arr - 1
--         in Unfold.lmap f (getIndicesFromThenTo i (i - 1) 0)
--   
-- -- Unimplemented getIndices :: Unfold m (Array a) Int -> Unfold m (Array a) a -- | Unfolds (from, then, to, array) generating a finite stream -- whose first element is the array value from the index from -- and the successive elements are from the indices in increments of -- then up to to. Index enumeration can occur downwards -- or upwards depending on whether then comes before or after -- from. -- --
--   getIndicesFromThenTo =
--       let f (from, next, to, arr) =
--               (Stream.enumerateFromThenTo from next to, arr)
--        in Unfold.lmap f getIndices
--   
-- -- Unimplemented getIndicesFromThenTo :: Unfold m (Int, Int, Int, Array a) a -- | O(1) Get the length of the array i.e. the number of elements in -- the array. -- -- Since 0.7.0 (Streamly.Memory.Array) length :: forall a. Storable a => Array a -> Int -- |
--   >>> import qualified Streamly.Internal.Data.Array.Foreign.Type as Array
--   
--   >>> null arr = Array.byteLength arr == 0
--   
-- -- Pre-release null :: Array a -> Bool -- | Given a sorted array, perform a binary search to find the given -- element. Returns the index of the element if found. -- -- Unimplemented binarySearch :: a -> Array a -> Maybe Int -- | Perform a linear search to find all the indices where a given element -- is present in an array. -- -- Unimplemented findIndicesOf :: (a -> Bool) -> Unfold Identity (Array a) Int -- | Cast an array having elements of type a into an array having -- elements of type b. The length of the array should be a -- multiple of the size of the target element otherwise Nothing is -- returned. cast :: forall a b. Storable b => Array a -> Maybe (Array b) -- | Cast an Array a into an Array Word8. asBytes :: Array a -> Array Word8 -- | Cast an array having elements of type a into an array having -- elements of type b. The array size must be a multiple of the -- size of type b otherwise accessing the last element of the -- array may result into a crash or a random value. -- -- Pre-release unsafeCast :: Array a -> Array b -- | Use an Array a as Ptr b. -- -- Unsafe -- -- Pre-release unsafeAsPtr :: Array a -> (Ptr b -> IO c) -> IO c -- | Convert an array of any type into a null terminated CString Ptr. -- -- Unsafe -- -- O(n) Time: (creates a copy of the array) -- -- Pre-release unsafeAsCString :: Array a -> (CString -> IO b) -> IO b -- | Makes an immutable array using the underlying memory of the mutable -- array. -- -- Please make sure that there are no other references to the mutable -- array lying around, so that it is never used after freezing it using -- unsafeFreeze. If the underlying array is mutated, the immutable -- promise is lost. -- -- Pre-release unsafeFreeze :: Array a -> Array a -- | Makes a mutable array using the underlying memory of the immutable -- array. -- -- Please make sure that there are no other references to the immutable -- array lying around, so that it is never used after thawing it using -- unsafeThaw. If the resulting array is mutated, any references -- to the older immutable array are mutated as well. -- -- Pre-release unsafeThaw :: Array a -> Array a -- | O(1) Slice an array in constant time. -- -- Caution: The bounds of the slice are not checked. -- -- Unsafe -- -- Pre-release getSliceUnsafe :: forall a. Storable a => Int -> Int -> Array a -> Array a genSlicesFromLen :: forall m a. (Monad m, Storable a) => Int -> Int -> Unfold m (Array a) (Int, Int) -- | Generate a stream of slices of specified length from an array, -- starting from the supplied array index. The last slice may be shorter -- than the requested length. -- -- Pre-release/ getSlicesFromLen :: forall m a. (Monad m, Storable a) => Int -> Int -> Unfold m (Array a) (Array a) -- | Split the array into a stream of slices using a predicate. The element -- matching the predicate is dropped. -- -- Pre-release splitOn :: (Monad m, Storable a) => (a -> Bool) -> Array a -> SerialT m (Array a) -- | Transform an array into another array using a stream transformation -- operation. -- -- Pre-release streamTransform :: forall m a b. (MonadIO m, Storable a, Storable b) => (SerialT m a -> SerialT m b) -> Array a -> m (Array b) -- | Fold an array using a stream fold operation. -- -- Pre-release streamFold :: (MonadIO m, Storable a) => (SerialT m a -> m b) -> Array a -> m b -- | Fold an array using a Fold. -- -- Pre-release fold :: forall m a b. (MonadIO m, Storable a) => Fold m a b -> Array a -> m b -- | Parsers for binary encoded basic Haskell data types. module Streamly.Internal.Data.Binary.Decode -- | A value of type () is encoded as 0 in binary -- encoding. -- --
--   0 ==> ()
--   
-- -- Pre-release unit :: MonadCatch m => Parser m Word8 () -- | A value of type Bool is encoded as follows in binary encoding. -- --
--   0 ==> False
--   1 ==> True
--   
-- -- Pre-release bool :: MonadCatch m => Parser m Word8 Bool -- | A value of type Ordering is encoded as follows in binary -- encoding. -- --
--   0 ==> LT
--   1 ==> EQ
--   2 ==> GT
--   
-- -- Pre-release ordering :: MonadCatch m => Parser m Word8 Ordering -- | Accept the input byte only if it is equal to the specified value. -- -- Pre-release eqWord8 :: MonadCatch m => Word8 -> Parser m Word8 Word8 -- | Accept any byte. -- -- Pre-release word8 :: MonadCatch m => Parser m Word8 Word8 -- | Parse two bytes as a Word16, the first byte is the MSB of the -- Word16 and second byte is the LSB (big endian representation). -- -- Pre-release word16be :: MonadCatch m => Parser m Word8 Word16 -- | Parse two bytes as a Word16, the first byte is the LSB of the -- Word16 and second byte is the MSB (little endian representation). -- -- Pre-release word16le :: MonadCatch m => Parser m Word8 Word16 -- | Parse four bytes as a Word32, the first byte is the MSB of the -- Word32 and last byte is the LSB (big endian representation). -- -- Pre-release word32be :: MonadCatch m => Parser m Word8 Word32 -- | Parse four bytes as a Word32, the first byte is the MSB of the -- Word32 and last byte is the LSB (big endian representation). -- -- Pre-release word32le :: MonadCatch m => Parser m Word8 Word32 -- | Parse eight bytes as a Word64, the first byte is the MSB of the -- Word64 and last byte is the LSB (big endian representation). -- -- Pre-release word64be :: MonadCatch m => Parser m Word8 Word64 -- | Parse eight bytes as a Word64, the first byte is the MSB of the -- Word64 and last byte is the LSB (big endian representation). -- -- Pre-release word64le :: MonadCatch m => Parser m Word8 Word64 -- | Parse eight bytes as a Word64 in the host byte order. -- -- Pre-release word64host :: (MonadIO m, MonadCatch m) => Parser m Word8 Word64 -- | Fold a stream of foreign arrays. Fold m a b in this module -- works on a stream of "Array a" and produces an output of type -- b. -- -- Though Fold m a b in this module works on a stream of -- Array a it is different from Data.Fold m (Array a) -- b. While the latter works on arrays as a whole treating them as -- atomic elements, the folds in this module can work on the stream of -- arrays as if it is an element stream with all the arrays coalesced -- together. This module allows adapting the element stream folds in -- Data.Fold to correctly work on an array stream as if it is an element -- stream. For example: -- --
--   >>> import qualified Streamly.Data.Fold as Fold
--   
--   >>> import qualified Streamly.Internal.Data.Array.Stream.Foreign as ArrayStream
--   
--   >>> import qualified Streamly.Internal.Data.Array.Stream.Fold.Foreign as ArrayFold
--   
--   >>> import qualified Streamly.Internal.Data.Stream.IsStream as Stream (arraysOf)
--   
--   >>> import qualified Streamly.Prelude as Stream
--   
-- --
--   >>> ArrayStream.foldArr (ArrayFold.fromFold (Fold.take 7 Fold.toList)) $ Stream.arraysOf 5 $ Stream.fromList "hello world"
--   "hello w"
--   
module Streamly.Internal.Data.Array.Stream.Fold.Foreign -- | Array stream fold. -- -- An array stream fold is basically an array stream Parser that -- does not fail. In case of array stream folds the count in -- Partial, Continue and Done is a count of elements -- that includes the leftover element count in the array that is -- currently being processed by the parser. If none of the elements is -- consumed by the parser the count is at least the whole array length. -- If the whole array is consumed by the parser then the count will be 0. -- -- Pre-release newtype Fold m a b Fold :: Parser m (Array a) b -> Fold m a b -- | Convert an element Fold into an array stream fold. -- -- Pre-release fromFold :: forall m a b. (MonadIO m, Storable a) => Fold m a b -> Fold m a b -- | Convert an element Parser into an array stream fold. If the -- parser fails the fold would throw an exception. -- -- Pre-release fromParser :: forall m a b. (MonadIO m, Storable a) => Parser m a b -> Fold m a b -- | Adapt an array stream fold. -- -- Pre-release fromArrayFold :: forall m a b. MonadIO m => Fold m (Array a) b -> Fold m a b -- | Map a monadic function on the output of a fold. -- -- Pre-release rmapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c -- | A fold that always yields a pure value without consuming any input. -- -- Pre-release fromPure :: Monad m => b -> Fold m a b -- | A fold that always yields the result of an effectful action without -- consuming any input. -- -- Pre-release fromEffect :: Monad m => m b -> Fold m a b -- | Applies two folds sequentially on the input stream and combines their -- results using the supplied function. -- -- Pre-release serialWith :: MonadThrow m => (a -> b -> c) -> Fold m x a -> Fold m x b -> Fold m x c -- | Applies a fold on the input stream, generates the next fold from the -- output of the previously applied fold and then applies that fold. -- -- Pre-release concatMap :: MonadThrow m => (b -> Fold m a c) -> Fold m a b -> Fold m a c take :: forall m a b. (Monad m, Storable a) => Int -> Fold m a b -> Fold m a b instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Array.Stream.Fold.Foreign.Fold m a) instance Control.Monad.Catch.MonadThrow m => GHC.Base.Applicative (Streamly.Internal.Data.Array.Stream.Fold.Foreign.Fold m a) instance Control.Monad.Catch.MonadThrow m => GHC.Base.Monad (Streamly.Internal.Data.Array.Stream.Fold.Foreign.Fold m a) -- | Combinators to efficiently manipulate streams of immutable arrays. module Streamly.Internal.Data.Array.Stream.Foreign -- | arraysOf n stream groups the elements in the input stream -- into arrays of n elements each. -- --
--   arraysOf n = Stream.chunksOf n (Array.writeN n)
--   
-- -- Pre-release arraysOf :: (IsStream t, MonadIO m, Storable a) => Int -> t m a -> t m (Array a) -- | Convert a stream of arrays into a stream of their elements. -- -- Same as the following but more efficient: -- --
--   concat = Stream.unfoldMany Array.read
--   
concat :: (IsStream t, MonadIO m, Storable a) => t m (Array a) -> t m a -- | Convert a stream of arrays into a stream of their elements reversing -- the contents of each array before flattening. -- --
--   concatRev = Stream.unfoldMany Array.readRev
--   
concatRev :: (IsStream t, MonadIO m, Storable a) => t m (Array a) -> t m a -- | Flatten a stream of arrays after inserting the given element between -- arrays. -- -- Pre-release interpose :: (MonadIO m, IsStream t, Storable a) => a -> t m (Array a) -> t m a -- | Flatten a stream of arrays appending the given element after each -- array. interposeSuffix :: (MonadIO m, IsStream t, Storable a) => a -> t m (Array a) -> t m a intercalateSuffix :: (MonadIO m, IsStream t, Storable a) => Array a -> t m (Array a) -> t m a unlines :: forall m a. (MonadIO m, Storable a) => a -> Stream m (Array a) -> Stream m a -- | Fold an array stream using the supplied Fold. Returns the fold -- result and the unconsumed stream. -- -- Internal fold :: (MonadIO m, Storable a) => Fold m a b -> SerialT m (Array a) -> m (b, SerialT m (Array a)) -- | Parse an array stream using the supplied Parser. Returns the -- parse result and the unconsumed stream. Throws ParseError if -- the parse fails. -- -- Internal parse :: (MonadIO m, MonadThrow m, Storable a) => Parser m a b -> SerialT m (Array a) -> m (b, SerialT m (Array a)) parseD :: forall m a b. (MonadIO m, MonadThrow m, Storable a) => Parser m a b -> Stream m (Array a) -> m (b, Stream m (Array a)) -- | Fold an array stream using the supplied array stream Fold. -- -- Pre-release foldArr :: (MonadIO m, MonadThrow m, Storable a) => Fold m a b -> SerialT m (Array a) -> m b -- | Like fold but also returns the remaining stream. -- -- Pre-release foldArr_ :: (MonadIO m, MonadThrow m, Storable a) => Fold m a b -> SerialT m (Array a) -> m (b, SerialT m (Array a)) parseArrD :: forall m a b. (MonadIO m, MonadThrow m, Storable a) => Parser m (Array a) b -> Stream m (Array a) -> m (b, Stream m (Array a)) -- | Apply an array stream Fold repeatedly on an array stream and -- emit the fold outputs in the output stream. -- -- See "Streamly.Prelude.foldMany" for more details. -- -- Pre-release foldArrMany :: (IsStream t, MonadThrow m, Storable a) => Fold m a b -> t m (Array a) -> t m b -- | Given a stream of arrays, splice them all together to generate a -- single array. The stream must be finite. toArray :: (MonadIO m, Storable a) => SerialT m (Array a) -> m (Array a) lpackArraysChunksOf :: (MonadIO m, Storable a) => Int -> Fold m (Array a) () -> Fold m (Array a) () -- | Coalesce adjacent arrays in incoming stream to form bigger arrays of a -- maximum specified size in bytes. compact :: (MonadIO m, Storable a) => Int -> SerialT m (Array a) -> SerialT m (Array a) -- | Split a stream of arrays on a given separator byte, dropping the -- separator and coalescing all the arrays between two separators into a -- single array. splitOn :: (IsStream t, MonadIO m) => Word8 -> t m (Array Word8) -> t m (Array Word8) splitOnSuffix :: (IsStream t, MonadIO m) => Word8 -> t m (Array Word8) -> t m (Array Word8) module Streamly.Internal.Network.Socket -- | Specify the socket protocol details. data SockSpec SockSpec :: !Family -> !SocketType -> !ProtocolNumber -> ![(SocketOption, Int)] -> SockSpec [sockFamily] :: SockSpec -> !Family [sockType] :: SockSpec -> !SocketType [sockProto] :: SockSpec -> !ProtocolNumber [sockOpts] :: SockSpec -> ![(SocketOption, Int)] -- | forSocketM action socket runs the monadic computation -- action passing the socket handle to it. The handle will be -- closed on exit from forSocketM, whether by normal termination -- or by raising an exception. If closing the handle raises an exception, -- then this exception will be raised by forSocketM rather than -- any exception raised by action. forSocketM :: (MonadMask m, MonadIO m) => (Socket -> m ()) -> Socket -> m () -- | Like forSocketM but runs a streaming computation instead of a -- monadic computation. -- -- Inhibits stream fusion -- -- Internal withSocket :: (IsStream t, MonadAsync m, MonadCatch m) => Socket -> (Socket -> t m a) -> t m a -- | Unfold a three tuple (listenQLen, spec, addr) into a stream -- of connected protocol sockets corresponding to incoming connections. -- listenQLen is the maximum number of pending connections in -- the backlog. spec is the socket protocol and options -- specification and addr is the protocol address where the -- server listens for incoming connections. accept :: MonadIO m => Unfold m (Int, SockSpec, SockAddr) Socket -- | Start a TCP stream server that listens for connections on the supplied -- server address specification (address family, local interface IP -- address and port). The server generates a stream of connected sockets. -- The first argument is the maximum number of pending connections in the -- backlog. -- -- Pre-release connections :: MonadAsync m => Int -> SockSpec -> SockAddr -> SerialT m Socket -- | Connect to a remote host using the given socket specification and -- remote address. Returns a connected socket or throws an exception. -- -- Pre-release connect :: SockSpec -> SockAddr -> IO Socket -- | Connect to a remote host using the given socket specification, a local -- address to bind to and a remote address to connect to. Returns a -- connected socket or throws an exception. -- -- Pre-release connectFrom :: SockSpec -> SockAddr -> SockAddr -> IO Socket -- | Unfolds a Socket into a byte stream. IO requests to the socket -- are performed in sizes of defaultChunkSize. read :: MonadIO m => Unfold m Socket Word8 -- | Unfolds the tuple (bufsize, socket) into a byte stream, read -- requests to the socket are performed using buffers of -- bufsize. readWithBufferOf :: MonadIO m => Unfold m (Int, Socket) Word8 -- | Read a byte array from a file handle up to a maximum of the requested -- size. If no data is available on the handle it blocks until some data -- becomes available. If data is available then it immediately returns -- that data without blocking. readChunk :: Int -> Socket -> IO (Array Word8) -- | Unfolds a socket into a stream of Word8 arrays. Requests to the -- socket are performed using a buffer of size defaultChunkSize. -- The size of arrays in the resulting stream are therefore less than or -- equal to defaultChunkSize. readChunks :: MonadIO m => Unfold m Socket (Array Word8) -- | Unfold the tuple (bufsize, socket) into a stream of -- Word8 arrays. Read requests to the socket are performed using a -- buffer of size bufsize. The size of an array in the resulting -- stream is always less than or equal to bufsize. readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Socket) (Array Word8) -- | toChunksWithBufferOf size h reads a stream of arrays from -- file handle h. The maximum size of a single array is limited -- to size. fromHandleArraysUpto ignores the prevailing -- TextEncoding and NewlineMode on the Handle. toChunksWithBufferOf :: (IsStream t, MonadIO m) => Int -> Socket -> t m (Array Word8) -- | toChunks h reads a stream of arrays from socket handle -- h. The maximum size of a single array is limited to -- defaultChunkSize. toChunks :: (IsStream t, MonadIO m) => Socket -> t m (Array Word8) -- | Generate a stream of elements of the given type from a socket. The -- stream ends when EOF is encountered. toBytes :: (IsStream t, MonadIO m) => Socket -> t m Word8 -- | Write a byte stream to a socket. Accumulates the input in chunks of up -- to defaultChunkSize bytes before writing. -- --
--   write = writeWithBufferOf defaultChunkSize
--   
write :: MonadIO m => Socket -> Fold m Word8 () -- | Write a byte stream to a socket. Accumulates the input in chunks of -- specified number of bytes before writing. writeWithBufferOf :: MonadIO m => Int -> Socket -> Fold m Word8 () -- | Write a stream of Maybe values. Keep buffering the Just -- values in an array. Write the array to the Handle as soon as -- a Nothing is encountered or the buffer size exceeds the -- specified limit. -- -- Pre-release writeMaybesWithBufferOf :: MonadIO m => Int -> Socket -> Fold m (Maybe Word8) () -- | Write a stream of arrays to a handle. putChunks :: (MonadIO m, Storable a) => Socket -> SerialT m (Array a) -> m () -- | Like write but provides control over the write buffer. Output -- will be written to the IO device as soon as we collect the specified -- number of input elements. putBytesWithBufferOf :: MonadIO m => Int -> Socket -> SerialT m Word8 -> m () -- | Write a byte stream to a file handle. Combines the bytes in chunks of -- size up to defaultChunkSize before writing. Note that the write -- behavior depends on the IOMode and the current seek position -- of the handle. putBytes :: MonadIO m => Socket -> SerialT m Word8 -> m () -- | Write an Array to a file handle. writeChunk :: Storable a => Socket -> Array a -> IO () -- | Write a stream of arrays to a socket. Each array in the stream is -- written to the socket as a separate IO request. writeChunks :: (MonadIO m, Storable a) => Socket -> Fold m (Array a) () -- | writeChunksWithBufferOf bufsize socket writes a stream of -- arrays to socket after coalescing the adjacent arrays in -- chunks of bufsize. Multiple arrays are coalesed as long as -- the total size remains below the specified size. It never splits an -- array, if a single array is bigger than the specified size it emitted -- as it is. writeChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Socket -> Fold m (Array a) () -- | Combinators to build Inet/TCP clients and servers. module Streamly.Internal.Network.Inet.TCP -- | Unfold a tuple (ipAddr, port) into a stream of connected TCP -- sockets. ipAddr is the local IP address and port is -- the local port on which connections are accepted. acceptOnAddr :: MonadIO m => Unfold m ((Word8, Word8, Word8, Word8), PortNumber) Socket acceptOnAddrWith :: MonadIO m => [(SocketOption, Int)] -> Unfold m ((Word8, Word8, Word8, Word8), PortNumber) Socket -- | Like acceptOnAddr but binds on the IPv4 address -- 0.0.0.0 i.e. on all IPv4 addresses/interfaces of the machine -- and listens for TCP connections on the specified port. -- --
--   acceptOnPort = UF.supplyFirst acceptOnAddr (0,0,0,0)
--   
acceptOnPort :: MonadIO m => Unfold m PortNumber Socket acceptOnPortWith :: MonadIO m => [(SocketOption, Int)] -> Unfold m PortNumber Socket -- | Like acceptOnAddr but binds on the localhost IPv4 address -- 127.0.0.1. The server can only be accessed from the local -- host, it cannot be accessed from other hosts on the network. -- --
--   acceptOnPortLocal = UF.supplyFirst acceptOnAddr (127,0,0,1)
--   
acceptOnPortLocal :: MonadIO m => Unfold m PortNumber Socket -- | Like connections but binds on the specified IPv4 address of the -- machine and listens for TCP connections on the specified port. -- -- Pre-release connectionsOnAddr :: MonadAsync m => (Word8, Word8, Word8, Word8) -> PortNumber -> SerialT m Socket connectionsOnAddrWith :: MonadAsync m => [(SocketOption, Int)] -> (Word8, Word8, Word8, Word8) -> PortNumber -> SerialT m Socket -- | Like connections but binds on the IPv4 address 0.0.0.0 -- i.e. on all IPv4 addresses/interfaces of the machine and listens for -- TCP connections on the specified port. -- --
--   connectionsOnPort = connectionsOnAddr (0,0,0,0)
--   
-- -- Pre-release connectionsOnPort :: MonadAsync m => PortNumber -> SerialT m Socket -- | Like connections but binds on the localhost IPv4 address -- 127.0.0.1. The server can only be accessed from the local -- host, it cannot be accessed from other hosts on the network. -- --
--   connectionsOnLocalHost = connectionsOnAddr (127,0,0,1)
--   
-- -- Pre-release connectionsOnLocalHost :: MonadAsync m => PortNumber -> SerialT m Socket -- | Connect to the specified IP address and port number. Returns a -- connected socket or throws an exception. connect :: (Word8, Word8, Word8, Word8) -> PortNumber -> IO Socket -- | Connect to a remote host using IP address and port and run the -- supplied action on the resulting socket. withConnectionM makes -- sure that the socket is closed on normal termination or in case of an -- exception. If closing the socket raises an exception, then this -- exception will be raised by withConnectionM. -- -- Pre-release withConnectionM :: (MonadMask m, MonadIO m) => (Word8, Word8, Word8, Word8) -> PortNumber -> (Socket -> m ()) -> m () -- | Transform an Unfold from a Socket to an unfold from a -- remote IP address and port. The resulting unfold opens a socket, uses -- it using the supplied unfold and then makes sure that the socket is -- closed on normal termination or in case of an exception. If closing -- the socket raises an exception, then this exception will be raised by -- usingConnection. -- -- Pre-release usingConnection :: (MonadCatch m, MonadAsync m) => Unfold m Socket a -> Unfold m ((Word8, Word8, Word8, Word8), PortNumber) a -- | Read a stream from the supplied IPv4 host address and port number. read :: (MonadCatch m, MonadAsync m) => Unfold m ((Word8, Word8, Word8, Word8), PortNumber) Word8 -- | withConnection addr port act opens a connection to the -- specified IPv4 host address and port and passes the resulting socket -- handle to the computation act. The handle will be closed on -- exit from withConnection, whether by normal termination or by -- raising an exception. If closing the handle raises an exception, then -- this exception will be raised by withConnection rather than any -- exception raised by act. -- -- Pre-release withConnection :: (IsStream t, MonadCatch m, MonadAsync m) => (Word8, Word8, Word8, Word8) -> PortNumber -> (Socket -> t m a) -> t m a -- | Read a stream from the supplied IPv4 host address and port number. toBytes :: (IsStream t, MonadCatch m, MonadAsync m) => (Word8, Word8, Word8, Word8) -> PortNumber -> t m Word8 -- | Write a stream to the supplied IPv4 host address and port number. write :: (MonadAsync m, MonadCatch m) => (Word8, Word8, Word8, Word8) -> PortNumber -> Fold m Word8 () -- | Like write but provides control over the write buffer. Output -- will be written to the IO device as soon as we collect the specified -- number of input elements. writeWithBufferOf :: (MonadAsync m, MonadCatch m) => Int -> (Word8, Word8, Word8, Word8) -> PortNumber -> Fold m Word8 () -- | Write a stream to the supplied IPv4 host address and port number. putBytes :: (MonadCatch m, MonadAsync m) => (Word8, Word8, Word8, Word8) -> PortNumber -> SerialT m Word8 -> m () -- | Like write but provides control over the write buffer. Output -- will be written to the IO device as soon as we collect the specified -- number of input elements. putBytesWithBufferOf :: (MonadCatch m, MonadAsync m) => Int -> (Word8, Word8, Word8, Word8) -> PortNumber -> SerialT m Word8 -> m () -- | Write a stream of arrays to the supplied IPv4 host address and port -- number. writeChunks :: (MonadAsync m, MonadCatch m) => (Word8, Word8, Word8, Word8) -> PortNumber -> Fold m (Array Word8) () -- | Write a stream of arrays to the supplied IPv4 host address and port -- number. putChunks :: (MonadCatch m, MonadAsync m) => (Word8, Word8, Word8, Word8) -> PortNumber -> SerialT m (Array Word8) -> m () -- | Send an input stream to a remote host and produce the output stream -- from the host. The server host just acts as a transformation function -- on the input stream. Both sending and receiving happen asynchronously. -- -- Pre-release processBytes :: (IsStream t, MonadAsync m, MonadCatch m) => (Word8, Word8, Word8, Word8) -> PortNumber -> SerialT m Word8 -> t m Word8 -- | The fundamental singleton IO APIs are getChunk and -- putChunk and the fundamental stream IO APIs built on top of -- those are readChunksWithBufferOf and writeChunks. Rest -- of this module is just combinatorial programming using these. -- -- We can achieve line buffering by folding lines in the input stream -- into a stream of arrays using Stream.splitOn or Fold.takeEndBy_ and -- similar operations. One can wrap the input stream in Maybe type -- and then use writeMaybesWithBufferOf to achieve user controlled -- buffering. module Streamly.Internal.FileSystem.Handle -- | Read a ByteArray consisting of one or more bytes from a file -- handle. If no data is available on the handle it blocks until at least -- one byte becomes available. If any data is available then it -- immediately returns that data without blocking. As a result of this -- behavior, it may read less than or equal to the size requested. getChunk :: MonadIO m => Int -> Handle -> m (Array Word8) -- | Read a ByteArray consisting of exactly the specified number -- of bytes from a file handle. -- -- Unimplemented getChunkOf :: Int -> Handle -> IO (Array Word8) -- | Write an Array to a file handle. putChunk :: (MonadIO m, Storable a) => Handle -> Array a -> m () -- | Unfolds a file handle into a byte stream. IO requests to the device -- are performed in sizes of defaultChunkSize. -- --
--   >>> read = Unfold.many Handle.readChunks Array.read
--   
read :: MonadIO m => Unfold m Handle Word8 -- | Unfolds the tuple (bufsize, handle) into a byte stream, read -- requests to the IO device are performed using buffers of -- bufsize. -- --
--   >>> readWithBufferOf = Unfold.many Handle.readChunksWithBufferOf Array.read
--   
readWithBufferOf :: MonadIO m => Unfold m (Int, Handle) Word8 -- | Generate a byte stream from a file Handle. -- --
--   >>> toBytes h = Stream.unfoldMany Array.read $ Handle.toChunks h
--   
-- -- Pre-release toBytes :: (IsStream t, MonadIO m) => Handle -> t m Word8 -- | toBytesWithBufferOf bufsize handle reads a byte stream from a -- file handle, reads are performed in chunks of up to bufsize. -- --
--   >>> toBytesWithBufferOf size h = Stream.unfoldMany Array.read $ Handle.toChunksWithBufferOf size h
--   
-- -- Pre-release toBytesWithBufferOf :: (IsStream t, MonadIO m) => Int -> Handle -> t m Word8 -- | Unfolds a handle into a stream of Word8 arrays. Requests to the -- IO device are performed using a buffer of size -- defaultChunkSize. The size of arrays in the resulting stream -- are therefore less than or equal to defaultChunkSize. -- --
--   >>> readChunks = Unfold.supplyFirst IO.defaultChunkSize Handle.readChunksWithBufferOf
--   
readChunks :: MonadIO m => Unfold m Handle (Array Word8) -- | Unfold the tuple (bufsize, handle) into a stream of -- Word8 arrays. Read requests to the IO device are performed -- using a buffer of size bufsize. The size of an array in the -- resulting stream is always less than or equal to bufsize. readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Handle) (Array Word8) -- | toChunksWithBufferOf size handle reads a stream of arrays -- from the file handle handle. The maximum size of a single -- array is limited to size. The actual size read may be less -- than or equal to size. -- --
--   >>> toChunksWithBufferOf size h = Stream.unfold Handle.readChunksWithBufferOf (size, h)
--   
toChunksWithBufferOf :: (IsStream t, MonadIO m) => Int -> Handle -> t m (Array Word8) -- | toChunks handle reads a stream of arrays from the specified -- file handle. The maximum size of a single array is limited to -- defaultChunkSize. The actual size read may be less than or -- equal to defaultChunkSize. -- --
--   >>> toChunks = Handle.toChunksWithBufferOf IO.defaultChunkSize
--   
toChunks :: (IsStream t, MonadIO m) => Handle -> t m (Array Word8) -- | Write a byte stream to a file handle. Accumulates the input in chunks -- of up to defaultChunkSize before writing to the IO device. -- --
--   >>> write = Handle.writeWithBufferOf IO.defaultChunkSize
--   
write :: MonadIO m => Handle -> Fold m Word8 () -- | Like write but uses the experimental Refold API. -- -- Internal consumer :: MonadIO m => Refold m Handle Word8 () -- | writeWithBufferOf reqSize handle writes the input stream to -- handle. Bytes in the input stream are collected into a buffer -- until we have a chunk of reqSize and then written to the IO -- device. -- --
--   >>> writeWithBufferOf n h = Fold.chunksOf n (Array.writeNUnsafe n) (Handle.writeChunks h)
--   
writeWithBufferOf :: MonadIO m => Int -> Handle -> Fold m Word8 () -- | Write a stream of Maybe values. Keep buffering the just values -- in an array until a Nothing is encountered or the buffer size -- exceeds the specified limit, at that point flush the buffer to the -- handle. -- -- Pre-release writeMaybesWithBufferOf :: MonadIO m => Int -> Handle -> Fold m (Maybe Word8) () -- | Write a byte stream to a file handle. Accumulates the input in chunks -- of up to defaultChunkSize before writing. -- -- NOTE: This may perform better than the write fold, you can try -- this if you need some extra perf boost. -- --
--   >>> putBytes = Handle.putBytesWithBufferOf IO.defaultChunkSize
--   
putBytes :: MonadIO m => Handle -> SerialT m Word8 -> m () -- | putBytesWithBufferOf bufsize handle stream writes -- stream to handle in chunks of bufsize. A -- write is performed to the IO device as soon as we collect the required -- input size. -- --
--   >>> putBytesWithBufferOf n h m = Handle.putChunks h $ Stream.arraysOf n m
--   
putBytesWithBufferOf :: MonadIO m => Int -> Handle -> SerialT m Word8 -> m () -- | Write a stream of arrays to a handle. Each array in the stream is -- written to the device as a separate IO request. -- -- writeChunks h = Fold.drainBy (Handle.putChunk h) writeChunks :: (MonadIO m, Storable a) => Handle -> Fold m (Array a) () -- | writeChunksWithBufferOf bufsize handle writes a stream of -- arrays to handle after coalescing the adjacent arrays in -- chunks of bufsize. We never split an array, if a single array -- is bigger than the specified size it emitted as it is. Multiple arrays -- are coalesed as long as the total size remains below the specified -- size. writeChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Handle -> Fold m (Array a) () -- | putChunksWithBufferOf bufsize handle stream writes a stream -- of arrays to handle after coalescing the adjacent arrays in -- chunks of bufsize. The chunk size is only a maximum and the -- actual writes could be smaller as we do not split the arrays to fit -- exactly to the specified size. putChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Handle -> SerialT m (Array a) -> m () -- | Write a stream of arrays to a handle. -- --
--   >>> putChunks h = Stream.mapM_ (Handle.putChunk h)
--   
putChunks :: (MonadIO m, Storable a) => Handle -> SerialT m (Array a) -> m () -- | The input to the unfold is (from, to, bufferSize, handle). It -- starts reading from the offset from in the file and reads up -- to the offset to. readChunksFromToWith :: MonadIO m => Unfold m (Int, Int, Int, Handle) (Array Word8) -- |
--   >>> import qualified Streamly.FileSystem.Handle as Handle
--   
-- -- Read and write byte streams and array streams to and from file handles -- (Handle). -- -- The TextEncoding, NewLineMode, and -- Buffering options of the underlying GHC Handle are -- ignored by these APIs. Please use Streamly.Unicode.* modules -- for encoding and decoding a byte stream, use stream splitting -- operations in Streamly.Prelude to create a stream of lines or -- to split the input stream on any other type of boundaries. -- -- To set the read or write start position use hSeek on the -- Handle, the before combinator may be used to do that -- on a streaming combinator. To restrict the length of read or write use -- the stream trimming operations like take. -- -- Note that a Handle is inherently stateful, therefore, we -- cannot use these APIs from multiple threads without serialization; -- reading or writing in one thread would affect the file position for -- other threads. -- -- For additional, experimental APIs take a look at -- Streamly.Internal.FileSystem.Handle module. module Streamly.FileSystem.Handle -- | Read a ByteArray consisting of one or more bytes from a file -- handle. If no data is available on the handle it blocks until at least -- one byte becomes available. If any data is available then it -- immediately returns that data without blocking. As a result of this -- behavior, it may read less than or equal to the size requested. getChunk :: MonadIO m => Int -> Handle -> m (Array Word8) -- | Write an Array to a file handle. putChunk :: (MonadIO m, Storable a) => Handle -> Array a -> m () -- | Unfolds a file handle into a byte stream. IO requests to the device -- are performed in sizes of defaultChunkSize. -- --
--   >>> read = Unfold.many Handle.readChunks Array.read
--   
read :: MonadIO m => Unfold m Handle Word8 -- | Unfolds the tuple (bufsize, handle) into a byte stream, read -- requests to the IO device are performed using buffers of -- bufsize. -- --
--   >>> readWithBufferOf = Unfold.many Handle.readChunksWithBufferOf Array.read
--   
readWithBufferOf :: MonadIO m => Unfold m (Int, Handle) Word8 -- | Unfolds a handle into a stream of Word8 arrays. Requests to the -- IO device are performed using a buffer of size -- defaultChunkSize. The size of arrays in the resulting stream -- are therefore less than or equal to defaultChunkSize. -- --
--   >>> readChunks = Unfold.supplyFirst IO.defaultChunkSize Handle.readChunksWithBufferOf
--   
readChunks :: MonadIO m => Unfold m Handle (Array Word8) -- | Unfold the tuple (bufsize, handle) into a stream of -- Word8 arrays. Read requests to the IO device are performed -- using a buffer of size bufsize. The size of an array in the -- resulting stream is always less than or equal to bufsize. readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Handle) (Array Word8) -- | Write a byte stream to a file handle. Accumulates the input in chunks -- of up to defaultChunkSize before writing to the IO device. -- --
--   >>> write = Handle.writeWithBufferOf IO.defaultChunkSize
--   
write :: MonadIO m => Handle -> Fold m Word8 () -- | writeWithBufferOf reqSize handle writes the input stream to -- handle. Bytes in the input stream are collected into a buffer -- until we have a chunk of reqSize and then written to the IO -- device. -- --
--   >>> writeWithBufferOf n h = Fold.chunksOf n (Array.writeNUnsafe n) (Handle.writeChunks h)
--   
writeWithBufferOf :: MonadIO m => Int -> Handle -> Fold m Word8 () -- | Write a stream of arrays to a handle. Each array in the stream is -- written to the device as a separate IO request. -- -- writeChunks h = Fold.drainBy (Handle.putChunk h) writeChunks :: (MonadIO m, Storable a) => Handle -> Fold m (Array a) () -- | Read and write streams and arrays to and from files specified by their -- paths in the file system. Unlike the handle based APIs which can have -- a read/write session consisting of multiple reads and writes to the -- handle, these APIs are one shot read or write APIs. These APIs open -- the file handle, perform the requested operation and close the handle. -- Thease are safer compared to the handle based APIs as there is no -- possibility of a file descriptor leakage. -- --
--   import qualified Streamly.Internal.FileSystem.File as File
--   
module Streamly.Internal.FileSystem.File -- | withFile name mode act opens a file using -- openFile and passes the resulting handle to the computation -- act. The handle will be closed on exit from withFile, -- whether by normal termination or by raising an exception. If closing -- the handle raises an exception, then this exception will be raised by -- withFile rather than any exception raised by act. -- -- Pre-release withFile :: (IsStream t, MonadCatch m, MonadAsync m) => FilePath -> IOMode -> (Handle -> t m a) -> t m a -- | Unfolds the tuple (bufsize, filepath) into a byte stream, -- read requests to the IO device are performed using buffers of -- bufsize. -- -- Pre-release readWithBufferOf :: (MonadCatch m, MonadAsync m) => Unfold m (Int, FilePath) Word8 -- | Unfolds a file path into a byte stream. IO requests to the device are -- performed in sizes of defaultChunkSize. read :: (MonadCatch m, MonadAsync m) => Unfold m FilePath Word8 -- | Generate a stream of bytes from a file specified by path. The stream -- ends when EOF is encountered. File is locked using multiple reader and -- single writer locking mode. -- -- Pre-release toBytes :: (IsStream t, MonadCatch m, MonadAsync m) => FilePath -> t m Word8 -- | Unfold the tuple (bufsize, filepath) into a stream of -- Word8 arrays. Read requests to the IO device are performed -- using a buffer of size bufsize. The size of an array in the -- resulting stream is always less than or equal to bufsize. -- -- Pre-release readChunksWithBufferOf :: (MonadCatch m, MonadAsync m) => Unfold m (Int, FilePath) (Array Word8) -- | Unfold the tuple (from, to, bufsize, filepath) into a stream -- of Word8 arrays. Read requests to the IO device are performed -- using a buffer of size bufsize starting from absolute offset -- of from till the absolute position of to. The size -- of an array in the resulting stream is always less than or equal to -- bufsize. -- -- Pre-release readChunksFromToWith :: (MonadCatch m, MonadAsync m) => Unfold m (Int, Int, Int, FilePath) (Array Word8) -- | Unfolds a FilePath into a stream of Word8 arrays. -- Requests to the IO device are performed using a buffer of size -- defaultChunkSize. The size of arrays in the resulting stream -- are therefore less than or equal to defaultChunkSize. -- -- Pre-release readChunks :: (MonadCatch m, MonadAsync m) => Unfold m FilePath (Array Word8) -- | toChunksWithBufferOf size file reads a stream of arrays from -- file file. The maximum size of a single array is specified by -- size. The actual size read may be less than or equal to -- size. toChunksWithBufferOf :: (IsStream t, MonadCatch m, MonadAsync m) => Int -> FilePath -> t m (Array Word8) -- | toChunks file reads a stream of arrays from file -- file. The maximum size of a single array is limited to -- defaultChunkSize. The actual size read may be less than -- defaultChunkSize. -- --
--   toChunks = toChunksWithBufferOf defaultChunkSize
--   
toChunks :: (IsStream t, MonadCatch m, MonadAsync m) => FilePath -> t m (Array Word8) -- | Write a byte stream to a file. Accumulates the input in chunks of up -- to defaultChunkSize before writing to the IO device. -- -- Pre-release write :: (MonadIO m, MonadCatch m) => FilePath -> Fold m Word8 () -- | writeWithBufferOf chunkSize handle writes the input stream to -- handle. Bytes in the input stream are collected into a buffer -- until we have a chunk of size chunkSize and then written to -- the IO device. -- -- Pre-release writeWithBufferOf :: (MonadIO m, MonadCatch m) => Int -> FilePath -> Fold m Word8 () -- | Write a byte stream to a file. Combines the bytes in chunks of size up -- to defaultChunkSize before writing. If the file exists it is -- truncated to zero size before writing. If the file does not exist it -- is created. File is locked using single writer locking mode. -- -- Pre-release fromBytes :: (MonadAsync m, MonadCatch m) => FilePath -> SerialT m Word8 -> m () -- | Like write but provides control over the write buffer. Output -- will be written to the IO device as soon as we collect the specified -- number of input elements. fromBytesWithBufferOf :: (MonadAsync m, MonadCatch m) => Int -> FilePath -> SerialT m Word8 -> m () -- | Write an array to a file. Overwrites the file if it exists. putChunk :: Storable a => FilePath -> Array a -> IO () -- | Write a stream of chunks to a handle. Each chunk in the stream is -- written to the device as a separate IO request. -- -- Pre-release writeChunks :: (MonadIO m, MonadCatch m, Storable a) => FilePath -> Fold m (Array a) () -- | Write a stream of arrays to a file. Overwrites the file if it exists. fromChunks :: (MonadAsync m, MonadCatch m, Storable a) => FilePath -> SerialT m (Array a) -> m () -- | Append a byte stream to a file. Combines the bytes in chunks of size -- up to defaultChunkSize before writing. If the file exists then -- the new data is appended to the file. If the file does not exist it is -- created. File is locked using single writer locking mode. append :: (MonadAsync m, MonadCatch m) => FilePath -> SerialT m Word8 -> m () -- | Like append but provides control over the write buffer. Output -- will be written to the IO device as soon as we collect the specified -- number of input elements. appendWithBufferOf :: (MonadAsync m, MonadCatch m) => Int -> FilePath -> SerialT m Word8 -> m () -- | append an array to a file. appendArray :: Storable a => FilePath -> Array a -> IO () -- | Append a stream of arrays to a file. appendChunks :: (MonadAsync m, MonadCatch m, Storable a) => FilePath -> SerialT m (Array a) -> m () -- | This module provides immutable arrays in pinned memory (non GC memory) -- suitable for long lived data storage, random access and for -- interfacing with the operating system. -- -- Arrays in this module are chunks of pinned memory that hold a sequence -- of Storable values of a given type, they cannot store -- non-serializable data like functions. Once created an array cannot be -- modified. Pinned memory allows efficient buffering of long lived data -- without adding any impact to GC. One array is just one pointer visible -- to GC and it does not have to be copied across generations. Moreover, -- pinned memory allows communication with foreign consumers and -- producers (e.g. file or network IO) without copying the data. -- --

Programmer Notes

-- -- To apply a transformation to an array use read to unfold the -- array into a stream, apply a transformation on the stream and then use -- write to fold it back to an array. -- -- This module is designed to be imported qualified: -- --
--   import qualified Streamly.Data.Array.Foreign as Array
--   
-- -- For experimental APIs see Streamly.Internal.Data.Array.Foreign. module Streamly.Data.Array.Foreign data Array a -- | Create an Array from the first N elements of a list. The array -- is allocated to size N, if the list terminates before N elements then -- the array may hold less than N elements. -- -- Since 0.7.0 (Streamly.Memory.Array) fromListN :: Storable a => Int -> [a] -> Array a -- | Create an Array from a list. The list must be of finite size. -- -- Since 0.7.0 (Streamly.Memory.Array) fromList :: Storable a => [a] -> Array a -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- -- Since 0.7.0 (Streamly.Memory.Array) writeN :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Caution! Do not use this on infinite streams. -- -- Since 0.7.0 (Streamly.Memory.Array) write :: forall m a. (MonadIO m, Storable a) => Fold m a (Array a) -- | writeLastN n folds a maximum of n elements from the -- end of the input stream to an Array. writeLastN :: (Storable a, MonadIO m) => Int -> Fold m a (Array a) -- | Convert an Array into a list. -- -- Since 0.7.0 (Streamly.Memory.Array) toList :: Storable a => Array a -> [a] -- | Unfold an array into a stream. -- -- Since 0.7.0 (Streamly.Memory.Array) read :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a -- | Unfold an array into a stream in reverse order. readRev :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a -- | Cast an array having elements of type a into an array having -- elements of type b. The length of the array should be a -- multiple of the size of the target element otherwise Nothing is -- returned. cast :: forall a b. Storable b => Array a -> Maybe (Array b) -- | Cast an Array a into an Array Word8. asBytes :: Array a -> Array Word8 -- | O(1) Get the length of the array i.e. the number of elements in -- the array. -- -- Since 0.7.0 (Streamly.Memory.Array) length :: forall a. Storable a => Array a -> Int -- | O(1) Lookup the element at the given index. Index starts from -- 0. getIndex :: forall a. Storable a => Array a -> Int -> Maybe a -- | Low level IO routines interfacing the operating system. module Streamly.Internal.System.IOVec.Type data IOVec IOVec :: {-# UNPACK #-} !Ptr Word8 -> {-# UNPACK #-} !Word64 -> IOVec [iovBase] :: IOVec -> {-# UNPACK #-} !Ptr Word8 [iovLen] :: IOVec -> {-# UNPACK #-} !Word64 c_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize c_safe_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize instance GHC.Show.Show Streamly.Internal.System.IOVec.Type.IOVec instance GHC.Classes.Eq Streamly.Internal.System.IOVec.Type.IOVec instance Foreign.Storable.Storable Streamly.Internal.System.IOVec.Type.IOVec -- | Low level IO routines interfacing the operating system. module Streamly.Internal.System.IOVec data IOVec IOVec :: {-# UNPACK #-} !Ptr Word8 -> {-# UNPACK #-} !Word64 -> IOVec [iovBase] :: IOVec -> {-# UNPACK #-} !Ptr Word8 [iovLen] :: IOVec -> {-# UNPACK #-} !Word64 c_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize c_safe_writev :: CInt -> Ptr IOVec -> CInt -> IO CSsize -- | groupIOVecsOf maxBytes maxEntries groups arrays in the -- incoming stream to create a stream of IOVec arrays with a -- maximum of maxBytes bytes in each array and a maximum of -- maxEntries entries in each array. groupIOVecsOf :: MonadIO m => Int -> Int -> Stream m (Array a) -> Stream m (Array IOVec) -- | groupIOVecsOf maxBytes maxEntries groups arrays in the -- incoming stream to create a stream of IOVec arrays with a -- maximum of maxBytes bytes in each array and a maximum of -- maxEntries entries in each array. groupIOVecsOfMut :: MonadIO m => Int -> Int -> Stream m (Array a) -> Stream m (Array IOVec) -- | Low level IO routines interfacing the operating system. module Streamly.Internal.FileSystem.FDIO -- | write FD buffer offset length tries to write data on the -- given filesystem fd (cannot be a socket) up to sepcified length -- starting from the given offset in the buffer. The write will not block -- the OS thread, it may suspend the Haskell thread until write can -- proceed. Returns the actual amount of data written. write :: FD -> Ptr Word8 -> Int -> CSize -> IO CInt -- | Keep writing in a loop until all data in the buffer has been written. writeAll :: FD -> Ptr Word8 -> Int -> IO () -- | write FD iovec count tries to write data on the given -- filesystem fd (cannot be a socket) from an iovec with specified number -- of entries. The write will not block the OS thread, it may suspend the -- Haskell thread until write can proceed. Returns the actual amount of -- data written. writev :: FD -> Ptr IOVec -> Int -> IO CInt -- | Keep writing an iovec in a loop until all the iovec entries are -- written. writevAll :: FD -> Ptr IOVec -> Int -> IO () module Streamly.Internal.Unicode.Char -- | Select alphabetic characters in the ascii character set. -- -- Pre-release isAsciiAlpha :: Char -> Bool data NormalizationMode -- | Canonical decomposition. NFD :: NormalizationMode -- | Compatibility decomposition. NFKD :: NormalizationMode -- | Canonical decomposition followed by canonical composition. NFC :: NormalizationMode -- | Compatibility decomposition followed by canonical composition. NFKC :: NormalizationMode normalize :: (IsStream t, Monad m) => NormalizationMode -> t m Char -> t m Char instance GHC.Enum.Enum Streamly.Internal.Unicode.Char.NormalizationMode instance GHC.Show.Show Streamly.Internal.Unicode.Char.NormalizationMode instance GHC.Classes.Eq Streamly.Internal.Unicode.Char.NormalizationMode -- | To parse a text input, use the decode routines from -- Streamly.Unicode.Stream module to convert an input byte stream -- to a Unicode Char stream and then use these parsers on the Char -- stream. module Streamly.Internal.Unicode.Char.Parser space :: MonadCatch m => Parser m Char Char lower :: MonadCatch m => Parser m Char Char upper :: MonadCatch m => Parser m Char Char alpha :: MonadCatch m => Parser m Char Char alphaNum :: MonadCatch m => Parser m Char Char print :: MonadCatch m => Parser m Char Char digit :: MonadCatch m => Parser m Char Char octDigit :: MonadCatch m => Parser m Char Char hexDigit :: MonadCatch m => Parser m Char Char letter :: MonadCatch m => Parser m Char Char mark :: MonadCatch m => Parser m Char Char number :: MonadCatch m => Parser m Char Char punctuation :: MonadCatch m => Parser m Char Char symbol :: MonadCatch m => Parser m Char Char separator :: MonadCatch m => Parser m Char Char ascii :: MonadCatch m => Parser m Char Char latin1 :: MonadCatch m => Parser m Char Char asciiUpper :: MonadCatch m => Parser m Char Char asciiLower :: MonadCatch m => Parser m Char Char -- | Match a specific character. char :: MonadCatch m => Char -> Parser m Char Char -- | Parse and decode an unsigned integral decimal number. decimal :: (MonadCatch m, Integral a) => Parser m Char a -- | Parse and decode an unsigned integral hexadecimal number. The hex -- digits 'a' through 'f' may be upper or lower case. -- -- Note: This parser does not accept a leading "0x" string. hexadecimal :: (MonadCatch m, Integral a, Bits a) => Parser m Char a -- | Allow an optional leading '+' or '-' sign character -- before any parser. signed :: (Num a, MonadCatch m) => Parser m Char a -> Parser m Char a -- | Parse a Double. -- -- This parser accepts an optional leading sign character, followed by at -- most one decimal digit. The syntax is similar to that accepted by the -- read function, with the exception that a trailing '.' -- is consumed. -- --

Examples

-- -- Examples with behaviour identical to read, if you feed an empty -- continuation to the first result: -- --
--   IS.parse double (IS.fromList "3")     == 3.0
--   IS.parse double (IS.fromList "3.1")   == 3.1
--   IS.parse double (IS.fromList "3e4")   == 30000.0
--   IS.parse double (IS.fromList "3.1e4") == 31000.0
--   IS.parse double (IS.fromList "3e")    == 30
--   
-- -- Examples with behaviour identical to read: -- --
--   IS.parse (IS.fromList ".3")    == error "Parse failed"
--   IS.parse (IS.fromList "e3")    == error "Parse failed"
--   
-- -- Example of difference from read: -- --
--   IS.parse double (IS.fromList "3.foo") == 3.0
--   
-- -- This function does not accept string representations of "NaN" or -- "Infinity". -- -- Unimplemented double :: Parser m Char Double module Streamly.Internal.Unicode.Stream -- | Decode a stream of bytes to Unicode characters by mapping each byte to -- a corresponding Unicode Char in 0-255 range. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) decodeLatin1 :: (IsStream t, Monad m) => t m Word8 -> t m Char -- | Decode a UTF-8 encoded bytestream to a stream of Unicode characters. -- Any invalid codepoint encountered is replaced with the unicode -- replacement character. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) -- -- Since: 0.8.0 (Lenient Behaviour) decodeUtf8 :: (Monad m, IsStream t) => t m Word8 -> t m Char -- | Decode a UTF-8 encoded bytestream to a stream of Unicode characters. -- The function throws an error if an invalid codepoint is encountered. decodeUtf8' :: (Monad m, IsStream t) => t m Word8 -> t m Char -- | Decode a UTF-8 encoded bytestream to a stream of Unicode characters. -- Any invalid codepoint encountered is dropped. decodeUtf8_ :: (Monad m, IsStream t) => t m Word8 -> t m Char data DecodeError DecodeError :: !DecodeState -> !CodePoint -> DecodeError type DecodeState = Word8 type CodePoint = Int -- | Pre-release decodeUtf8Either :: (Monad m, IsStream t) => t m Word8 -> t m (Either DecodeError Char) -- | Pre-release resumeDecodeUtf8Either :: (Monad m, IsStream t) => DecodeState -> CodePoint -> t m Word8 -> t m (Either DecodeError Char) -- | Pre-release decodeUtf8Arrays :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char -- | Pre-release decodeUtf8Arrays' :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char -- | Pre-release decodeUtf8Arrays_ :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char -- | Like encodeLatin1' but silently maps input codepoints beyond -- 255 to arbitrary Latin1 chars in 0-255 range. No error or exception is -- thrown when such mapping occurs. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) -- -- Since: 0.8.0 (Lenient Behaviour) encodeLatin1 :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Encode a stream of Unicode characters to bytes by mapping each -- character to a byte in 0-255 range. Throws an error if the input -- stream contains characters beyond 255. encodeLatin1' :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Like encodeLatin1 but drops the input characters beyond 255. encodeLatin1_ :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Encode a stream of Unicode characters to a UTF-8 encoded bytestream. -- Any Invalid characters (U+D800-U+D8FF) in the input stream are -- replaced by the Unicode replacement character U+FFFD. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) -- -- Since: 0.8.0 (Lenient Behaviour) encodeUtf8 :: (Monad m, IsStream t) => t m Char -> t m Word8 -- | Encode a stream of Unicode characters to a UTF-8 encoded bytestream. -- When any invalid character (U+D800-U+D8FF) is encountered in the input -- stream the function errors out. encodeUtf8' :: (Monad m, IsStream t) => t m Char -> t m Word8 -- | Encode a stream of Unicode characters to a UTF-8 encoded bytestream. -- Any Invalid characters (U+D800-U+D8FF) in the input stream are -- dropped. encodeUtf8_ :: (Monad m, IsStream t) => t m Char -> t m Word8 -- | Encode a stream of String using the supplied encoding scheme. -- Each string is encoded as an Array Word8. encodeStrings :: (MonadIO m, IsStream t) => (SerialT m Char -> SerialT m Word8) -> t m String -> t m (Array Word8) -- | Remove leading whitespace from a string. -- --
--   stripHead = S.dropWhile isSpace
--   
-- -- Pre-release stripHead :: (Monad m, IsStream t) => t m Char -> t m Char -- | Fold each line of the stream using the supplied Fold and stream -- the result. -- --
--   >>> Stream.toList $ lines Fold.toList (Stream.fromList "lines\nthis\nstring\n\n\n")
--   ["lines","this","string","",""]
--   
-- --
--   lines = S.splitOnSuffix (== '\n')
--   
-- -- Pre-release lines :: (Monad m, IsStream t) => Fold m Char b -> t m Char -> t m b -- | Fold each word of the stream using the supplied Fold and stream -- the result. -- --
--   >>> Stream.toList $ words Fold.toList (Stream.fromList "fold these     words")
--   ["fold","these","words"]
--   
-- --
--   words = S.wordsBy isSpace
--   
-- -- Pre-release words :: (Monad m, IsStream t) => Fold m Char b -> t m Char -> t m b -- | Unfold a stream to character streams using the supplied Unfold -- and concat the results suffixing a newline character \n to -- each stream. -- --
--   unlines = Stream.interposeSuffix 'n'
--   unlines = Stream.intercalateSuffix Unfold.fromList "n"
--   
-- -- Pre-release unlines :: (MonadIO m, IsStream t) => Unfold m a Char -> t m a -> t m Char -- | Unfold the elements of a stream to character streams using the -- supplied Unfold and concat the results with a whitespace -- character infixed between the streams. -- --
--   unwords = Stream.interpose ' '
--   unwords = Stream.intercalate Unfold.fromList " "
--   
-- -- Pre-release unwords :: (MonadIO m, IsStream t) => Unfold m a Char -> t m a -> t m Char decodeUtf8D :: Monad m => Stream m Word8 -> Stream m Char decodeUtf8D' :: Monad m => Stream m Word8 -> Stream m Char decodeUtf8D_ :: Monad m => Stream m Word8 -> Stream m Char -- | See section "3.9 Unicode Encoding Forms" in -- https://www.unicode.org/versions/Unicode13.0.0/UnicodeStandard-13.0.pdf encodeUtf8D :: Monad m => Stream m Char -> Stream m Word8 encodeUtf8D' :: Monad m => Stream m Char -> Stream m Word8 encodeUtf8D_ :: Monad m => Stream m Char -> Stream m Word8 decodeUtf8EitherD :: Monad m => Stream m Word8 -> Stream m (Either DecodeError Char) resumeDecodeUtf8EitherD :: Monad m => DecodeState -> CodePoint -> Stream m Word8 -> Stream m (Either DecodeError Char) decodeUtf8ArraysD :: MonadIO m => Stream m (Array Word8) -> Stream m Char decodeUtf8ArraysD' :: MonadIO m => Stream m (Array Word8) -> Stream m Char decodeUtf8ArraysD_ :: MonadIO m => Stream m (Array Word8) -> Stream m Char -- | Same as decodeUtf8 -- | Deprecated: Please use decodeUtf8 instead decodeUtf8Lax :: (IsStream t, Monad m) => t m Word8 -> t m Char -- | Same as encodeLatin1 -- | Deprecated: Please use encodeLatin1 instead encodeLatin1Lax :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Same as encodeUtf8 -- | Deprecated: Please use encodeUtf8 instead encodeUtf8Lax :: (IsStream t, Monad m) => t m Char -> t m Word8 instance GHC.Show.Show Streamly.Internal.Unicode.Stream.DecodeError instance GHC.Show.Show Streamly.Internal.Unicode.Stream.CodingFailureMode module Streamly.Internal.Console.Stdio -- | Unfold standard input into a stream of Word8. read :: MonadIO m => Unfold m () Word8 -- | Read a byte stream from standard input. -- --
--   getBytes = Handle.toBytes stdin
--   getBytes = Stream.unfold Stdio.read ()
--   
-- -- Pre-release getBytes :: MonadIO m => SerialT m Word8 -- | Read a character stream from Utf8 encoded standard input. -- --
--   getChars = Unicode.decodeUtf8 Stdio.getBytes
--   
-- -- Pre-release getChars :: MonadIO m => SerialT m Char -- | Unfolds standard input into a stream of Word8 arrays. readChunks :: MonadIO m => Unfold m () (Array Word8) -- | Read a stream of chunks from standard input. The maximum size of a -- single chunk is limited to defaultChunkSize. The actual size -- read may be less than defaultChunkSize. -- --
--   getChunks = Handle.toChunks stdin
--   getChunks = Stream.unfold Stdio.readChunks ()
--   
-- -- Pre-release getChunks :: MonadIO m => SerialT m (Array Word8) -- | Fold a stream of Word8 to standard output. write :: MonadIO m => Fold m Word8 () -- | Fold a stream of Word8 to standard error. writeErr :: MonadIO m => Fold m Word8 () -- | Write a stream of bytes to standard output. -- --
--   putBytes = Handle.putBytes stdout
--   putBytes = Stream.fold Stdio.write
--   
-- -- Pre-release putBytes :: MonadIO m => SerialT m Word8 -> m () -- | Encode a character stream to Utf8 and write it to standard output. -- --
--   putChars = Stdio.putBytes . Unicode.encodeUtf8
--   
-- -- Pre-release putChars :: MonadIO m => SerialT m Char -> m () -- | Fold a stream of Array Word8 to standard output. writeChunks :: MonadIO m => Fold m (Array Word8) () -- | Fold a stream of Array Word8 to standard error. writeErrChunks :: MonadIO m => Fold m (Array Word8) () -- | Write a stream of chunks to standard output. -- --
--   putChunks = Handle.putChunks stdout
--   putChunks = Stream.fold Stdio.writeChunks
--   
-- -- Pre-release putChunks :: MonadIO m => SerialT m (Array Word8) -> m () -- | Write a stream of strings to standard output using the supplied -- encoding. Output is flushed to the device for each string. -- -- Pre-release putStringsWith :: MonadIO m => (SerialT m Char -> SerialT m Word8) -> SerialT m String -> m () -- | Write a stream of strings to standard output using UTF8 encoding. -- Output is flushed to the device for each string. -- -- Pre-release putStrings :: MonadIO m => SerialT m String -> m () -- | Like putStrings but adds a newline at the end of each string. -- -- XXX This is not portable, on Windows we need to use "rn" instead. -- -- Pre-release putStringsLn :: MonadIO m => SerialT m String -> m () -- | Combinators to work with standard input, output and error streams. -- -- See also: Streamly.Internal.Console.Stdio module Streamly.Console.Stdio -- | Unfold standard input into a stream of Word8. read :: MonadIO m => Unfold m () Word8 -- | Unfolds standard input into a stream of Word8 arrays. readChunks :: MonadIO m => Unfold m () (Array Word8) -- | Fold a stream of Word8 to standard output. write :: MonadIO m => Fold m Word8 () -- | Fold a stream of Array Word8 to standard output. writeChunks :: MonadIO m => Fold m (Array Word8) () -- | Fold a stream of Word8 to standard error. writeErr :: MonadIO m => Fold m Word8 () -- | Fold a stream of Array Word8 to standard error. writeErrChunks :: MonadIO m => Fold m (Array Word8) () -- |

Processing Unicode Strings

-- -- A Char stream is the canonical representation to process -- Unicode strings. It can be processed efficiently using regular stream -- processing operations. A byte stream of Unicode text read from an IO -- device or from an Array in memory can be decoded into a -- Char stream using the decoding routines in this module. A -- String ([Char]) can be converted into a Char -- stream using fromList. An Array Char can be -- unfolded into a stream using the array read unfold. -- --

Storing Unicode Strings

-- -- A stream of Char can be encoded into a byte stream using the -- encoding routines in this module and then written to IO devices or to -- arrays in memory. -- -- If you have to store a Char stream in memory you can convert it -- into a String using toList or using the toList -- fold. The String type can be more efficient than pinned arrays -- for short and short lived strings. -- -- For longer or long lived streams you can fold the Char -- stream as Array Char using the array write fold. The -- Array type provides a more compact representation and pinned -- memory reducing GC overhead. If space efficiency is a concern you can -- use encodeUtf8' on the Char stream before writing it to -- an Array providing an even more compact representation. -- --

String Literals

-- -- SerialT Identity Char and Array Char are instances -- of IsString and IsList, therefore, -- OverloadedStrings and OverloadedLists extensions can -- be used for convenience when specifying unicode strings literals using -- these types. -- --

Pitfalls

-- -- -- --

Experimental APIs

-- -- Some experimental APIs to conveniently process text using the -- Array Char represenation directly can be found in -- Streamly.Internal.Memory.Unicode.Array. -- | Deprecated: Use Streamly.Unicode.Stream instead module Streamly.Data.Unicode.Stream -- | Decode a stream of bytes to Unicode characters by mapping each byte to -- a corresponding Unicode Char in 0-255 range. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) decodeLatin1 :: (IsStream t, Monad m) => t m Word8 -> t m Char -- | Decode a UTF-8 encoded bytestream to a stream of Unicode characters. -- Any invalid codepoint encountered is replaced with the unicode -- replacement character. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) -- -- Since: 0.8.0 (Lenient Behaviour) decodeUtf8 :: (Monad m, IsStream t) => t m Word8 -> t m Char -- | Like encodeLatin1' but silently maps input codepoints beyond -- 255 to arbitrary Latin1 chars in 0-255 range. No error or exception is -- thrown when such mapping occurs. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) -- -- Since: 0.8.0 (Lenient Behaviour) encodeLatin1 :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Encode a stream of Unicode characters to a UTF-8 encoded bytestream. -- Any Invalid characters (U+D800-U+D8FF) in the input stream are -- replaced by the Unicode replacement character U+FFFD. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) -- -- Since: 0.8.0 (Lenient Behaviour) encodeUtf8 :: (Monad m, IsStream t) => t m Char -> t m Word8 -- | Same as decodeUtf8 -- | Deprecated: Please use decodeUtf8 instead decodeUtf8Lax :: (IsStream t, Monad m) => t m Word8 -> t m Char -- | Same as encodeLatin1 -- | Deprecated: Please use encodeLatin1 instead encodeLatin1Lax :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Same as encodeUtf8 -- | Deprecated: Please use encodeUtf8 instead encodeUtf8Lax :: (IsStream t, Monad m) => t m Char -> t m Word8 module Streamly.Internal.Unicode.Utf8 -- | A space efficient, packed, unboxed Unicode container. data Utf8 pack :: String -> Utf8 unpack :: Utf8 -> String toArray :: Utf8 -> Array Word8 instance Control.DeepSeq.NFData Streamly.Internal.Unicode.Utf8.Utf8 -- | This module provides immutable arrays in pinned memory (non GC memory) -- suitable for long lived data storage, random access and for -- interfacing with the operating system. -- -- Arrays in this module are chunks of pinned memory that hold a sequence -- of Storable values of a given type, they cannot store -- non-serializable data like functions. Once created an array cannot be -- modified. Pinned memory allows efficient buffering of long lived data -- without adding any impact to GC. One array is just one pointer visible -- to GC and it does not have to be copied across generations. Moreover, -- pinned memory allows communication with foreign consumers and -- producers (e.g. file or network IO) without copying the data. -- --

Programmer Notes

-- -- To apply a transformation to an array use read to unfold the -- array into a stream, apply a transformation on the stream and then use -- write to fold it back to an array. -- -- This module is designed to be imported qualified: -- --
--   import qualified Streamly.Array as A
--   
-- -- For experimental APIs see Streamly.Internal.Data.Array.Foreign. -- | Deprecated: Use Streamly.Data.Array.Foreign instead module Streamly.Memory.Array data Array a -- | Create an Array from the first N elements of a list. The array -- is allocated to size N, if the list terminates before N elements then -- the array may hold less than N elements. -- -- Since 0.7.0 (Streamly.Memory.Array) fromListN :: Storable a => Int -> [a] -> Array a -- | Create an Array from a list. The list must be of finite size. -- -- Since 0.7.0 (Streamly.Memory.Array) fromList :: Storable a => [a] -> Array a -- | writeN n folds a maximum of n elements from the -- input stream to an Array. -- -- Since 0.7.0 (Streamly.Memory.Array) writeN :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (Array a) -- | Fold the whole input to a single array. -- -- Caution! Do not use this on infinite streams. -- -- Since 0.7.0 (Streamly.Memory.Array) write :: forall m a. (MonadIO m, Storable a) => Fold m a (Array a) -- | Convert an Array into a list. -- -- Since 0.7.0 (Streamly.Memory.Array) toList :: Storable a => Array a -> [a] -- | Unfold an array into a stream. -- -- Since 0.7.0 (Streamly.Memory.Array) read :: forall m a. (Monad m, Storable a) => Unfold m (Array a) a -- | O(1) Get the length of the array i.e. the number of elements in -- the array. -- -- Since 0.7.0 (Streamly.Memory.Array) length :: forall a. Storable a => Array a -> Int -- | Combinators to build Inet/TCP clients and servers. -- --
--   import qualified Streamly.Network.Inet.TCP as TCP
--   
module Streamly.Network.Inet.TCP -- | Unfold a tuple (ipAddr, port) into a stream of connected TCP -- sockets. ipAddr is the local IP address and port is -- the local port on which connections are accepted. acceptOnAddr :: MonadIO m => Unfold m ((Word8, Word8, Word8, Word8), PortNumber) Socket -- | Like acceptOnAddr but binds on the IPv4 address -- 0.0.0.0 i.e. on all IPv4 addresses/interfaces of the machine -- and listens for TCP connections on the specified port. -- --
--   acceptOnPort = UF.supplyFirst acceptOnAddr (0,0,0,0)
--   
acceptOnPort :: MonadIO m => Unfold m PortNumber Socket -- | Like acceptOnAddr but binds on the localhost IPv4 address -- 127.0.0.1. The server can only be accessed from the local -- host, it cannot be accessed from other hosts on the network. -- --
--   acceptOnPortLocal = UF.supplyFirst acceptOnAddr (127,0,0,1)
--   
acceptOnPortLocal :: MonadIO m => Unfold m PortNumber Socket -- | Connect to the specified IP address and port number. Returns a -- connected socket or throws an exception. connect :: (Word8, Word8, Word8, Word8) -> PortNumber -> IO Socket -- | This module provides Array and stream based socket operations to -- connect to remote hosts, to receive connections from remote hosts, and -- to read and write streams and arrays of bytes to and from network -- sockets. -- -- For basic socket types and operations please consult the -- Network.Socket module of the network package. -- --

Examples

-- -- To write a server, use the accept unfold to start listening for -- connections from clients. accept supplies a stream of connected -- sockets. We can map an effectful action on this socket stream to -- handle the connections. The action would typically use socket reading -- and writing operations to communicate with the remote host. We can -- read/write a stream of bytes or a stream of chunks of bytes -- (Array). -- -- Following is a short example of a concurrent echo server. Please note -- that this example can be written even more succinctly by using higher -- level operations from Streamly.Network.Inet.TCP module. -- --
--   {-# LANGUAGE FlexibleContexts #-}
--   
--   import Data.Function ((&))
--   import Network.Socket
--   import Streamly.Network.Socket (SockSpec(..))
--   
--   import qualified Streamly.Prelude as Stream
--   import qualified Streamly.Network.Socket as Socket
--   
--   main = do
--       let spec = SockSpec
--                  { sockFamily = AF_INET
--                  , sockType   = Stream
--                  , sockProto  = defaultProtocol
--                  , sockOpts   = []
--                  }
--           addr = SockAddrInet 8090 (tupleToHostAddress (0,0,0,0))
--        in server spec addr
--   
--       where
--   
--       server spec addr =
--             Stream.unfold Socket.accept (maxListenQueue, spec, addr) -- ParallelT IO Socket
--           & Stream.mapM (Socket.forSocketM echo)                     -- ParallelT IO ()
--           & Stream.fromParallel                                      -- SerialT IO ()
--           & Stream.drain                                             -- IO ()
--   
--       echo sk =
--             Stream.unfold Socket.readChunks sk  -- SerialT IO (Array Word8)
--           & Stream.fold (Socket.writeChunks sk) -- IO ()
--   
-- --

Programmer Notes

-- -- Read IO requests to connected stream sockets are performed in chunks -- of defaultChunkSize. Unless specified otherwise in the API, -- writes are collected into chunks of defaultChunkSize before -- they are written to the socket. APIs are provided to control the -- chunking behavior. -- --
--   import qualified Streamly.Network.Socket as Socket
--   
-- --

See Also

-- -- module Streamly.Network.Socket -- | Specify the socket protocol details. data SockSpec SockSpec :: !Family -> !SocketType -> !ProtocolNumber -> ![(SocketOption, Int)] -> SockSpec [sockFamily] :: SockSpec -> !Family [sockType] :: SockSpec -> !SocketType [sockProto] :: SockSpec -> !ProtocolNumber [sockOpts] :: SockSpec -> ![(SocketOption, Int)] -- | Unfold a three tuple (listenQLen, spec, addr) into a stream -- of connected protocol sockets corresponding to incoming connections. -- listenQLen is the maximum number of pending connections in -- the backlog. spec is the socket protocol and options -- specification and addr is the protocol address where the -- server listens for incoming connections. accept :: MonadIO m => Unfold m (Int, SockSpec, SockAddr) Socket -- | Unfolds a Socket into a byte stream. IO requests to the socket -- are performed in sizes of defaultChunkSize. read :: MonadIO m => Unfold m Socket Word8 -- | Unfolds the tuple (bufsize, socket) into a byte stream, read -- requests to the socket are performed using buffers of -- bufsize. readWithBufferOf :: MonadIO m => Unfold m (Int, Socket) Word8 -- | Unfolds a socket into a stream of Word8 arrays. Requests to the -- socket are performed using a buffer of size defaultChunkSize. -- The size of arrays in the resulting stream are therefore less than or -- equal to defaultChunkSize. readChunks :: MonadIO m => Unfold m Socket (Array Word8) -- | Unfold the tuple (bufsize, socket) into a stream of -- Word8 arrays. Read requests to the socket are performed using a -- buffer of size bufsize. The size of an array in the resulting -- stream is always less than or equal to bufsize. readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Socket) (Array Word8) -- | Read a byte array from a file handle up to a maximum of the requested -- size. If no data is available on the handle it blocks until some data -- becomes available. If data is available then it immediately returns -- that data without blocking. readChunk :: Int -> Socket -> IO (Array Word8) -- | Write a byte stream to a socket. Accumulates the input in chunks of up -- to defaultChunkSize bytes before writing. -- --
--   write = writeWithBufferOf defaultChunkSize
--   
write :: MonadIO m => Socket -> Fold m Word8 () -- | Write a byte stream to a socket. Accumulates the input in chunks of -- specified number of bytes before writing. writeWithBufferOf :: MonadIO m => Int -> Socket -> Fold m Word8 () -- | Write a stream of arrays to a socket. Each array in the stream is -- written to the socket as a separate IO request. writeChunks :: (MonadIO m, Storable a) => Socket -> Fold m (Array a) () -- | writeChunksWithBufferOf bufsize socket writes a stream of -- arrays to socket after coalescing the adjacent arrays in -- chunks of bufsize. Multiple arrays are coalesed as long as -- the total size remains below the specified size. It never splits an -- array, if a single array is bigger than the specified size it emitted -- as it is. writeChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Socket -> Fold m (Array a) () -- | Write an Array to a file handle. writeChunk :: Storable a => Socket -> Array a -> IO () -- | forSocketM action socket runs the monadic computation -- action passing the socket handle to it. The handle will be -- closed on exit from forSocketM, whether by normal termination -- or by raising an exception. If closing the handle raises an exception, -- then this exception will be raised by forSocketM rather than -- any exception raised by action. forSocketM :: (MonadMask m, MonadIO m) => (Socket -> m ()) -> Socket -> m () -- | To run examples in this module: -- --
--   >>> import qualified Streamly.Data.Fold as Fold
--   
--   >>> import qualified Streamly.Prelude as Stream
--   
-- -- We will add some more imports in the examples as needed. -- -- For effectful streams we will use the following IO action that blocks -- for n seconds: -- --
--   >>> import Control.Concurrent (threadDelay)
--   
--   >>> :{
--    delay n = do
--        threadDelay (n * 1000000)   -- sleep for n seconds
--        putStrLn (show n ++ " sec") -- print "n sec"
--        return n                    -- IO Int
--   :}
--   
-- --
--   >>> delay 1
--   1 sec
--   1
--   
-- --

Overview

-- -- Streamly is a framework for modular data flow based programming and -- declarative concurrency. Powerful stream fusion framework in streamly -- allows high performance combinatorial programming even when using byte -- level streams. Streamly API is similar to Haskell lists. -- -- The basic stream type is SerialT. The type SerialT IO -- a is an effectful equivalent of a list [a] using the IO -- monad. Streams can be constructed like lists, except that they use -- nil instead of '[]' and cons instead of :. -- -- cons constructs a pure stream which is more or less the same as -- a list: -- --
--   >>> import Streamly.Prelude (SerialT, cons, consM, nil)
--   
--   >>> stream = 1 `cons` 2 `cons` nil :: SerialT IO Int
--   
--   >>> Stream.toList stream -- IO [Int]
--   [1,2]
--   
-- -- consM constructs a stream from effectful actions: -- --
--   >>> stream = delay 1 `consM` delay 2 `consM` nil
--   
--   >>> Stream.toList stream
--   1 sec
--   2 sec
--   [1,2]
--   
-- --

Console Echo Program

-- -- In the following example, repeatM generates an infinite stream -- of String by repeatedly performing the getLine IO -- action. mapM then applies putStrLn on each element in -- the stream converting it to stream of (). Finally, -- drain folds the stream to IO discarding the () values, thus -- producing only effects. -- --
--   >>> import Data.Function ((&))
--   
-- --
--   > :{
--    Stream.repeatM getLine      -- SerialT IO String
--        & Stream.mapM putStrLn  -- SerialT IO ()
--        & Stream.drain          -- IO ()
--   :}
--   
-- -- This is a console echo program. It is an example of a declarative loop -- written using streaming combinators. Compare it with an imperative -- while loop. -- -- Hopefully, this gives you an idea how we can program declaratively by -- representing loops using streams. In this module, you can find all -- Data.List like functions and many more powerful combinators to -- perform common programming tasks. Also see -- Streamly.Internal.Data.Stream.IsStream module for many more -- Pre-release combinators. See the -- https://github.com/composewell/streamly-examples repository for -- many more real world examples of stream programming. -- --

Polymorphic Combinators

-- -- Streamly has several stream types, SerialT is one type of -- stream with serial execution of actions, AsyncT is another with -- concurrent execution. The combinators in this module are polymorphic -- in stream type. For example, -- --
--   repeatM :: (IsStream t, MonadAsync m) => m a -> t m a
--   
-- -- t is the stream type, m is the underlying -- Monad of the stream (e.g. IO) and a is the type of -- elements in the stream (e.g. Int). -- -- Stream elimination combinators accept a SerialT type instead of -- a polymorphic type to force a concrete monomorphic type by default, -- reducing type errors. That's why in the console echo example above the -- stream type is SerialT. -- --
--   drain :: Monad m => SerialT m a -> m ()
--   
-- -- We can force a certain stream type in polymorphic code by using -- "Stream Type Adaptors". For example, to force AsyncT: -- --
--   >>> Stream.drain $ Stream.fromAsync $ Stream.replicateM 10 $ delay 1
--   ...
--   
-- --

Combining two streams

-- -- Two streams can be combined to form a single stream in various -- interesting ways. serial (append), wSerial (interleave), -- ahead (concurrent, ordered append), async (lazy -- concurrent, unordered append) , wAsync (lazy concurrent, -- unordered interleave), parallel (strict concurrent merge), -- zipWith, zipAsyncWith (concurrent zip), mergeBy, -- mergeAsyncBy (concurrent merge) are some ways of combining two -- streams. -- -- For example, the parallel combinator schedules both the streams -- concurrently. -- --
--   >>> stream1 = Stream.fromListM [delay 3, delay 4]
--   
--   >>> stream2 = Stream.fromListM [delay 1, delay 2]
--   
--   >>> Stream.toList $ stream1 `parallel` stream2
--   ...
--   
-- -- We can chain the operations to combine more than two streams: -- --
--   >>> stream3 = Stream.fromListM [delay 1, delay 2]
--   
--   >>> Stream.toList $ stream1 `parallel` stream2 `parallel` stream3
--   ...
--   
-- -- Concurrent generation (consM) and concurrent merging of streams -- is the fundamental basis of all concurrency in streamly. -- --

Combining many streams

-- -- The concatMapWith combinator can be used to generalize the two -- stream combining combinators to n streams. For example, we -- can use concatMapWith parallel to read concurrently from all -- incoming network connections and combine the input streams into a -- single output stream: -- --
--   import qualified Streamly.Network.Inet.TCP as TCP
--   import qualified Streamly.Network.Socket as Socket
--   
--   Stream.unfold TCP.acceptOnPort 8090
--    & Stream.concatMapWith Stream.parallel (Stream.unfold Socket.read)
--   
-- -- See the streamly-examples repository for a full working -- example. -- --

Concurrent Nested Loops

-- -- The Monad instance of SerialT is an example of nested looping. -- It is in fact a list transformer. Different stream types provide -- different variants of nested looping. For example, the Monad -- instance of ParallelT uses concatMapWith parallel as -- its bind operation. Therefore, each iteration of the loop for -- ParallelT stream can run concurrently. See the documentation -- for individual stream types for the specific execution behavior of the -- stream as well as the behavior of Semigroup and Monad -- instances. -- --

Stream Types

-- -- Streamly has several stream types. These types differ in three -- fundamental operations, consM (IsStream instance), -- <> (Semigroup instance) and >>= -- (Monad instance). Below we will see how consM behaves -- for SerialT, AsyncT and AheadT stream types. -- -- SerialT executes actions serially, so the total delay in the -- following example is 2 + 1 = 3 seconds: -- --
--   >>> stream = delay 2 `consM` delay 1 `consM` nil
--   
--   >>> Stream.toList stream -- IO [Int]
--   2 sec
--   1 sec
--   [2,1]
--   
-- -- AsyncT executes the actions concurrently, so the total delay is -- max 2 1 = 2 seconds: -- --
--   >>> Stream.toList $ Stream.fromAsync stream -- IO [Int]
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- AsyncT produces the results in the order in which execution -- finishes. Notice the order of elements in the list above, it is not -- the same as the order of actions in the stream. -- -- AheadT is similar to AsyncT but the order of results is -- the same as the order of actions, even though they execute -- concurrently: -- --
--   >>> Stream.toList $ Stream.fromAhead stream -- IO [Int]
--   1 sec
--   2 sec
--   [2,1]
--   
-- --

Semigroup Instance

-- -- Earlier we distinguished stream types based on the execution behavior -- of actions within a stream. Stream types are also distinguished based -- on how actions from different streams are scheduled for execution when -- two streams are combined together. -- -- For example, both SerialT and WSerialT execute actions -- within the stream serially, however, they differ in how actions from -- individual streams are executed when two streams are combined with -- <> (the Semigroup instance). -- -- For SerialT, <> has an appending behavior i.e. it -- executes the actions from the second stream after executing actions -- from the first stream: -- --
--   >>> stream1 = Stream.fromListM [delay 1, delay 2]
--   
--   >>> stream2 = Stream.fromListM [delay 3, delay 4]
--   
--   >>> Stream.toList $ stream1 <> stream2
--   1 sec
--   2 sec
--   3 sec
--   4 sec
--   [1,2,3,4]
--   
-- -- For WSerialT, <> has an interleaving behavior i.e. -- it executes one action from the first stream and then one action from -- the second stream and so on: -- --
--   >>> Stream.toList $ Stream.fromWSerial $ stream1 <> stream2
--   1 sec
--   3 sec
--   2 sec
--   4 sec
--   [1,3,2,4]
--   
-- -- The <> operation of SerialT and WSerialT is -- the same as serial and wSerial respectively. The -- serial combinator combines two streams of any type in the same -- way as a serial stream combines. -- --

Concurrent Combinators

-- -- Like consM, there are several other stream generation -- operations whose execution behavior depends on the stream type, they -- all follow behavior similar to consM. -- -- By default, folds like drain force the stream type to be -- SerialT, so replicateM in the following code runs -- serially, and takes 10 seconds: -- --
--   >>> Stream.drain $ Stream.replicateM 10 $ delay 1
--   ...
--   
-- -- We can use the fromAsync combinator to force the argument -- stream to be of AsyncT type, replicateM in the following -- example executes the replicated actions concurrently, thus taking only -- 1 second: -- --
--   >>> Stream.drain $ Stream.fromAsync $ Stream.replicateM 10 $ delay 1
--   ...
--   
-- -- We can use mapM to map an action concurrently: -- --
--   >>> f x = delay 1 >> return (x + 1)
--   
--   >>> Stream.toList $ Stream.fromAhead $ Stream.mapM f $ Stream.fromList [1..3]
--   ...
--   [2,3,4]
--   
-- -- fromAhead forces mapM to happen in AheadT style, thus -- all three actions take only one second even though each individual -- action blocks for a second. -- -- See the documentation of individual combinators to check if it is -- concurrent or not. The concurrent combinators necessarily have a -- MonadAsync m constraint. However, a MonadAsync m -- constraint does not necessarily mean that the combinator is -- concurrent. -- --

Automatic Concurrency Control

-- -- SerialT (and WSerialT) runs all tasks serially whereas -- ParallelT runs all tasks concurrently i.e. one thread per task. -- The stream types AsyncT, WAsyncT, and AheadT -- provide demand driven concurrency. It means that based on the rate at -- which the consumer is consuming the stream, it maintains the optimal -- number of threads to increase or decrease parallelism. -- -- However, the programmer can control the maximum number of threads -- using maxThreads. It provides an upper bound on the concurrent -- IO requests or CPU cores that can be used. maxBuffer limits the -- number of evaluated stream elements that we can buffer. See the -- "Concurrency Control" section for details. -- --

Caveats

-- -- When we use combinators like fromAsync on a piece of code, all -- combinators inside the argument of fromAsync become concurrent which -- is often counter productive. Therefore, we recommend that in a -- pipeline, you identify the combinators that you really want to be -- concurrent and add a fromSerial after those combinators so that -- the code following the combinator remains serial: -- --
--   Stream.fromAsync $ ... concurrent combinator here ... $ Stream.fromSerial $ ...
--   
-- --

Conventions

-- -- Functions with the suffix M are general functions that work -- on monadic arguments. The corresponding functions without the suffix -- M work on pure arguments and can in general be derived from -- their monadic versions but are provided for convenience and for -- consistency with other pure APIs in the base package. -- -- In many cases, short definitions of the combinators are provided in -- the documentation for illustration. The actual implementation may -- differ for performance reasons. module Streamly.Prelude nil :: IsStream t => t m a -- | Construct a stream by adding a pure value at the head of an existing -- stream. For serial streams this is the same as (return a) `consM` -- r but more efficient. For concurrent streams this is not -- concurrent whereas consM is concurrent. For example: -- --
--   > toList $ 1 `cons` 2 `cons` 3 `cons` nil
--   [1,2,3]
--   
cons :: IsStream t => a -> t m a -> t m a infixr 5 `cons` -- | Operator equivalent of cons. -- --
--   > toList $ 1 .: 2 .: 3 .: nil
--   [1,2,3]
--   
(.:) :: IsStream t => a -> t m a -> t m a infixr 5 .: -- | Constructs a stream by adding a monadic action at the head of an -- existing stream. For example: -- --
--   > toList $ getLine `consM` getLine `consM` nil
--   hello
--   world
--   ["hello","world"]
--   
-- -- Concurrent (do not use fromParallel to construct infinite -- streams) consM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 `consM` -- | Operator equivalent of consM. We can read it as "parallel -- colon" to remember that | comes before :. -- --
--   > toList $ getLine |: getLine |: nil
--   hello
--   world
--   ["hello","world"]
--   
-- --
--   let delay = threadDelay 1000000 >> print 1
--   drain $ fromSerial  $ delay |: delay |: delay |: nil
--   drain $ fromParallel $ delay |: delay |: delay |: nil
--   
-- -- Concurrent (do not use fromParallel to construct infinite -- streams) (|:) :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 |: -- | Convert an Unfold into a stream by supplying it an input seed. -- --
--   >>> Stream.drain $ Stream.unfold (Unfold.replicateM 3) (putStrLn "hello")
--   hello
--   hello
--   hello
--   
-- -- Since: 0.7.0 unfold :: (IsStream t, Monad m) => Unfold m a b -> a -> t m b -- |
--   >>> :{
--   unfoldr step s =
--       case step s of
--           Nothing -> Stream.nil
--           Just (a, b) -> a `Stream.cons` unfoldr step b
--   :}
--   
-- -- Build a stream by unfolding a pure step function step -- starting from a seed s. The step function returns the next -- element in the stream and the next seed value. When it is done it -- returns Nothing and the stream ends. For example, -- --
--   >>> :{
--   let f b =
--           if b > 2
--           then Nothing
--           else Just (b, b + 1)
--   in Stream.toList $ Stream.unfoldr f 0
--   :}
--   [0,1,2]
--   
unfoldr :: (Monad m, IsStream t) => (b -> Maybe (a, b)) -> b -> t m a -- | Build a stream by unfolding a monadic step function starting -- from a seed. The step function returns the next element in the stream -- and the next seed value. When it is done it returns Nothing and -- the stream ends. For example, -- --
--   >>> :{
--   let f b =
--           if b > 2
--           then return Nothing
--           else return (Just (b, b + 1))
--   in Stream.toList $ Stream.unfoldrM f 0
--   :}
--   [0,1,2]
--   
-- -- When run concurrently, the next unfold step can run concurrently with -- the processing of the output of the previous step. Note that more than -- one step cannot run concurrently as the next step depends on the -- output of the previous step. -- --
--   >>> :{
--   let f b =
--           if b > 2
--           then return Nothing
--           else threadDelay 1000000 >> return (Just (b, b + 1))
--   in Stream.toList $ Stream.delay 1 $ Stream.fromAsync $ Stream.unfoldrM f 0
--   :}
--   [0,1,2]
--   
-- -- Concurrent -- -- Since: 0.1.0 unfoldrM :: forall t m b a. (IsStream t, MonadAsync m) => (b -> m (Maybe (a, b))) -> b -> t m a -- |
--   fromPure a = a `cons` nil
--   
-- -- Create a singleton stream from a pure value. -- -- The following holds in monadic streams, but not in Zip streams: -- --
--   fromPure = pure
--   fromPure = fromEffect . pure
--   
-- -- In Zip applicative streams fromPure is not the same as -- pure because in that case pure is equivalent to -- repeat instead. fromPure and pure are equally -- efficient, in other cases fromPure may be slightly more -- efficient than the other equivalent definitions. -- -- Since: 0.8.0 (Renamed yield to fromPure) fromPure :: IsStream t => a -> t m a -- |
--   fromEffect m = m `consM` nil
--   
-- -- Create a singleton stream from a monadic action. -- --
--   > Stream.toList $ Stream.fromEffect getLine
--   hello
--   ["hello"]
--   
-- -- Since: 0.8.0 (Renamed yieldM to fromEffect) fromEffect :: (Monad m, IsStream t) => m a -> t m a -- | Generate an infinite stream by repeating a pure value. repeat :: (IsStream t, Monad m) => a -> t m a -- |
--   >>> repeatM = fix . consM
--   
--   >>> repeatM = cycle1 . fromEffect
--   
-- -- Generate a stream by repeatedly executing a monadic action forever. -- --
--   >>> :{
--   repeatAsync =
--          Stream.repeatM (threadDelay 1000000 >> print 1)
--        & Stream.take 10
--        & Stream.fromAsync
--        & Stream.drain
--   :}
--   
-- -- Concurrent, infinite (do not use with fromParallel) repeatM :: (IsStream t, MonadAsync m) => m a -> t m a -- |
--   >>> replicate n = Stream.take n . Stream.repeat
--   
-- -- Generate a stream of length n by repeating a value n -- times. replicate :: (IsStream t, Monad m) => Int -> a -> t m a -- |
--   >>> replicateM n = Stream.take n . Stream.repeatM
--   
-- -- Generate a stream by performing a monadic action n times. -- Same as: -- --
--   >>> pr n = threadDelay 1000000 >> print n
--   
-- -- This runs serially and takes 3 seconds: -- --
--   >>> Stream.drain $ Stream.fromSerial $ Stream.replicateM 3 $ pr 1
--   1
--   1
--   1
--   
-- -- This runs concurrently and takes just 1 second: -- --
--   >>> Stream.drain $ Stream.fromAsync  $ Stream.replicateM 3 $ pr 1
--   1
--   1
--   1
--   
-- -- Concurrent replicateM :: forall t m a. (IsStream t, MonadAsync m) => Int -> m a -> t m a -- | Types that can be enumerated as a stream. The operations in this type -- class are equivalent to those in the Enum type class, except -- that these generate a stream instead of a list. Use the functions in -- Streamly.Internal.Data.Stream.Enumeration module to define new -- instances. class Enum a => Enumerable a -- | enumerateFrom from generates a stream starting with the -- element from, enumerating up to maxBound when the type -- is Bounded or generating an infinite stream when the type is -- not Bounded. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFrom (0 :: Int)
--   [0,1,2,3]
--   
-- -- For Fractional types, enumeration is numerically stable. -- However, no overflow or underflow checks are performed. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFrom 1.1
--   [1.1,2.1,3.1,4.1]
--   
enumerateFrom :: (Enumerable a, IsStream t, Monad m) => a -> t m a -- | Generate a finite stream starting with the element from, -- enumerating the type up to the value to. If to is -- smaller than from then an empty stream is returned. -- --
--   >>> Stream.toList $ Stream.enumerateFromTo 0 4
--   [0,1,2,3,4]
--   
-- -- For Fractional types, the last element is equal to the -- specified to value after rounding to the nearest integral -- value. -- --
--   >>> Stream.toList $ Stream.enumerateFromTo 1.1 4
--   [1.1,2.1,3.1,4.1]
--   
--   >>> Stream.toList $ Stream.enumerateFromTo 1.1 4.6
--   [1.1,2.1,3.1,4.1,5.1]
--   
enumerateFromTo :: (Enumerable a, IsStream t, Monad m) => a -> a -> t m a -- | enumerateFromThen from then generates a stream whose first -- element is from, the second element is then and the -- successive elements are in increments of then - from. -- Enumeration can occur downwards or upwards depending on whether -- then comes before or after from. For Bounded -- types the stream ends when maxBound is reached, for unbounded -- types it keeps enumerating infinitely. -- --
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThen 0 2
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.take 4 $ Stream.enumerateFromThen 0 (-2)
--   [0,-2,-4,-6]
--   
enumerateFromThen :: (Enumerable a, IsStream t, Monad m) => a -> a -> t m a -- | enumerateFromThenTo from then to generates a finite stream -- whose first element is from, the second element is -- then and the successive elements are in increments of -- then - from up to to. Enumeration can occur -- downwards or upwards depending on whether then comes before -- or after from. -- --
--   >>> Stream.toList $ Stream.enumerateFromThenTo 0 2 6
--   [0,2,4,6]
--   
--   >>> Stream.toList $ Stream.enumerateFromThenTo 0 (-2) (-6)
--   [0,-2,-4,-6]
--   
enumerateFromThenTo :: (Enumerable a, IsStream t, Monad m) => a -> a -> a -> t m a -- |
--   enumerate = enumerateFrom minBound
--   
-- -- Enumerate a Bounded type from its minBound to -- maxBound enumerate :: (IsStream t, Monad m, Bounded a, Enumerable a) => t m a -- |
--   enumerateTo = enumerateFromTo minBound
--   
-- -- Enumerate a Bounded type from its minBound to specified -- value. enumerateTo :: (IsStream t, Monad m, Bounded a, Enumerable a) => a -> t m a -- |
--   >>> iterate f x = x `Stream.cons` iterate f x
--   
-- -- Generate an infinite stream with x as the first element and -- each successive element derived by applying the function f on -- the previous element. -- --
--   >>> Stream.toList $ Stream.take 5 $ Stream.iterate (+1) 1
--   [1,2,3,4,5]
--   
iterate :: (IsStream t, Monad m) => (a -> a) -> a -> t m a -- |
--   >>> iterateM f m = m >>= \a -> return a `Stream.consM` iterateM f (f a)
--   
-- -- Generate an infinite stream with the first element generated by the -- action m and each successive element derived by applying the -- monadic function f on the previous element. -- --
--   >>> pr n = threadDelay 1000000 >> print n
--   
--   >>> :{
--   Stream.iterateM (\x -> pr x >> return (x + 1)) (return 0)
--       & Stream.take 3
--       & Stream.fromSerial
--       & Stream.toList
--   :}
--   0
--   1
--   [0,1,2]
--   
-- -- When run concurrently, the next iteration can run concurrently with -- the processing of the previous iteration. Note that more than one -- iteration cannot run concurrently as the next iteration depends on the -- output of the previous iteration. -- --
--   >>> :{
--   Stream.iterateM (\x -> pr x >> return (x + 1)) (return 0)
--       & Stream.delay 1
--       & Stream.take 3
--       & Stream.fromAsync
--       & Stream.toList
--   :}
--   0
--   1
--   ...
--   
-- -- Concurrent -- -- Since: 0.1.2 -- -- Since: 0.7.0 (signature change) iterateM :: forall t m a. (IsStream t, MonadAsync m) => (a -> m a) -> m a -> t m a -- |
--   >>> fromIndices f = fmap f $ Stream.enumerateFrom 0
--   
--   >>> fromIndices f = let g i = f i `Stream.cons` g (i + 1) in g 0
--   
-- -- Generate an infinite stream, whose values are the output of a function -- f applied on the corresponding index. Index starts at 0. -- --
--   >>> Stream.toList $ Stream.take 5 $ Stream.fromIndices id
--   [0,1,2,3,4]
--   
fromIndices :: (IsStream t, Monad m) => (Int -> a) -> t m a -- |
--   >>> fromIndicesM f = Stream.mapM f $ Stream.enumerateFrom 0
--   
--   >>> fromIndicesM f = let g i = f i `Stream.consM` g (i + 1) in g 0
--   
-- -- Generate an infinite stream, whose values are the output of a monadic -- function f applied on the corresponding index. Index starts -- at 0. -- -- Concurrent fromIndicesM :: forall t m a. (IsStream t, MonadAsync m) => (Int -> m a) -> t m a -- |
--   fromList = foldr cons nil
--   
-- -- Construct a stream from a list of pure values. This is more efficient -- than fromFoldable for serial streams. fromList :: (Monad m, IsStream t) => [a] -> t m a -- |
--   >>> fromListM = Stream.fromFoldableM
--   
--   >>> fromListM = Stream.sequence . Stream.fromList
--   
--   >>> fromListM = Stream.mapM id . Stream.fromList
--   
--   >>> fromListM = Prelude.foldr Stream.consM Stream.nil
--   
-- -- Construct a stream from a list of monadic actions. This is more -- efficient than fromFoldableM for serial streams. fromListM :: (MonadAsync m, IsStream t) => [m a] -> t m a -- |
--   >>> fromFoldable = Prelude.foldr Stream.cons Stream.nil
--   
-- -- Construct a stream from a Foldable containing pure values: fromFoldable :: (IsStream t, Foldable f) => f a -> t m a -- |
--   >>> fromFoldableM = Prelude.foldr Stream.consM Stream.nil
--   
-- -- Construct a stream from a Foldable containing monadic actions. -- --
--   >>> pr n = threadDelay 1000000 >> print n
--   
--   >>> Stream.drain $ Stream.fromSerial $ Stream.fromFoldableM $ map pr [1,2,3]
--   1
--   2
--   3
--   
-- --
--   >>> Stream.drain $ Stream.fromAsync $ Stream.fromFoldableM $ map pr [1,2,3]
--   ...
--   ...
--   ...
--   
-- -- Concurrent (do not use with fromParallel on infinite -- containers) fromFoldableM :: (IsStream t, MonadAsync m, Foldable f) => f (m a) -> t m a -- | Fold a stream using the supplied left Fold and reducing the -- resulting expression strictly at each step. The behavior is similar to -- foldl'. A Fold can terminate early without consuming -- the full stream. See the documentation of individual Folds for -- termination behavior. -- --
--   >>> Stream.fold Fold.sum (Stream.enumerateFromTo 1 100)
--   5050
--   
-- -- Folds never fail, therefore, they produce a default value even when no -- input is provided. It means we can always fold an empty stream and get -- a valid result. For example: -- --
--   >>> Stream.fold Fold.sum Stream.nil
--   0
--   
-- -- However, foldMany on an empty stream results in an empty -- stream. Therefore, Stream.fold f is not the same as -- Stream.head . Stream.foldMany f. -- --
--   fold f = Stream.parse (Parser.fromFold f)
--   
fold :: Monad m => Fold m a b -> SerialT m a -> m b -- | Decompose a stream into its head and tail. If the stream is empty, -- returns Nothing. If the stream is non-empty, returns Just -- (a, ma), where a is the head of the stream and -- ma its tail. -- -- This is a brute force primitive. Avoid using it as long as possible, -- use it when no other combinator can do the job. This can be used to do -- pretty much anything in an imperative manner, as it just breaks down -- the stream into individual elements and we can loop over them as we -- deem fit. For example, this can be used to convert a streamly stream -- into other stream types. -- -- All the folds in this module can be expressed in terms of -- uncons, however the specific implementations are generally more -- efficient. uncons :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (a, t m a)) -- |
--   tail = fmap (fmap snd) . Stream.uncons
--   
-- -- Extract all but the first element of the stream, if any. tail :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (t m a)) -- | Extract all but the last element of the stream, if any. init :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (t m a)) -- | Right associative/lazy pull fold. foldrM build final stream -- constructs an output structure using the step function build. -- build is invoked with the next input element and the -- remaining (lazy) tail of the output structure. It builds a lazy output -- expression using the two. When the "tail structure" in the output -- expression is evaluated it calls build again thus lazily -- consuming the input stream until either the output expression -- built by build is free of the "tail" or the input is -- exhausted in which case final is used as the terminating case -- for the output structure. For more details see the description in the -- previous section. -- -- Example, determine if any element is odd in a stream: -- --
--   >>> Stream.foldrM (\x xs -> if odd x then return True else xs) (return False) $ Stream.fromList (2:4:5:undefined)
--   True
--   
-- -- Since: 0.7.0 (signature changed) -- -- Since: 0.2.0 (signature changed) -- -- Since: 0.1.0 foldrM :: Monad m => (a -> m b -> m b) -> m b -> SerialT m a -> m b -- | Right fold, lazy for lazy monads and pure streams, and strict for -- strict monads. -- -- Please avoid using this routine in strict monads like IO unless you -- need a strict right fold. This is provided only for use in lazy monads -- (e.g. Identity) or pure streams. Note that with this signature it is -- not possible to implement a lazy foldr when the monad m is -- strict. In that case it would be strict in its accumulator and -- therefore would necessarily consume all its input. foldr :: Monad m => (a -> b -> b) -> b -> SerialT m a -> m b -- | Left associative/strict push fold. foldl' reduce initial -- stream invokes reduce with the accumulator and the next -- input in the input stream, using initial as the initial value -- of the current value of the accumulator. When the input is exhausted -- the current value of the accumulator is returned. Make sure to use a -- strict data structure for accumulator to not build unnecessary lazy -- expressions unless that's what you want. See the previous section for -- more details. foldl' :: Monad m => (b -> a -> b) -> b -> SerialT m a -> m b -- | Strict left fold, for non-empty streams, using first element as the -- starting value. Returns Nothing if the stream is empty. foldl1' :: Monad m => (a -> a -> a) -> SerialT m a -> m (Maybe a) -- | Like foldl' but with a monadic step function. -- -- Since: 0.2.0 -- -- Since: 0.8.0 (signature change) foldlM' :: Monad m => (b -> a -> m b) -> m b -> SerialT m a -> m b -- |
--   drain = mapM_ (\_ -> return ())
--   drain = Stream.fold Fold.drain
--   
-- -- Run a stream, discarding the results. By default it interprets the -- stream as SerialT, to run other types of streams use the type -- adapting combinators for example Stream.drain . -- fromAsync. drain :: Monad m => SerialT m a -> m () -- | Extract the last element of the stream, if any. -- --
--   last xs = xs !! (Stream.length xs - 1)
--   last = Stream.fold Fold.last
--   
last :: Monad m => SerialT m a -> m (Maybe a) -- | Determine the length of the stream. length :: Monad m => SerialT m a -> m Int -- | Determine the sum of all elements of a stream of numbers. Returns -- 0 when the stream is empty. Note that this is not numerically -- stable for floating point numbers. -- --
--   sum = Stream.fold Fold.sum
--   
sum :: (Monad m, Num a) => SerialT m a -> m a -- | Determine the product of all elements of a stream of numbers. Returns -- 1 when the stream is empty. -- --
--   product = Stream.fold Fold.product
--   
product :: (Monad m, Num a) => SerialT m a -> m a -- | Determine the maximum element in a stream using the supplied -- comparison function. -- --
--   maximumBy = Stream.fold Fold.maximumBy
--   
maximumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) -- |
--   maximum = maximumBy compare
--   maximum = Stream.fold Fold.maximum
--   
-- -- Determine the maximum element in a stream. maximum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a) -- | Determine the minimum element in a stream using the supplied -- comparison function. -- --
--   minimumBy = Stream.fold Fold.minimumBy
--   
minimumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) -- |
--   minimum = minimumBy compare
--   minimum = Stream.fold Fold.minimum
--   
-- -- Determine the minimum element in a stream. minimum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a) -- | Ensures that all the elements of the stream are identical and then -- returns that unique element. the :: (Eq a, Monad m) => SerialT m a -> m (Maybe a) -- |
--   drainN n = Stream.drain . Stream.take n
--   drainN n = Stream.fold (Fold.take n Fold.drain)
--   
-- -- Run maximum up to n iterations of a stream. drainN :: Monad m => Int -> SerialT m a -> m () -- |
--   drainWhile p = Stream.drain . Stream.takeWhile p
--   
-- -- Run a stream as long as the predicate holds true. drainWhile :: Monad m => (a -> Bool) -> SerialT m a -> m () -- | Lookup the element at the given index. (!!) :: Monad m => SerialT m a -> Int -> m (Maybe a) -- | Extract the first element of the stream, if any. -- --
--   head = (!! 0)
--   head = Stream.fold Fold.head
--   
head :: Monad m => SerialT m a -> m (Maybe a) -- | Returns the first element that satisfies the given predicate. -- --
--   findM = Stream.fold Fold.findM
--   
findM :: Monad m => (a -> m Bool) -> SerialT m a -> m (Maybe a) -- | Like findM but with a non-monadic predicate. -- --
--   find p = findM (return . p)
--   find = Stream.fold Fold.find
--   
find :: Monad m => (a -> Bool) -> SerialT m a -> m (Maybe a) -- | In a stream of (key-value) pairs (a, b), return the value -- b of the first pair where the key equals the given value -- a. -- --
--   lookup = snd <$> Stream.find ((==) . fst)
--   lookup = Stream.fold Fold.lookup
--   
lookup :: (Monad m, Eq a) => a -> SerialT m (a, b) -> m (Maybe b) -- | Returns the first index that satisfies the given predicate. -- --
--   findIndex = Stream.fold Fold.findIndex
--   
findIndex :: Monad m => (a -> Bool) -> SerialT m a -> m (Maybe Int) -- | Returns the first index where a given value is found in the stream. -- --
--   elemIndex a = Stream.findIndex (== a)
--   
elemIndex :: (Monad m, Eq a) => a -> SerialT m a -> m (Maybe Int) -- | Determine whether the stream is empty. -- --
--   null = Stream.fold Fold.null
--   
null :: Monad m => SerialT m a -> m Bool -- | Determine whether an element is present in the stream. -- --
--   elem = Stream.fold Fold.elem
--   
elem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool -- | Determine whether an element is not present in the stream. -- --
--   notElem = Stream.fold Fold.length
--   
notElem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool -- | Determine whether all elements of a stream satisfy a predicate. -- --
--   all = Stream.fold Fold.all
--   
all :: Monad m => (a -> Bool) -> SerialT m a -> m Bool -- | Determine whether any of the elements of a stream satisfy a predicate. -- --
--   any = Stream.fold Fold.any
--   
any :: Monad m => (a -> Bool) -> SerialT m a -> m Bool -- | Determines if all elements of a boolean stream are True. -- --
--   and = Stream.fold Fold.and
--   
and :: Monad m => SerialT m Bool -> m Bool -- | Determines whether at least one element of a boolean stream is True. -- --
--   or = Stream.fold Fold.or
--   
or :: Monad m => SerialT m Bool -> m Bool -- |
--   toList = Stream.foldr (:) []
--   
-- -- Convert a stream into a list in the underlying monad. The list can be -- consumed lazily in a lazy monad (e.g. Identity). In a strict -- monad (e.g. IO) the whole list is generated and buffered before it can -- be consumed. -- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using Streamly.Array -- instead. toList :: Monad m => SerialT m a -> m [a] -- | Parallel fold application operator; applies a fold function t m a -- -> m b to a stream t m a concurrently; The the input -- stream is evaluated asynchronously in an independent thread yielding -- elements to a buffer and the folding action runs in another thread -- consuming the input from the buffer. -- -- If you read the signature as (t m a -> m b) -> (t m a -> -- m b) you can look at it as a transformation that converts a fold -- function to a buffered concurrent fold function. -- -- The . at the end of the operator is a mnemonic for -- termination of the stream. -- -- In the example below, each stage introduces a delay of 1 sec but -- output is printed every second because both stages are concurrent. -- --
--   >>> import Control.Concurrent (threadDelay)
--   
--   >>> import Streamly.Prelude ((|$.))
--   
--   >>> :{
--    Stream.foldlM' (\_ a -> threadDelay 1000000 >> print a) (return ())
--        |$. Stream.replicateM 3 (threadDelay 1000000 >> return 1)
--   :}
--   1
--   1
--   1
--   
-- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|$.) :: (IsStream t, MonadAsync m) => (t m a -> m b) -> t m a -> m b infixr 0 |$. -- | Same as |$. but with arguments reversed. -- --
--   (|&.) = flip (|$.)
--   
-- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|&.) :: (IsStream t, MonadAsync m) => t m a -> (t m a -> m b) -> m b infixl 1 |&. -- | Compare two streams for equality using an equality function. eqBy :: (IsStream t, Monad m) => (a -> b -> Bool) -> t m a -> t m b -> m Bool -- | Compare two streams lexicographically using a comparison function. cmpBy :: (IsStream t, Monad m) => (a -> b -> Ordering) -> t m a -> t m b -> m Ordering -- | Returns True if the first stream is the same as or a prefix of -- the second. A stream is a prefix of itself. -- --
--   >>> Stream.isPrefixOf (Stream.fromList "hello") (Stream.fromList "hello" :: SerialT IO Char)
--   True
--   
isPrefixOf :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m Bool -- | Returns True if all the elements of the first stream occur, in -- order, in the second stream. The elements do not have to occur -- consecutively. A stream is a subsequence of itself. -- --
--   >>> Stream.isSubsequenceOf (Stream.fromList "hlo") (Stream.fromList "hello" :: SerialT IO Char)
--   True
--   
isSubsequenceOf :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m Bool -- | stripPrefix prefix stream strips prefix from -- stream if it is a prefix of stream. Returns Nothing if -- the stream does not start with the given prefix, stripped stream -- otherwise. Returns Just nil when the prefix is the same as -- the stream. -- -- See also "Streamly.Internal.Data.Stream.IsStream.Nesting.dropPrefix". -- -- Space: O(1) stripPrefix :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m (Maybe (t m a)) -- |
--   map = fmap
--   
-- -- Same as fmap. -- --
--   > S.toList $ S.map (+1) $ S.fromList [1,2,3]
--   [2,3,4]
--   
map :: (IsStream t, Monad m) => (a -> b) -> t m a -> t m b -- |
--   sequence = mapM id
--   
-- -- Replace the elements of a stream of monadic actions with the outputs -- of those actions. -- --
--   >>> drain $ Stream.sequence $ Stream.fromList [putStr "a", putStr "b", putStrLn "c"]
--   abc
--   
--   >>> :{
--   drain $ Stream.replicateM 3 (return $ threadDelay 1000000 >> print 1)
--    & (fromSerial . Stream.sequence)
--   :}
--   1
--   1
--   1
--   
--   >>> :{
--   drain $ Stream.replicateM 3 (return $ threadDelay 1000000 >> print 1)
--    & (fromAsync . Stream.sequence)
--   :}
--   1
--   1
--   1
--   
-- -- Concurrent (do not use with fromParallel on infinite -- streams) sequence :: (IsStream t, MonadAsync m) => t m (m a) -> t m a -- |
--   mapM f = sequence . map f
--   
-- -- Apply a monadic function to each element of the stream and replace it -- with the output of the resulting action. -- --
--   >>> drain $ Stream.mapM putStr $ Stream.fromList ["a", "b", "c"]
--   abc
--   
--   >>> :{
--      drain $ Stream.replicateM 10 (return 1)
--        & (fromSerial . Stream.mapM (x -> threadDelay 1000000 >> print x))
--   :}
--   1
--   ...
--   1
--   
--   > drain $ Stream.replicateM 10 (return 1)
--    & (fromAsync . Stream.mapM (x -> threadDelay 1000000 >> print x))
--   
-- -- Concurrent (do not use with fromParallel on infinite -- streams) mapM :: forall t m a b. (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m b -- |
--   mapM_ = Stream.drain . Stream.mapM
--   
-- -- Apply a monadic action to each element of the stream and discard the -- output of the action. This is not really a pure transformation -- operation but a transformation followed by fold. mapM_ :: Monad m => (a -> m b) -> SerialT m a -> m () -- | Apply a monadic function to each element flowing through the stream -- and discard the results. -- --
--   >>> Stream.drain $ Stream.trace print (Stream.enumerateFromTo 1 2)
--   1
--   2
--   
-- -- Compare with tap. trace :: (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m a -- | Tap the data flowing through a stream into a Fold. For example, -- you may add a tap to log the contents flowing through the stream. The -- fold is used only for effects, its result is discarded. -- --
--                     Fold m a b
--                         |
--   -----stream m a ---------------stream m a-----
--   
-- --
--   >>> Stream.drain $ Stream.tap (Fold.drainBy print) (Stream.enumerateFromTo 1 2)
--   1
--   2
--   
-- -- Compare with trace. tap :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m a -- | Introduce a delay of specified seconds before consuming an element of -- the stream except the first one. -- --
--   >>> Stream.mapM_ print $ Stream.timestamped $ Stream.delay 1 $ Stream.enumerateFromTo 1 3
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),1)
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),2)
--   (AbsTime (TimeSpec {sec = ..., nsec = ...}),3)
--   
delay :: (IsStream t, MonadIO m) => Double -> t m a -> t m a -- | Strict left scan. Like map, scanl' too is a one to one -- transformation, however it adds an extra element. -- --
--   >>> Stream.toList $ Stream.scanl' (+) 0 $ fromList [1,2,3,4]
--   [0,1,3,6,10]
--   
-- --
--   >>> Stream.toList $ Stream.scanl' (flip (:)) [] $ Stream.fromList [1,2,3,4]
--   [[],[1],[2,1],[3,2,1],[4,3,2,1]]
--   
-- -- The output of scanl' is the initial value of the accumulator -- followed by all the intermediate steps and the final result of -- foldl'. -- -- By streaming the accumulated state after each fold step, we can share -- the state across multiple stages of stream composition. Each stage can -- modify or extend the state, do some processing with it and emit it for -- the next stage, thus modularizing the stream processing. This can be -- useful in stateful or event-driven programming. -- -- Consider the following monolithic example, computing the sum and the -- product of the elements in a stream in one go using a foldl': -- --
--   >>> Stream.foldl' ((s, p) x -> (s + x, p * x)) (0,1) $ Stream.fromList 1,2,3,4
--   
-- -- Using scanl' we can make it modular by computing the sum in -- the first stage and passing it down to the next stage for computing -- the product: -- --
--   >>> :{
--     Stream.foldl' ((_, p) (s, x) -> (s, p * x)) (0,1)
--     $ Stream.scanl' ((s, _) x -> (s + x, x)) (0,1)
--     $ Stream.fromList [1,2,3,4]
--   :}
--   (10,24)
--   
-- -- IMPORTANT: scanl' evaluates the accumulator to WHNF. To avoid -- building lazy expressions inside the accumulator, it is recommended -- that a strict data structure is used for accumulator. -- --
--   >>> scanl' f z xs = scanlM' (\a b -> return (f a b)) (return z) xs
--   
--   >>> scanl' f z xs = z `Stream.cons` postscanl' f z xs
--   
-- -- See also: usingStateT scanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b -- | Like scanl' but with a monadic step function and a monadic -- seed. -- -- Since: 0.4.0 -- -- Since: 0.8.0 (signature change) scanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> m b -> t m a -> t m b -- | Like scanl' but does not stream the initial value of the -- accumulator. -- --
--   >>> postscanl' f z = postscanlM' (\a b -> return (f a b)) (return z)
--   
--   >>> postscanl' f z xs = Stream.drop 1 $ Stream.scanl' f z xs
--   
postscanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b -- | Like postscanl' but with a monadic step function and a -- monadic seed. -- --
--   >>> postscanlM' f z xs = Stream.drop 1 $ Stream.scanlM' f z xs
--   
-- -- Since: 0.7.0 -- -- Since: 0.8.0 (signature change) postscanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> m b -> t m a -> t m b -- | Like scanl' but for a non-empty stream. The first element of -- the stream is used as the initial value of the accumulator. Does -- nothing if the stream is empty. -- --
--   >>> Stream.toList $ Stream.scanl1' (+) $ fromList [1,2,3,4]
--   [1,3,6,10]
--   
scanl1' :: (IsStream t, Monad m) => (a -> a -> a) -> t m a -> t m a -- | Like scanl1' but with a monadic step function. scanl1M' :: (IsStream t, Monad m) => (a -> a -> m a) -> t m a -> t m a -- | Scan a stream using the given monadic fold. -- --
--   >>> Stream.toList $ Stream.takeWhile (< 10) $ Stream.scan Fold.sum (Stream.fromList [1..10])
--   [0,1,3,6]
--   
scan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | Postscan a stream using the given monadic fold. -- -- The following example extracts the input stream up to a point where -- the running average of elements is no more than 10: -- --
--   >>> import Data.Maybe (fromJust)
--   
--   >>> let avg = Fold.teeWith (/) Fold.sum (fmap fromIntegral Fold.length)
--   
--   >>> :{
--    Stream.toList
--     $ Stream.map (fromJust . fst)
--     $ Stream.takeWhile (\(_,x) -> x <= 10)
--     $ Stream.postscan (Fold.tee Fold.last avg) (Stream.enumerateFromTo 1.0 100.0)
--   :}
--   [1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0,16.0,17.0,18.0,19.0]
--   
postscan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | Deletes the first occurrence of the element in the stream that -- satisfies the given equality predicate. -- --
--   >>> Stream.toList $ Stream.deleteBy (==) 3 $ Stream.fromList [1,3,3,5]
--   [1,3,5]
--   
deleteBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> a -> t m a -> t m a -- | Include only those elements that pass a predicate. filter :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a -- | Same as filter but with a monadic predicate. filterM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a -- | Drop repeated elements that are adjacent to each other. uniq :: (Eq a, IsStream t, Monad m) => t m a -> t m a -- | Take first n elements from the stream and discard the rest. take :: (IsStream t, Monad m) => Int -> t m a -> t m a -- | End the stream as soon as the predicate fails on an element. takeWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a -- | Same as takeWhile but with a monadic predicate. takeWhileM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a -- | Discard first n elements from the stream and take the rest. drop :: (IsStream t, Monad m) => Int -> t m a -> t m a -- | Drop elements in the stream as long as the predicate succeeds and then -- take the rest of the stream. dropWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a -- | Same as dropWhile but with a monadic predicate. dropWhileM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a -- | insertBy cmp elem stream inserts elem before the -- first element in stream that is less than elem when -- compared using cmp. -- --
--   insertBy cmp x = mergeBy cmp (fromPure x)
--   
-- --
--   >>> Stream.toList $ Stream.insertBy compare 2 $ Stream.fromList [1,3,5]
--   [1,2,3,5]
--   
insertBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> a -> t m a -> t m a -- | Insert an effect and its output before consuming an element of a -- stream except the first one. -- --
--   >>> Stream.toList $ Stream.trace putChar $ Stream.intersperseM (putChar '.' >> return ',') $ Stream.fromList "hello"
--   h.,e.,l.,l.,o"h,e,l,l,o"
--   
intersperseM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a -- | Insert a pure value between successive elements of a stream. -- --
--   >>> Stream.toList $ Stream.intersperse ',' $ Stream.fromList "hello"
--   "h,e,l,l,o"
--   
intersperse :: (IsStream t, MonadAsync m) => a -> t m a -> t m a -- | Returns the elements of the stream in reverse order. The stream must -- be finite. Note that this necessarily buffers the entire stream in -- memory. -- --
--   >>> reverse = Stream.foldlT (flip Stream.cons) Stream.nil
--   
-- -- Since 0.7.0 (Monad m constraint) -- -- Since: 0.1.1 reverse :: (IsStream t, Monad m) => t m a -> t m a -- |
--   indexed = Stream.postscanl' (\(i, _) x -> (i + 1, x)) (-1,undefined)
--   indexed = Stream.zipWith (,) (Stream.enumerateFrom 0)
--   
-- -- Pair each element in a stream with its index, starting from index 0. -- --
--   >>> Stream.toList $ Stream.indexed $ Stream.fromList "hello"
--   [(0,'h'),(1,'e'),(2,'l'),(3,'l'),(4,'o')]
--   
indexed :: (IsStream t, Monad m) => t m a -> t m (Int, a) -- |
--   indexedR n = Stream.postscanl' (\(i, _) x -> (i - 1, x)) (n + 1,undefined)
--   indexedR n = Stream.zipWith (,) (Stream.enumerateFromThen n (n - 1))
--   
-- -- Pair each element in a stream with its index, starting from the given -- index n and counting down. -- --
--   >>> Stream.toList $ Stream.indexedR 10 $ Stream.fromList "hello"
--   [(10,'h'),(9,'e'),(8,'l'),(7,'l'),(6,'o')]
--   
indexedR :: (IsStream t, Monad m) => Int -> t m a -> t m (Int, a) -- | Find all the indices where the element in the stream satisfies the -- given predicate. -- --
--   findIndices = fold Fold.findIndices
--   
findIndices :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m Int -- | Find all the indices where the value of the element in the stream is -- equal to the given value. -- --
--   elemIndices a = findIndices (== a)
--   
elemIndices :: (IsStream t, Eq a, Monad m) => a -> t m a -> t m Int -- | Map a Maybe returning function to a stream, filter out the -- Nothing elements, and return a stream of values extracted from -- Just. -- -- Equivalent to: -- --
--   mapMaybe f = Stream.map fromJust . Stream.filter isJust . Stream.map f
--   
mapMaybe :: (IsStream t, Monad m) => (a -> Maybe b) -> t m a -> t m b -- | Like mapMaybe but maps a monadic function. -- -- Equivalent to: -- --
--   mapMaybeM f = Stream.map fromJust . Stream.filter isJust . Stream.mapM f
--   
-- -- Concurrent (do not use with fromParallel on infinite -- streams) mapMaybeM :: (IsStream t, MonadAsync m, Functor (t m)) => (a -> m (Maybe b)) -> t m a -> t m b -- | Parallel transform application operator; applies a stream -- transformation function t m a -> t m b to a stream t m -- a concurrently; the input stream is evaluated asynchronously in -- an independent thread yielding elements to a buffer and the -- transformation function runs in another thread consuming the input -- from the buffer. |$ is just like regular function application -- operator $ except that it is concurrent. -- -- If you read the signature as (t m a -> t m b) -> (t m a -- -> t m b) you can look at it as a transformation that converts -- a transform function to a buffered concurrent transform function. -- -- The following code prints a value every second even though each stage -- adds a 1 second delay. -- --
--   >>> :{
--   Stream.drain $
--      Stream.mapM (\x -> threadDelay 1000000 >> print x)
--        |$ Stream.replicateM 3 (threadDelay 1000000 >> return 1)
--   :}
--   1
--   1
--   1
--   
-- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|$) :: (IsStream t, MonadAsync m) => (t m a -> t m b) -> t m a -> t m b infixr 0 |$ -- | Same as |$ but with arguments reversed. -- -- (|&) = flip (|$) -- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|&) :: (IsStream t, MonadAsync m) => t m a -> (t m a -> t m b) -> t m b infixl 1 |& -- | Make the stream producer and consumer run concurrently by introducing -- a buffer between them. The producer thread evaluates the input stream -- until the buffer fills, it terminates if the buffer is full and a -- worker thread is kicked off again to evaluate the remaining stream -- when there is space in the buffer. The consumer consumes the stream -- lazily from the buffer. -- -- Since: 0.2.0 (Streamly) mkAsync :: (IsStream t, MonadAsync m) => t m a -> t m a -- | Specify the maximum number of threads that can be spawned concurrently -- for any concurrent combinator in a stream. A value of 0 resets the -- thread limit to default, a negative value means there is no limit. The -- default value is 1500. maxThreads does not affect -- ParallelT streams as they can use unbounded number of -- threads. -- -- When the actions in a stream are IO bound, having blocking IO calls, -- this option can be used to control the maximum number of in-flight IO -- requests. When the actions are CPU bound this option can be used to -- control the amount of CPU used by the stream. -- -- Since: 0.4.0 (Streamly) maxThreads :: IsStream t => Int -> t m a -> t m a -- | Specify the maximum size of the buffer for storing the results from -- concurrent computations. If the buffer becomes full we stop spawning -- more concurrent tasks until there is space in the buffer. A value of 0 -- resets the buffer size to default, a negative value means there is no -- limit. The default value is 1500. -- -- CAUTION! using an unbounded maxBuffer value (i.e. a negative -- value) coupled with an unbounded maxThreads value is a recipe -- for disaster in presence of infinite streams, or very large streams. -- Especially, it must not be used when pure is used in -- ZipAsyncM streams as pure in applicative zip streams -- generates an infinite stream causing unbounded concurrent generation -- with no limit on the buffer or threads. -- -- Since: 0.4.0 (Streamly) maxBuffer :: IsStream t => Int -> t m a -> t m a -- | Specifies the stream yield rate in yields per second (Hertz). -- We keep accumulating yield credits at rateGoal. At any point of -- time we allow only as many yields as we have accumulated as per -- rateGoal since the start of time. If the consumer or the -- producer is slower or faster, the actual rate may fall behind or -- exceed rateGoal. We try to recover the gap between the two by -- increasing or decreasing the pull rate from the producer. However, if -- the gap becomes more than rateBuffer we try to recover only as -- much as rateBuffer. -- -- rateLow puts a bound on how low the instantaneous rate can go -- when recovering the rate gap. In other words, it determines the -- maximum yield latency. Similarly, rateHigh puts a bound on how -- high the instantaneous rate can go when recovering the rate gap. In -- other words, it determines the minimum yield latency. We reduce the -- latency by increasing concurrency, therefore we can say that it puts -- an upper bound on concurrency. -- -- If the rateGoal is 0 or negative the stream never yields a -- value. If the rateBuffer is 0 or negative we do not attempt to -- recover. -- -- Since: 0.5.0 (Streamly) data Rate Rate :: Double -> Double -> Double -> Int -> Rate -- | The lower rate limit [rateLow] :: Rate -> Double -- | The target rate we want to achieve [rateGoal] :: Rate -> Double -- | The upper rate limit [rateHigh] :: Rate -> Double -- | Maximum slack from the goal [rateBuffer] :: Rate -> Int -- | Specify the pull rate of a stream. A Nothing value resets the -- rate to default which is unlimited. When the rate is specified, -- concurrent production may be ramped up or down automatically to -- achieve the specified yield rate. The specific behavior for different -- styles of Rate specifications is documented under Rate. -- The effective maximum production rate achieved by a stream is governed -- by: -- -- -- -- Since: 0.5.0 (Streamly) rate :: IsStream t => Maybe Rate -> t m a -> t m a -- | Same as rate (Just $ Rate (r/2) r (2*r) maxBound) -- -- Specifies the average production rate of a stream in number of yields -- per second (i.e. Hertz). Concurrent production is ramped up -- or down automatically to achieve the specified average yield rate. The -- rate can go down to half of the specified rate on the lower side and -- double of the specified rate on the higher side. -- -- Since: 0.5.0 (Streamly) avgRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate r r (2*r) maxBound) -- -- Specifies the minimum rate at which the stream should yield values. As -- far as possible the yield rate would never be allowed to go below the -- specified rate, even though it may possibly go above it at times, the -- upper limit is double of the specified rate. -- -- Since: 0.5.0 (Streamly) minRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate (r/2) r r maxBound) -- -- Specifies the maximum rate at which the stream should yield values. As -- far as possible the yield rate would never be allowed to go above the -- specified rate, even though it may possibly go below it at times, the -- lower limit is half of the specified rate. This can be useful in -- applications where certain resource usage must not be allowed to go -- beyond certain limits. -- -- Since: 0.5.0 (Streamly) maxRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate r r r 0) -- -- Specifies a constant yield rate. If for some reason the actual rate -- goes above or below the specified rate we do not try to recover it by -- increasing or decreasing the rate in future. This can be useful in -- applications like graphics frame refresh where we need to maintain a -- constant refresh rate. -- -- Since: 0.5.0 (Streamly) constRate :: IsStream t => Double -> t m a -> t m a -- | Appends two streams sequentially, yielding all elements from the first -- stream, and then all elements from the second stream. -- --
--   >>> import Streamly.Prelude (serial)
--   
--   >>> stream1 = Stream.fromList [1,2]
--   
--   >>> stream2 = Stream.fromList [3,4]
--   
--   >>> Stream.toList $ stream1 `serial` stream2
--   [1,2,3,4]
--   
-- -- This operation can be used to fold an infinite lazy container of -- streams. -- -- Since: 0.2.0 (Streamly) serial :: IsStream t => t m a -> t m a -> t m a infixr 6 `serial` -- | Interleaves two streams, yielding one element from each stream -- alternately. When one stream stops the rest of the other stream is -- used in the output stream. -- --
--   >>> import Streamly.Prelude (wSerial)
--   
--   >>> stream1 = Stream.fromList [1,2]
--   
--   >>> stream2 = Stream.fromList [3,4]
--   
--   >>> Stream.toList $ Stream.fromWSerial $ stream1 `wSerial` stream2
--   [1,3,2,4]
--   
-- -- Note, for singleton streams wSerial and serial are -- identical. -- -- Note that this operation cannot be used to fold a container of -- infinite streams but it can be used for very large streams as the -- state that it needs to maintain is proportional to the logarithm of -- the number of streams. -- -- Since: 0.2.0 (Streamly) wSerial :: IsStream t => t m a -> t m a -> t m a infixr 6 `wSerial` -- | Appends two streams, both the streams may be evaluated concurrently -- but the outputs are used in the same order as the corresponding -- actions in the original streams, side effects will happen in the order -- in which the streams are evaluated: -- --
--   >>> import Streamly.Prelude (ahead, SerialT)
--   
--   >>> stream1 = Stream.fromEffect (delay 4) :: SerialT IO Int
--   
--   >>> stream2 = Stream.fromEffect (delay 2) :: SerialT IO Int
--   
--   >>> Stream.toList $ stream1 `ahead` stream2 :: IO [Int]
--   2 sec
--   4 sec
--   [4,2]
--   
-- -- Multiple streams can be combined. With enough threads, all of them can -- be scheduled simultaneously: -- --
--   >>> stream3 = Stream.fromEffect (delay 1)
--   
--   >>> Stream.toList $ stream1 `ahead` stream2 `ahead` stream3
--   1 sec
--   2 sec
--   4 sec
--   [4,2,1]
--   
-- -- With 2 threads, only two can be scheduled at a time, when one of those -- finishes, the third one gets scheduled: -- --
--   >>> Stream.toList $ Stream.maxThreads 2 $ stream1 `ahead` stream2 `ahead` stream3
--   2 sec
--   1 sec
--   4 sec
--   [4,2,1]
--   
-- -- Only streams are scheduled for ahead evaluation, how actions within a -- stream are evaluated depends on the stream type. If it is a concurrent -- stream they will be evaluated concurrently. It may not make much sense -- combining serial streams using ahead. -- -- ahead can be safely used to fold an infinite lazy container of -- streams. -- -- Since: 0.3.0 (Streamly) ahead :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `ahead` -- | Merges two streams, both the streams may be evaluated concurrently, -- outputs from both are used as they arrive: -- --
--   >>> import Streamly.Prelude (async)
--   
--   >>> stream1 = Stream.fromEffect (delay 4)
--   
--   >>> stream2 = Stream.fromEffect (delay 2)
--   
--   >>> Stream.toList $ stream1 `async` stream2
--   2 sec
--   4 sec
--   [2,4]
--   
-- -- Multiple streams can be combined. With enough threads, all of them can -- be scheduled simultaneously: -- --
--   >>> stream3 = Stream.fromEffect (delay 1)
--   
--   >>> Stream.toList $ stream1 `async` stream2 `async` stream3
--   ...
--   [1,2,4]
--   
-- -- With 2 threads, only two can be scheduled at a time, when one of those -- finishes, the third one gets scheduled: -- --
--   >>> Stream.toList $ Stream.maxThreads 2 $ stream1 `async` stream2 `async` stream3
--   ...
--   [2,1,4]
--   
-- -- With a single thread, it becomes serial: -- --
--   >>> Stream.toList $ Stream.maxThreads 1 $ stream1 `async` stream2 `async` stream3
--   ...
--   [4,2,1]
--   
-- -- Only streams are scheduled for async evaluation, how actions within a -- stream are evaluated depends on the stream type. If it is a concurrent -- stream they will be evaluated concurrently. -- -- In the following example, both the streams are scheduled for -- concurrent evaluation but each individual stream is evaluated -- serially: -- --
--   >>> stream1 = Stream.fromListM $ Prelude.map delay [3,3] -- SerialT IO Int
--   
--   >>> stream2 = Stream.fromListM $ Prelude.map delay [1,1] -- SerialT IO Int
--   
--   >>> Stream.toList $ stream1 `async` stream2 -- IO [Int]
--   ...
--   [1,1,3,3]
--   
-- -- If total threads are 2, the third stream is scheduled only after one -- of the first two has finished: -- --
--   stream3 = Stream.fromListM $ Prelude.map delay [2,2] -- SerialT IO Int
--   Stream.toList $ Stream.maxThreads 2 $ stream1 `async` stream2 `async` stream3 -- IO [Int]
--   
-- -- ... [1,1,3,2,3,2] -- -- Thus async goes deep in first few streams rather than going -- wide in all streams. It prefers to evaluate the leftmost streams as -- much as possible. Because of this behavior, async can be safely -- used to fold an infinite lazy container of streams. -- -- Since: 0.2.0 (Streamly) async :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `async` -- | For singleton streams, wAsync is the same as async. See -- async for singleton stream behavior. For multi-element streams, -- while async is left biased i.e. it tries to evaluate the left -- side stream as much as possible, wAsync tries to schedule them -- both fairly. In other words, async goes deep while -- wAsync goes wide. However, outputs are always used as they -- arrive. -- -- With a single thread, async starts behaving like serial -- while wAsync starts behaving like wSerial. -- --
--   >>> import Streamly.Prelude (async, wAsync)
--   
--   >>> stream1 = Stream.fromList [1,2,3]
--   
--   >>> stream2 = Stream.fromList [4,5,6]
--   
--   >>> Stream.toList $ Stream.fromAsync $ Stream.maxThreads 1 $ stream1 `async` stream2
--   [1,2,3,4,5,6]
--   
-- --
--   >>> Stream.toList $ Stream.fromWAsync $ Stream.maxThreads 1 $ stream1 `wAsync` stream2
--   [1,4,2,5,3,6]
--   
-- -- With two threads available, and combining three streams: -- --
--   >>> stream3 = Stream.fromList [7,8,9]
--   
--   >>> Stream.toList $ Stream.fromAsync $ Stream.maxThreads 2 $ stream1 `async` stream2 `async` stream3
--   [1,2,3,4,5,6,7,8,9]
--   
-- --
--   >>> Stream.toList $ Stream.fromWAsync $ Stream.maxThreads 2 $ stream1 `wAsync` stream2 `wAsync` stream3
--   [1,4,2,7,5,3,8,6,9]
--   
-- -- This operation cannot be used to fold an infinite lazy container of -- streams, because it schedules all the streams in a round robin manner. -- -- Note that WSerialT and single threaded WAsyncT both -- interleave streams but the exact scheduling is slightly different in -- both cases. -- -- Since: 0.2.0 (Streamly) wAsync :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `wAsync` -- | Like async except that the execution is much more strict. There -- is no limit on the number of threads. While async may not -- schedule a stream if there is no demand from the consumer, -- parallel always evaluates both the streams immediately. The -- only limit that applies to parallel is maxBuffer. -- Evaluation may block if the output buffer becomes full. -- --
--   >>> import Streamly.Prelude (parallel)
--   
--   >>> stream = Stream.fromEffect (delay 2) `parallel` Stream.fromEffect (delay 1)
--   
--   >>> Stream.toList stream -- IO [Int]
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- parallel guarantees that all the streams are scheduled for -- execution immediately, therefore, we could use things like starting -- timers inside the streams and relying on the fact that all timers were -- started at the same time. -- -- Unlike async this operation cannot be used to fold an infinite -- lazy container of streams, because it schedules all the streams -- strictly concurrently. -- -- Since: 0.2.0 (Streamly) parallel :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `parallel` -- | Merge two streams using a comparison function. The head elements of -- both the streams are compared and the smaller of the two elements is -- emitted, if both elements are equal then the element from the first -- stream is used first. -- -- If the streams are sorted in ascending order, the resulting stream -- would also remain sorted in ascending order. -- --
--   >>> Stream.toList $ Stream.mergeBy compare (Stream.fromList [1,3,5]) (Stream.fromList [2,4,6,8])
--   [1,2,3,4,5,6,8]
--   
-- -- See also: mergeByMFused mergeBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> t m a -> t m a -> t m a -- | Like mergeBy but with a monadic comparison function. -- -- Merge two streams randomly: -- --
--   > randomly _ _ = randomIO >>= x -> return $ if x then LT else GT
--   > Stream.toList $ Stream.mergeByM randomly (Stream.fromList [1,1,1,1]) (Stream.fromList [2,2,2,2])
--   [2,1,2,2,2,1,1,1]
--   
-- -- Merge two streams in a proportion of 2:1: -- --
--   >>> :{
--   do
--    let proportionately m n = do
--         ref <- newIORef $ cycle $ Prelude.concat [Prelude.replicate m LT, Prelude.replicate n GT]
--         return $ _ _ -> do
--            r <- readIORef ref
--            writeIORef ref $ Prelude.tail r
--            return $ Prelude.head r
--    f <- proportionately 2 1
--    xs <- Stream.toList $ Stream.mergeByM f (Stream.fromList [1,1,1,1,1,1]) (Stream.fromList [2,2,2])
--    print xs
--   :}
--   [1,1,2,1,1,2,1,1,2]
--   
-- -- See also: mergeByMFused mergeByM :: (IsStream t, Monad m) => (a -> a -> m Ordering) -> t m a -> t m a -> t m a -- | Like mergeBy but merges concurrently (i.e. both the elements -- being merged are generated concurrently). mergeAsyncBy :: (IsStream t, MonadAsync m) => (a -> a -> Ordering) -> t m a -> t m a -> t m a -- | Like mergeByM but merges concurrently (i.e. both the elements -- being merged are generated concurrently). mergeAsyncByM :: (IsStream t, MonadAsync m) => (a -> a -> m Ordering) -> t m a -> t m a -> t m a -- | Stream a is evaluated first, followed by stream b, -- the resulting elements a and b are then zipped using -- the supplied zip function and the result c is yielded to the -- consumer. -- -- If stream a or stream b ends, the zipped stream -- ends. If stream b ends first, the element a from -- previous evaluation of stream a is discarded. -- --
--   > S.toList $ S.zipWith (+) (S.fromList [1,2,3]) (S.fromList [4,5,6])
--   [5,7,9]
--   
zipWith :: (IsStream t, Monad m) => (a -> b -> c) -> t m a -> t m b -> t m c -- | Like zipWith but using a monadic zipping function. zipWithM :: (IsStream t, Monad m) => (a -> b -> m c) -> t m a -> t m b -> t m c -- | Like zipWith but zips concurrently i.e. both the streams being -- zipped are evaluated concurrently using the ParallelT -- concurrent evaluation style. The maximum number of elements of each -- stream evaluated in advance can be controlled by maxBuffer. -- -- The stream ends if stream a or stream b ends. -- However, if stream b ends while we are still evaluating -- stream a and waiting for a result then stream will not end -- until after the evaluation of stream a finishes. This -- behavior can potentially be changed in future to end the stream -- immediately as soon as any of the stream end is detected. zipAsyncWith :: (IsStream t, MonadAsync m) => (a -> b -> c) -> t m a -> t m b -> t m c -- | Like zipAsyncWith but with a monadic zipping function. zipAsyncWithM :: (IsStream t, MonadAsync m) => (a -> b -> m c) -> t m a -> t m b -> t m c -- | Like concatMap but uses an Unfold for stream generation. -- Unlike concatMap this can fuse the Unfold code with the -- inner loop and therefore provide many times better performance. unfoldMany :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b -- | intersperse followed by unfold and concat. -- --
--   intercalate unf a str = unfoldMany unf $ intersperse a str
--   intersperse = intercalate (Unfold.function id)
--   unwords = intercalate Unfold.fromList " "
--   
-- --
--   >>> Stream.toList $ Stream.intercalate Unfold.fromList " " $ Stream.fromList ["abc", "def", "ghi"]
--   "abc def ghi"
--   
intercalate :: (IsStream t, Monad m) => Unfold m b c -> b -> t m b -> t m c -- | intersperseSuffix followed by unfold and concat. -- --
--   intercalateSuffix unf a str = unfoldMany unf $ intersperseSuffix a str
--   intersperseSuffix = intercalateSuffix (Unfold.function id)
--   unlines = intercalateSuffix Unfold.fromList "\n"
--   
-- --
--   >>> Stream.toList $ Stream.intercalateSuffix Unfold.fromList "\n" $ Stream.fromList ["abc", "def", "ghi"]
--   "abc\ndef\nghi\n"
--   
intercalateSuffix :: (IsStream t, Monad m) => Unfold m b c -> b -> t m b -> t m c -- | concatMapWith mixer generator stream is a two dimensional -- looping combinator. The generator function is used to -- generate streams from the elements in the input stream and -- the mixer function is used to merge those streams. -- -- Note we can merge streams concurrently by using a concurrent merge -- function. -- -- Since: 0.7.0 -- -- Since: 0.8.0 (signature change) concatMapWith :: IsStream t => (t m b -> t m b -> t m b) -> (a -> t m b) -> t m a -> t m b -- | Map a stream producing function on each element of the stream and then -- flatten the results into a single stream. -- --
--   >>> concatMap f = Stream.concatMapM (return . f)
--   
--   >>> concatMap f = Stream.concatMapWith Stream.serial f
--   
--   >>> concatMap f = Stream.concat . Stream.map f
--   
--   >>> concatMap f = Stream.unfoldMany (Unfold.lmap f Unfold.fromStream)
--   
concatMap :: (IsStream t, Monad m) => (a -> t m b) -> t m a -> t m b -- | Map a stream producing monadic function on each element of the stream -- and then flatten the results into a single stream. Since the stream -- generation function is monadic, unlike concatMap, it can -- produce an effect at the beginning of each iteration of the inner -- loop. concatMapM :: (IsStream t, Monad m) => (a -> m (t m b)) -> t m a -> t m b -- | A variant of fold that allows you to fold a Foldable -- container of streams using the specified stream sum operation. -- --
--   concatFoldableWith async $ map return [1..3]
--   
-- -- Equivalent to: -- --
--   concatFoldableWith f = Prelude.foldr f S.nil
--   concatFoldableWith f = S.concatMapFoldableWith f id
--   
-- -- Since: 0.8.0 (Renamed foldWith to concatFoldableWith) -- -- Since: 0.1.0 (Streamly) concatFoldableWith :: (IsStream t, Foldable f) => (t m a -> t m a -> t m a) -> f (t m a) -> t m a -- | A variant of foldMap that allows you to map a monadic streaming -- action on a Foldable container and then fold it using the -- specified stream merge operation. -- --
--   concatMapFoldableWith async return [1..3]
--   
-- -- Equivalent to: -- --
--   concatMapFoldableWith f g = Prelude.foldr (f . g) S.nil
--   concatMapFoldableWith f g xs = S.concatMapWith f g (S.fromFoldable xs)
--   
-- -- Since: 0.8.0 (Renamed foldMapWith to concatMapFoldableWith) -- -- Since: 0.1.0 (Streamly) concatMapFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b -- | Like concatMapFoldableWith but with the last two arguments -- reversed i.e. the monadic streaming function is the last argument. -- -- Equivalent to: -- --
--   concatForFoldableWith f xs g = Prelude.foldr (f . g) S.nil xs
--   concatForFoldableWith f = flip (S.concatMapFoldableWith f)
--   
-- -- Since: 0.8.0 (Renamed forEachWith to concatForFoldableWith) -- -- Since: 0.1.0 (Streamly) concatForFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b -- | Apply a Fold repeatedly on a stream and emit the fold outputs -- in the output stream. -- -- To sum every two contiguous elements in a stream: -- --
--   >>> f = Fold.take 2 Fold.sum
--   
--   >>> Stream.toList $ Stream.foldMany f $ Stream.fromList [1..10]
--   [3,7,11,15,19]
--   
-- -- On an empty stream the output is empty: -- --
--   >>> Stream.toList $ Stream.foldMany f $ Stream.fromList []
--   []
--   
-- -- Note Stream.foldMany (Fold.take 0) would result in an -- infinite loop in a non-empty stream. foldMany :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | Group the input stream into groups of n elements each and -- then fold each group using the provided fold function. -- --
--   >>> Stream.toList $ Stream.chunksOf 2 Fold.sum (Stream.enumerateFromTo 1 10)
--   [3,7,11,15,19]
--   
-- -- This can be considered as an n-fold version of take where we -- apply take repeatedly on the leftover stream until the stream -- exhausts. -- --
--   chunksOf n f = foldMany (FL.take n f)
--   
chunksOf :: (IsStream t, Monad m) => Int -> Fold m a b -> t m a -> t m b -- | Group the input stream into windows of n second each and then -- fold each group using the provided fold function. -- --
--   >>> Stream.toList $ Stream.take 5 $ Stream.intervalsOf 1 Fold.sum $ Stream.constRate 2 $ Stream.enumerateFrom 1
--   [...,...,...,...,...]
--   
intervalsOf :: (IsStream t, MonadAsync m) => Double -> Fold m a b -> t m a -> t m b -- | Split on an infixed separator element, dropping the separator. The -- supplied Fold is applied on the split segments. Splits the -- stream on separator elements determined by the supplied predicate, -- separator is considered as infixed between two segments: -- --
--   >>> splitOn' p xs = Stream.toList $ Stream.splitOn p Fold.toList (Stream.fromList xs)
--   
--   >>> splitOn' (== '.') "a.b"
--   ["a","b"]
--   
-- -- An empty stream is folded to the default value of the fold: -- --
--   >>> splitOn' (== '.') ""
--   [""]
--   
-- -- If one or both sides of the separator are missing then the empty -- segment on that side is folded to the default output of the fold: -- --
--   >>> splitOn' (== '.') "."
--   ["",""]
--   
-- --
--   >>> splitOn' (== '.') ".a"
--   ["","a"]
--   
-- --
--   >>> splitOn' (== '.') "a."
--   ["a",""]
--   
-- --
--   >>> splitOn' (== '.') "a..b"
--   ["a","","b"]
--   
-- -- splitOn is an inverse of intercalating single element: -- --
--   Stream.intercalate (Stream.fromPure '.') Unfold.fromList . Stream.splitOn (== '.') Fold.toList === id
--   
-- -- Assuming the input stream does not contain the separator: -- --
--   Stream.splitOn (== '.') Fold.toList . Stream.intercalate (Stream.fromPure '.') Unfold.fromList === id
--   
splitOn :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b -- | Split on a suffixed separator element, dropping the separator. The -- supplied Fold is applied on the split segments. -- --
--   >>> splitOnSuffix' p xs = Stream.toList $ Stream.splitOnSuffix p Fold.toList (Stream.fromList xs)
--   
--   >>> splitOnSuffix' (== '.') "a.b."
--   ["a","b"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a."
--   ["a"]
--   
-- -- An empty stream results in an empty output stream: -- --
--   >>> splitOnSuffix' (== '.') ""
--   []
--   
-- -- An empty segment consisting of only a suffix is folded to the default -- output of the fold: -- --
--   >>> splitOnSuffix' (== '.') "."
--   [""]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a..b.."
--   ["a","","b",""]
--   
-- -- A suffix is optional at the end of the stream: -- --
--   >>> splitOnSuffix' (== '.') "a"
--   ["a"]
--   
-- --
--   >>> splitOnSuffix' (== '.') ".a"
--   ["","a"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a.b"
--   ["a","b"]
--   
-- --
--   lines = splitOnSuffix (== '\n')
--   
-- -- splitOnSuffix is an inverse of intercalateSuffix with -- a single element: -- --
--   Stream.intercalateSuffix (Stream.fromPure '.') Unfold.fromList . Stream.splitOnSuffix (== '.') Fold.toList === id
--   
-- -- Assuming the input stream does not contain the separator: -- --
--   Stream.splitOnSuffix (== '.') Fold.toList . Stream.intercalateSuffix (Stream.fromPure '.') Unfold.fromList === id
--   
splitOnSuffix :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b -- | Like splitOnSuffix but keeps the suffix attached to the -- resulting splits. -- --
--   >>> splitWithSuffix' p xs = Stream.toList $ splitWithSuffix p Fold.toList (Stream.fromList xs)
--   
-- --
--   >>> splitWithSuffix' (== '.') ""
--   []
--   
-- --
--   >>> splitWithSuffix' (== '.') "."
--   ["."]
--   
-- --
--   >>> splitWithSuffix' (== '.') "a"
--   ["a"]
--   
-- --
--   >>> splitWithSuffix' (== '.') ".a"
--   [".","a"]
--   
-- --
--   >>> splitWithSuffix' (== '.') "a."
--   ["a."]
--   
-- --
--   >>> splitWithSuffix' (== '.') "a.b"
--   ["a.","b"]
--   
-- --
--   >>> splitWithSuffix' (== '.') "a.b."
--   ["a.","b."]
--   
-- --
--   >>> splitWithSuffix' (== '.') "a..b.."
--   ["a.",".","b.","."]
--   
splitWithSuffix :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b -- | Like splitOn after stripping leading, trailing, and repeated -- separators. Therefore, ".a..b." with . as the -- separator would be parsed as ["a","b"]. In other words, its -- like parsing words from whitespace separated text. -- --
--   >>> wordsBy' p xs = Stream.toList $ Stream.wordsBy p Fold.toList (Stream.fromList xs)
--   
-- --
--   >>> wordsBy' (== ',') ""
--   []
--   
-- --
--   >>> wordsBy' (== ',') ","
--   []
--   
-- --
--   >>> wordsBy' (== ',') ",a,,b,"
--   ["a","b"]
--   
-- --
--   words = wordsBy isSpace
--   
wordsBy :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b -- |
--   groups = groupsBy (==)
--   groups = groupsByRolling (==)
--   
-- -- Groups contiguous spans of equal elements together in individual -- groups. -- --
--   >>> Stream.toList $ Stream.groups Fold.toList $ Stream.fromList [1,1,2,2]
--   [[1,1],[2,2]]
--   
groups :: (IsStream t, Monad m, Eq a) => Fold m a b -> t m a -> t m b -- | groupsBy cmp f $ S.fromList [a,b,c,...] assigns the element -- a to the first group, if b `cmp` a is True -- then b is also assigned to the same group. If c `cmp` -- a is True then c is also assigned to the same -- group and so on. When the comparison fails a new group is started. -- Each group is folded using the fold f and the result of the -- fold is emitted in the output stream. -- --
--   >>> Stream.toList $ Stream.groupsBy (>) Fold.toList $ Stream.fromList [1,3,7,0,2,5]
--   [[1,3,7],[0,2,5]]
--   
groupsBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> Fold m a b -> t m a -> t m b -- | Unlike groupsBy this function performs a rolling comparison -- of two successive elements in the input stream. groupsByRolling -- cmp f $ S.fromList [a,b,c,...] assigns the element a to -- the first group, if a `cmp` b is True then b -- is also assigned to the same group. If b `cmp` c is -- True then c is also assigned to the same group and so -- on. When the comparison fails a new group is started. Each group is -- folded using the fold f. -- --
--   >>> Stream.toList $ Stream.groupsByRolling (\a b -> a + 1 == b) Fold.toList $ Stream.fromList [1,2,3,7,8,9]
--   [[1,2,3],[7,8,9]]
--   
groupsByRolling :: (IsStream t, Monad m) => (a -> a -> Bool) -> Fold m a b -> t m a -> t m b -- | Run the action m b before the stream yields its first -- element. -- -- Same as the following but more efficient due to fusion: -- --
--   >>> before action xs = Stream.nilM action <> xs
--   
--   >>> before action xs = Stream.concatMap (const xs) (Stream.fromEffect action)
--   
before :: (IsStream t, Monad m) => m b -> t m a -> t m a -- | Run the action m b whenever the stream t m a stops -- normally, or if it is garbage collected after a partial lazy -- evaluation. -- -- The semantics of the action m b are similar to the semantics -- of cleanup action in bracket. -- -- See also after_ after :: (IsStream t, MonadIO m, MonadBaseControl IO m) => m b -> t m a -> t m a -- | Run the alloc action m b with async exceptions disabled but -- keeping blocking operations interruptible (see mask). Use the -- output b as input to b -> t m a to generate an -- output stream. -- -- b is usually a resource under the state of monad m, -- e.g. a file handle, that requires a cleanup after use. The cleanup -- action b -> m c, runs whenever the stream ends normally, -- due to a sync or async exception or if it gets garbage collected after -- a partial lazy evaluation. -- -- bracket only guarantees that the cleanup action runs, and it -- runs with async exceptions enabled. The action must ensure that it can -- successfully cleanup the resource in the face of sync or async -- exceptions. -- -- When the stream ends normally or on a sync exception, cleanup action -- runs immediately in the current thread context, whereas in other cases -- it runs in the GC context, therefore, cleanup may be delayed until the -- GC gets to run. -- -- See also: bracket_ -- -- Inhibits stream fusion bracket :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a -- | Run the action m b if the stream aborts due to an exception. -- The exception is not caught, simply rethrown. -- -- Inhibits stream fusion onException :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a -- | Run the action m b whenever the stream t m a stops -- normally, aborts due to an exception or if it is garbage collected -- after a partial lazy evaluation. -- -- The semantics of running the action m b are similar to the -- cleanup action semantics described in bracket. -- --
--   finally release = bracket (return ()) (const release)
--   
-- -- See also finally_ -- -- Inhibits stream fusion finally :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> t m a -> t m a -- | When evaluating a stream if an exception occurs, stream evaluation -- aborts and the specified exception handler is run with the exception -- as argument. -- -- Inhibits stream fusion handle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a) -> t m a -> t m a -- | Lift the inner monad m of a stream t m a to tr -- m using the monad transformer tr. liftInner :: (Monad m, IsStream t, MonadTrans tr, Monad (tr m)) => t m a -> t (tr m) a -- | Evaluate the inner monad of a stream as ReaderT. runReaderT :: (IsStream t, Monad m) => m s -> t (ReaderT s m) a -> t m a -- | Evaluate the inner monad of a stream as StateT and emit the -- resulting state and value pair after each step. -- -- This is supported only for SerialT as concurrent state updation -- may not be safe. runStateT :: Monad m => m s -> SerialT (StateT s m) a -> SerialT m (s, a) -- | For SerialT streams: -- --
--   (<>) = serial                       -- Semigroup
--   (>>=) = flip . concatMapWith serial -- Monad
--   
-- -- A single Monad bind behaves like a for loop: -- --
--   >>> :{
--   Stream.toList $ do
--        x <- Stream.fromList [1,2] -- foreach x in stream
--        return x
--   :}
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops: -- --
--   >>> :{
--   Stream.toList $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [3,4] -- foreach y in stream
--       return (x, y)
--   :}
--   [(1,3),(1,4),(2,3),(2,4)]
--   
-- -- Since: 0.2.0 (Streamly) data SerialT m a -- | For WSerialT streams: -- --
--   (<>) = wSerial                       -- Semigroup
--   (>>=) = flip . concatMapWith wSerial -- Monad
--   
-- -- Note that <> is associative only if we disregard the -- ordering of elements in the resulting stream. -- -- A single Monad bind behaves like a for loop: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWSerial $ do
--        x <- Stream.fromList [1,2] -- foreach x in stream
--        return x
--   :}
--   [1,2]
--   
-- -- Nested monad binds behave like interleaved nested for loops: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWSerial $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [3,4] -- foreach y in stream
--       return (x, y)
--   :}
--   [(1,3),(2,3),(1,4),(2,4)]
--   
-- -- It is a result of interleaving all the nested iterations corresponding -- to element 1 in the first stream with all the nested -- iterations of element 2: -- --
--   >>> import Streamly.Prelude (wSerial)
--   
--   >>> Stream.toList $ Stream.fromList [(1,3),(1,4)] `Stream.wSerial` Stream.fromList [(2,3),(2,4)]
--   [(1,3),(2,3),(1,4),(2,4)]
--   
-- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- SerialT. -- -- Since: 0.2.0 (Streamly) data WSerialT m a -- | For AheadT streams: -- --
--   (<>) = ahead
--   (>>=) = flip . concatMapWith ahead
--   
-- -- A single Monad bind behaves like a for loop with -- iterations executed concurrently, ahead of time, producing side -- effects of iterations out of order, but results in order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAhead $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [2,1]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, ahead of time: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAhead $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,5,4,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one output stream and all the iterations corresponding to 2 -- constitute another output stream and these two output streams are -- merged using ahead. -- -- Since: 0.3.0 (Streamly) data AheadT m a -- | For AsyncT streams: -- --
--   (<>) = async
--   (>>=) = flip . concatMapWith async
--   
-- -- A single Monad bind behaves like a for loop with -- iterations of the loop executed concurrently a la the async -- combinator, producing results and side effects of iterations out of -- order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAsync $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, a la the async combinator: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAsync $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,4,5,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one output stream and all the iterations corresponding to 2 -- constitute another output stream and these two output streams are -- merged using async. -- -- Since: 0.1.0 (Streamly) data AsyncT m a -- | For WAsyncT streams: -- --
--   (<>) = wAsync
--   (>>=) = flip . concatMapWith wAsync
--   
-- -- A single Monad bind behaves like a for loop with -- iterations of the loop executed concurrently a la the wAsync -- combinator, producing results and side effects of iterations out of -- order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWAsync $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, a la the wAsync combinator: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWAsync $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,4,5,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one WAsyncT output stream and all the iterations corresponding -- to 2 constitute another WAsyncT output stream and -- these two output streams are merged using wAsync. -- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- AsyncT. -- -- Since: 0.2.0 (Streamly) data WAsyncT m a -- | For ParallelT streams: -- --
--   (<>) = parallel
--   (>>=) = flip . concatMapWith parallel
--   
-- -- See AsyncT, ParallelT is similar except that all -- iterations are strictly concurrent while in AsyncT it depends -- on the consumer demand and available threads. See parallel -- for more details. -- -- Since: 0.1.0 (Streamly) -- -- Since: 0.7.0 (maxBuffer applies to ParallelT streams) data ParallelT m a -- | For ZipSerialM streams: -- --
--   (<>) = serial
--   (*) = 'Streamly.Prelude.serial.zipWith' id
--   
-- -- Applicative evaluates the streams being zipped serially: -- --
--   >>> s1 = Stream.fromFoldable [1, 2]
--   
--   >>> s2 = Stream.fromFoldable [3, 4]
--   
--   >>> s3 = Stream.fromFoldable [5, 6]
--   
--   >>> Stream.toList $ Stream.fromZipSerial $ (,,) <$> s1 <*> s2 <*> s3
--   [(1,3,5),(2,4,6)]
--   
-- -- Since: 0.2.0 (Streamly) data ZipSerialM m a -- | For ZipAsyncM streams: -- --
--   (<>) = serial
--   (*) = 'Streamly.Prelude.serial.zipAsyncWith' id
--   
-- -- Applicative evaluates the streams being zipped concurrently, the -- following would take half the time that it would take in serial -- zipping: -- --
--   >>> s = Stream.fromFoldableM $ Prelude.map delay [1, 1, 1]
--   
--   >>> Stream.toList $ Stream.fromZipAsync $ (,) <$> s <*> s
--   ...
--   [(1,1),(1,1),(1,1)]
--   
-- -- Since: 0.2.0 (Streamly) data ZipAsyncM m a -- | A serial IO stream of elements of type a. See SerialT -- documentation for more details. -- -- Since: 0.2.0 (Streamly) type Serial = SerialT IO -- | An interleaving serial IO stream of elements of type a. See -- WSerialT documentation for more details. -- -- Since: 0.2.0 (Streamly) type WSerial = WSerialT IO -- | A serial IO stream of elements of type a with concurrent -- lookahead. See AheadT documentation for more details. -- -- Since: 0.3.0 (Streamly) type Ahead = AheadT IO -- | A demand driven left biased parallely composing IO stream of elements -- of type a. See AsyncT documentation for more details. -- -- Since: 0.2.0 (Streamly) type Async = AsyncT IO -- | A round robin parallely composing IO stream of elements of type -- a. See WAsyncT documentation for more details. -- -- Since: 0.2.0 (Streamly) type WAsync = WAsyncT IO -- | A parallely composing IO stream of elements of type a. See -- ParallelT documentation for more details. -- -- Since: 0.2.0 (Streamly) type Parallel = ParallelT IO -- | An IO stream whose applicative instance zips streams serially. -- -- Since: 0.2.0 (Streamly) type ZipSerial = ZipSerialM IO -- | An IO stream whose applicative instance zips streams wAsyncly. -- -- Since: 0.2.0 (Streamly) type ZipAsync = ZipAsyncM IO -- | A monad that can perform concurrent or parallel IO operations. Streams -- that can be composed concurrently require the underlying monad to be -- MonadAsync. -- -- Since: 0.1.0 (Streamly) type MonadAsync m = (MonadIO m, MonadBaseControl IO m, MonadThrow m) -- | Class of types that can represent a stream of elements of some type -- a in some monad m. -- -- Since: 0.2.0 (Streamly) class (forall m a. MonadAsync m => Semigroup (t m a), forall m a. MonadAsync m => Monoid (t m a), forall m. Monad m => Functor (t m), forall m. MonadAsync m => Applicative (t m)) => IsStream t -- | Fix the type of a polymorphic stream as SerialT. -- -- Since: 0.1.0 (Streamly) fromSerial :: IsStream t => SerialT m a -> t m a -- | Fix the type of a polymorphic stream as WSerialT. -- -- Since: 0.2.0 (Streamly) fromWSerial :: IsStream t => WSerialT m a -> t m a -- | Fix the type of a polymorphic stream as AsyncT. -- -- Since: 0.1.0 (Streamly) fromAsync :: IsStream t => AsyncT m a -> t m a -- | Fix the type of a polymorphic stream as AheadT. -- -- Since: 0.3.0 (Streamly) fromAhead :: IsStream t => AheadT m a -> t m a -- | Fix the type of a polymorphic stream as WAsyncT. -- -- Since: 0.2.0 (Streamly) fromWAsync :: IsStream t => WAsyncT m a -> t m a -- | Fix the type of a polymorphic stream as ParallelT. -- -- Since: 0.1.0 (Streamly) fromParallel :: IsStream t => ParallelT m a -> t m a -- | Fix the type of a polymorphic stream as ZipSerialM. -- -- Since: 0.2.0 (Streamly) fromZipSerial :: IsStream t => ZipSerialM m a -> t m a -- | Fix the type of a polymorphic stream as ZipAsyncM. -- -- Since: 0.2.0 (Streamly) fromZipAsync :: IsStream t => ZipAsyncM m a -> t m a -- | Adapt any specific stream type to any other specific stream type. -- -- Since: 0.1.0 (Streamly) adapt :: (IsStream t1, IsStream t2) => t1 m a -> t2 m a -- | Same as fromEffect -- | Deprecated: Please use fromEffect instead. once :: (Monad m, IsStream t) => m a -> t m a -- | Same as fromPure -- | Deprecated: Please use fromPure instead. yield :: IsStream t => a -> t m a -- | Same as fromEffect -- | Deprecated: Please use fromEffect instead. yieldM :: (Monad m, IsStream t) => m a -> t m a -- | Same as fromFoldable. -- | Deprecated: Please use fromFoldable instead. each :: (IsStream t, Foldable f) => f a -> t m a -- | Strict left scan with an extraction function. Like scanl', but -- applies a user supplied extraction function (the third argument) at -- each step. This is designed to work with the foldl library. -- The suffix x is a mnemonic for extraction. -- -- Since 0.2.0 -- -- Since: 0.7.0 (Monad m constraint) -- | Deprecated: Please use scanl followed by map instead. scanx :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b -- | Strict left fold with an extraction function. Like the standard strict -- left fold, but applies a user supplied extraction function (the third -- argument) to the folded value at the end. This is designed to work -- with the foldl library. The suffix x is a mnemonic -- for extraction. -- | Deprecated: Please use foldl' followed by fmap instead. foldx :: Monad m => (x -> a -> x) -> x -> (x -> b) -> SerialT m a -> m b -- | Like foldx, but with a monadic step function. -- | Deprecated: Please use foldlM' followed by fmap instead. foldxM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> SerialT m a -> m b -- | Lazy right fold for non-empty streams, using first element as the -- starting value. Returns Nothing if the stream is empty. -- | Deprecated: Use foldrM instead. foldr1 :: Monad m => (a -> a -> a) -> SerialT m a -> m (Maybe a) -- | Run a stream, discarding the results. By default it interprets the -- stream as SerialT, to run other types of streams use the type -- adapting combinators for example runStream . -- fromAsync. -- | Deprecated: Please use "drain" instead runStream :: Monad m => SerialT m a -> m () -- |
--   runN n = runStream . take n
--   
-- -- Run maximum up to n iterations of a stream. -- | Deprecated: Please use "drainN" instead runN :: Monad m => Int -> SerialT m a -> m () -- |
--   runWhile p = runStream . takeWhile p
--   
-- -- Run a stream as long as the predicate holds true. -- | Deprecated: Please use "drainWhile" instead runWhile :: Monad m => (a -> Bool) -> SerialT m a -> m () -- | Read lines from an IO Handle into a stream of Strings. -- | Deprecated: Please use Streamly.FileSystem.Handle module (see the -- changelog) fromHandle :: (IsStream t, MonadIO m) => Handle -> t m String -- |
--   toHandle h = S.mapM_ $ hPutStrLn h
--   
-- -- Write a stream of Strings to an IO Handle. -- | Deprecated: Please use Streamly.FileSystem.Handle module (see the -- changelog) toHandle :: MonadIO m => Handle -> SerialT m String -> m () -- | Deprecated: Please use unfoldMany instead. concatUnfold :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b module Streamly.Internal.Unicode.Array.Prim.Pinned -- | Break a string up into a stream of strings at newline characters. The -- resulting strings do not contain newlines. -- --
--   lines = S.lines A.write
--   
-- --
--   >>> Stream.toList $ Unicode.lines $ Stream.fromList "lines\nthis\nstring\n\n\n"
--   [fromListN 5 "lines",fromListN 4 "this",fromListN 6 "string",fromListN 0 "",fromListN 0 ""]
--   
lines :: (MonadIO m, IsStream t) => t m Char -> t m (Array Char) -- | Break a string up into a stream of strings, which were delimited by -- characters representing white space. -- --
--   words = S.words A.write
--   
-- --
--   >>> Stream.toList $ Unicode.words $ Stream.fromList "A  newline\nis considered white space?"
--   [fromListN 1 "A",fromListN 7 "newline",fromListN 2 "is",fromListN 10 "considered",fromListN 5 "white",fromListN 6 "space?"]
--   
words :: (MonadIO m, IsStream t) => t m Char -> t m (Array Char) -- | Flattens the stream of Array Char, after appending a -- terminating newline to each string. -- -- unlines is an inverse operation to lines. -- --
--   >>> Stream.toList $ Unicode.unlines $ Stream.fromList ["lines", "this", "string"]
--   "lines\nthis\nstring\n"
--   
-- --
--   unlines = S.unlines A.read
--   
-- -- Note that, in general -- --
--   unlines . lines /= id
--   
unlines :: (MonadAsync m, IsStream t) => t m (Array Char) -> t m Char -- | Flattens the stream of Array Char, after appending a -- separating space to each string. -- -- unwords is an inverse operation to words. -- --
--   >>> Stream.toList $ Unicode.unwords $ Stream.fromList ["unwords", "this", "string"]
--   "unwords this string"
--   
-- --
--   unwords = S.unwords A.read
--   
-- -- Note that, in general -- --
--   unwords . words /= id
--   
unwords :: (MonadAsync m, IsStream t) => t m (Array Char) -> t m Char module Streamly.Internal.Unicode.Array.Char -- | Break a string up into a stream of strings at newline characters. The -- resulting strings do not contain newlines. -- --
--   lines = S.lines A.write
--   
-- --
--   >>> Stream.toList $ Unicode.lines $ Stream.fromList "lines\nthis\nstring\n\n\n"
--   ["lines","this","string","",""]
--   
lines :: (MonadIO m, IsStream t) => t m Char -> t m (Array Char) -- | Break a string up into a stream of strings, which were delimited by -- characters representing white space. -- --
--   words = S.words A.write
--   
-- --
--   >>> Stream.toList $ Unicode.words $ Stream.fromList "A  newline\nis considered white space?"
--   ["A","newline","is","considered","white","space?"]
--   
words :: (MonadIO m, IsStream t) => t m Char -> t m (Array Char) -- | Flattens the stream of Array Char, after appending a -- terminating newline to each string. -- -- unlines is an inverse operation to lines. -- --
--   >>> Stream.toList $ Unicode.unlines $ Stream.fromList ["lines", "this", "string"]
--   "lines\nthis\nstring\n"
--   
-- --
--   unlines = S.unlines A.read
--   
-- -- Note that, in general -- --
--   unlines . lines /= id
--   
unlines :: (MonadIO m, IsStream t) => t m (Array Char) -> t m Char -- | Flattens the stream of Array Char, after appending a -- separating space to each string. -- -- unwords is an inverse operation to words. -- --
--   >>> Stream.toList $ Unicode.unwords $ Stream.fromList ["unwords", "this", "string"]
--   "unwords this string"
--   
-- --
--   unwords = S.unwords A.read
--   
-- -- Note that, in general -- --
--   unwords . words /= id
--   
unwords :: (MonadAsync m, IsStream t) => t m (Array Char) -> t m Char -- | This module is a an experimental replacement for -- Streamly.FileSystem.Handle. The former module provides IO -- facilities based on the GHC Handle type. The APIs in this module avoid -- the GHC handle layer and provide more explicit control over buffering. -- -- Read and write data as streams and arrays to and from files. -- -- This module provides read and write APIs based on handles. Before -- reading or writing, a file must be opened first using openFile. -- The Handle returned by openFile is then used to access -- the file. A Handle is backed by an operating system file -- descriptor. When the Handle is garbage collected the underlying -- file descriptor is automatically closed. A handle can be explicitly -- closed using closeFile. -- -- Reading and writing APIs are divided into two categories, sequential -- streaming APIs and random or seekable access APIs. File IO APIs are -- quite similar to Streamly.Data.Array.Foreign read write APIs. -- In that regard, arrays can be considered as in-memory files or files -- can be considered as on-disk arrays. -- --
--   import qualified Streamly.Internal.FileSystem.FD as FD
--   
module Streamly.Internal.FileSystem.FD -- | A Handle is returned by openFile and is subsequently -- used to perform read and write operations on a file. data Handle -- | File handle for standard input stdin :: Handle -- | File handle for standard output stdout :: Handle -- | File handle for standard error stderr :: Handle -- | Open a file that is not a directory and return a file handle. -- openFile enforces a multiple-reader single-writer locking on -- files. That is, there may either be many handles on the same file -- which manage input, or just one handle on the file which manages -- output. If any open handle is managing a file for output, no new -- handle can be allocated for that file. If any open handle is managing -- a file for input, new handles can only be allocated if they do not -- manage output. Whether two files are the same is -- implementation-dependent, but they should normally be the same if they -- have the same absolute path name and neither has been renamed, for -- example. openFile :: FilePath -> IOMode -> IO Handle -- | Generate a stream of elements of the given type from a file -- Handle. The stream ends when EOF is encountered. read :: (IsStream t, MonadIO m) => Handle -> t m Word8 -- | readInChunksOf chunkSize handle reads a byte stream from a -- file handle, reads are performed in chunks of up to -- chunkSize. The stream ends as soon as EOF is encountered. readInChunksOf :: (IsStream t, MonadIO m) => Int -> Handle -> t m Word8 -- | readArrays h reads a stream of arrays from file handle -- h. The maximum size of a single array is limited to -- defaultChunkSize. readArrays ignores the prevailing -- TextEncoding and NewlineMode on the Handle. -- --
--   readArrays = readArraysOfUpto defaultChunkSize
--   
readArrays :: (IsStream t, MonadIO m) => Handle -> t m (Array Word8) readArraysOfUpto :: (IsStream t, MonadIO m) => Int -> Handle -> t m (Array Word8) -- | Write a byte stream to a file handle. Combines the bytes in chunks of -- size up to defaultChunkSize before writing. Note that the write -- behavior depends on the IOMode and the current seek position of -- the handle. write :: MonadIO m => Handle -> SerialT m Word8 -> m () -- | Like write but provides control over the write buffer. Output -- will be written to the IO device as soon as we collect the specified -- number of input elements. writeInChunksOf :: MonadIO m => Int -> Handle -> SerialT m Word8 -> m () -- | Write a stream of arrays to a handle. writeArrays :: (MonadIO m, Storable a) => Handle -> SerialT m (Array a) -> m () -- | Write a stream of arrays to a handle after coalescing them in chunks -- of specified size. The chunk size is only a maximum and the actual -- writes could be smaller than that as we do not split the arrays to fit -- them to the specified size. writeArraysPackedUpto :: (MonadIO m, Storable a) => Int -> Handle -> SerialT m (Array a) -> m () -- |

Overview

-- -- Use watchPaths with a list of file system paths you want to -- watch as argument. It returns a stream of Event representing -- the file system events occurring under the watched paths. -- --
--   Stream.mapM_ (putStrLn . showEvent) $ watchPaths [Array.fromCString# "dir"#]
--   
-- -- Event is an opaque type. Accessor functions (e.g. -- showEvent above) provided in this module are used to determine -- the attributes of the event. -- -- Identical successive events may be coalesced into a single event. -- --

Design notes

-- -- For reference documentation see: -- -- -- -- We try to keep the macOS/Linux/Windows event handling APIs and -- defaults semantically and syntactically as close as possible. -- --

BUGs

-- -- When testing on Linux Kernel version 5.3.0-53-generic -- #47-Ubuntu, the last event for the root path seems to be delayed -- until one more event occurs. -- --

Differences between macOS and Linux APIs:

-- --
    --
  1. macOS watch is based on the path provided to it, if the path is -- deleted and recreated it will still be watched, if the path moves to -- another path it won't be watched anymore. Whereas Linux watch is based -- on a handle to the path, if the path is deleted and recreated it won't -- be watched, if the path moves to another it can still be watched -- (though this is configurable).
  2. --
-- --
    --
  1. macOS watches the directory hierarchy recursively, Linux watches -- only one level of dir, recursive watch has to be built in user space -- by watching for create events and adding the new directories to the -- watch. Not sure how this will scale for too many paths.
  2. --
  3. In macOS the path of the subject of the event is absolute, in -- Linux the path is the name of the object inside the dir being -- watched.
  4. --
  5. On Linux watchPaths fails if a path does not exist, on -- macOS it does not fail.
  6. --
module Streamly.Internal.FileSystem.Event.Linux -- | Watch configuration, used to specify the events of interest and the -- behavior of the watch. -- -- Pre-release data Config Config :: Bool -> Word32 -> Config [watchRec] :: Config -> Bool [createFlags] :: Config -> Word32 -- | Whether a setting is On or Off. -- -- Pre-release data Toggle On :: Toggle Off :: Toggle -- | The default configuration settings are: -- -- -- -- The tunable events enabled by default are: -- -- -- -- Pre-release defaultConfig :: Config -- | Watch the whole directory tree recursively instead of watching just -- one level of directory. -- -- default: Off -- -- Pre-release setRecursiveMode :: Toggle -> Config -> Config -- | If the pathname to be watched is a symbolic link then watch the target -- of the symbolic link instead of the symbolic link itself. -- -- Note that the path location in the events is through the original -- symbolic link path rather than the resolved path. -- -- default: On -- -- Pre-release setFollowSymLinks :: Toggle -> Config -> Config -- | If an object moves out of the directory being watched then stop -- watching it. -- -- default: On -- -- Pre-release setUnwatchMoved :: Toggle -> Config -> Config -- | Watch the object only for one event and then remove it from the watch. -- -- default: Off -- -- Pre-release setOneShot :: Toggle -> Config -> Config -- | Watch the object only if it is a directory. This provides a race-free -- way to ensure that the watched object is a directory. -- -- default: Off -- -- Pre-release setOnlyDir :: Toggle -> Config -> Config -- | What to do if a watch already exists when openWatch or -- addToWatch is called for a path. -- -- Pre-release data WhenExists -- | Do not set an existing setting to Off only set to On AddIfExists :: WhenExists -- | Replace the existing settings with new settings ReplaceIfExists :: WhenExists -- | When adding a new path to the watch, specify what to do if a watch -- already exists on that path. -- -- default: FailIfExists -- -- Pre-release setWhenExists :: WhenExists -> Config -> Config -- | Report when the watched path itself gets deleted. -- -- default: On -- -- Pre-release setRootDeleted :: Toggle -> Config -> Config -- | Report when the watched root path itself gets renamed. -- -- default: On -- -- Pre-release setRootMoved :: Toggle -> Config -> Config -- | Report when the watched root path itself gets deleted or renamed. -- -- default: On -- -- Pre-release setRootPathEvents :: Toggle -> Config -> Config -- | Report when the metadata e.g. owner, permission modes, modifications -- times of an object changes. -- -- default: On -- -- Pre-release setAttrsModified :: Toggle -> Config -> Config -- | Report when a file is accessed. -- -- default: On -- -- Pre-release setAccessed :: Toggle -> Config -> Config -- | Report when a file is opened. -- -- default: On -- -- Pre-release setOpened :: Toggle -> Config -> Config -- | Report when a file that was opened for writes is closed. -- -- default: On -- -- Pre-release setWriteClosed :: Toggle -> Config -> Config -- | Report when a file that was opened for not writing is closed. -- -- default: On -- -- Pre-release setNonWriteClosed :: Toggle -> Config -> Config -- | Report when a file is created. -- -- default: On -- -- Pre-release setCreated :: Toggle -> Config -> Config -- | Report when a file is deleted. -- -- default: On -- -- Pre-release setDeleted :: Toggle -> Config -> Config -- | Report the source of a move. -- -- default: On -- -- Pre-release setMovedFrom :: Toggle -> Config -> Config -- | Report the target of a move. -- -- default: On -- -- Pre-release setMovedTo :: Toggle -> Config -> Config -- | Report when a file is modified. -- -- default: On -- -- Pre-release setModified :: Toggle -> Config -> Config -- | Set all tunable events On or Off. Equivalent to setting: -- -- -- -- Pre-release setAllEvents :: Toggle -> Config -> Config -- | Same as watchWith using defaultConfig and non-recursive mode. -- --
--   >>> watch = watchWith id
--   
-- -- Pre-release watch :: NonEmpty (Array Word8) -> SerialT IO Event -- | Same as watchWith using defaultConfig and recursive -- mode. -- --
--   >>> watchRecursive = watchWith (setRecursiveMode On)
--   
-- -- See watchWith for pitfalls and bugs when using recursive watch -- on Linux. -- -- Pre-release watchRecursive :: NonEmpty (Array Word8) -> SerialT IO Event -- | Start monitoring a list of file system paths for file system events -- with the supplied configuration operation over the -- defaultConfig. The paths could be files or directories. When -- recursive mode is set and the path is a directory, the whole directory -- tree under it is watched recursively. Monitoring starts from the -- current time onwards. The paths are specified as UTF-8 encoded -- Array of Word8. -- -- Non-existing Paths: the API fails if a watch is started on a -- non-exsting path. -- -- Performance: Note that recursive watch on a large directory -- tree could be expensive. When starting a watch, the whole tree must be -- read and watches are started on each directory in the tree. The -- initial time to start the watch as well as the memory required is -- proportional to the number of directories in the tree. -- -- Bugs: When new directories are created under the tree they are -- added to the watch on receiving the directory create event. However, -- the creation of a dir and adding a watch for it is not atomic. The -- implementation takes care of this and makes sure that watches are -- added for all directories. However, In the mean time, the directory -- may have received more events which may get lost. Handling of any such -- lost events is yet to be implemented. -- -- See the Linux inotify man page for more details. -- --
--   watchwith
--        (setFollowSymLinks On . setUnwatchMoved Off)
--        [Array.fromCString# "dir"#]
--   
-- -- Pre-release watchWith :: (Config -> Config) -> NonEmpty (Array Word8) -> SerialT IO Event -- | addToWatch cfg watch root subpath adds subpath to -- the list of paths being monitored under root via the watch -- handle watch. root must be an absolute path and -- subpath must be relative to root. -- -- Pre-release addToWatch :: Config -> Watch -> Array Word8 -> Array Word8 -> IO () -- | Remove an absolute root path from a Watch, if a path was moved -- after adding you need to provide the original path which was used to -- add the Watch. -- -- Pre-release removeFromWatch :: Watch -> Array Word8 -> IO () -- | An Event generated by the file system. Use the accessor functions to -- examine the event. -- -- Pre-release data Event Event :: CInt -> Word32 -> Word32 -> Array Word8 -> IntMap (Array Word8, Array Word8) -> Event [eventWd] :: Event -> CInt [eventFlags] :: Event -> Word32 [eventCookie] :: Event -> Word32 [eventRelPath] :: Event -> Array Word8 [eventMap] :: Event -> IntMap (Array Word8, Array Word8) -- | Get the watch root corresponding to the Event. -- -- Note that if a path was moved after adding to the watch, this will -- give the original path and not the new path after moving. -- -- TBD: we can possibly update the watch root on a move self event. -- -- Pre-release getRoot :: Event -> Array Word8 -- | Get the file system object path for which the event is generated, -- relative to the watched root. The path is a "/" separated array of -- bytes. -- -- Pre-release getRelPath :: Event -> Array Word8 -- | Get the absolute file system object path for which the event is -- generated. -- -- When the watch root is a symlink, the absolute path returned is via -- the original symlink and not through the resolved path. -- -- Pre-release getAbsPath :: Event -> Array Word8 -- | Cookie is set when a rename occurs. The cookie value can be used to -- connect the isMovedFrom and isMovedTo events, if both -- the events belong to the same move operation then they will have the -- same cookie value. -- -- Pre-release getCookie :: Event -> Cookie -- | Determine whether the event indicates a change of path of the -- monitored object itself. Note that the object may become unreachable -- or deleted after a change of path. -- -- Occurs only for a watched path -- -- Pre-release isRootPathEvent :: Event -> Bool -- | A path was removed from the watch explicitly using -- removeFromWatch or automatically (file was deleted, or -- filesystem was unmounted). -- -- Note that in recursive watch mode all the subdirectories are watch -- roots, therefore, they will all generate this event. -- -- Occurs only for a watched path -- -- Pre-release isRootUnwatched :: Event -> Bool -- | Watched file/directory was itself deleted. (This event also occurs if -- an object is moved to another filesystem, since mv(1) in effect copies -- the file to the other filesystem and then deletes it from the original -- filesystem.) In addition, an isRootUnwatched event will -- subsequently be generated for the watch descriptor. -- -- Note that in recursive watch mode all the subdirectories are watch -- roots, therefore, they will all generate this event. -- -- Occurs only for a watched path -- -- Pre-release isRootDeleted :: Event -> Bool -- | Watched file/directory was itself moved within the file system. -- -- Note that in recursive watch mode all the subdirectories are watch -- roots, therefore, they will all generate this event. -- -- Occurs only for a watched path -- -- Pre-release isRootMoved :: Event -> Bool -- | Filesystem containing watched object was unmounted. In addition, an -- isRootUnwatched event will subsequently be generated for the -- watch descriptor. -- -- Occurs only for a watched path -- -- Pre-release isRootUnmounted :: Event -> Bool -- | Determine whether the event indicates inode metadata change for an -- object contained within the monitored path. -- -- Metadata change may include, permissions (e.g., chmod(2)), timestamps -- (e.g., utimensat(2)), extended attributes (setxattr(2)), link count -- (since Linux 2.6.25; e.g., for the target of link(2) and for -- unlink(2)), and user/group ID (e.g., chown(2)). -- -- Can occur for watched path or a file inside it -- -- Pre-release isAttrsModified :: Event -> Bool -- | File was accessed (e.g. read, execve). -- -- Occurs only for a file inside the watched directory -- -- Pre-release isAccessed :: Event -> Bool -- | File or directory was opened. -- -- Occurs only for a file inside the watched directory -- -- Pre-release isOpened :: Event -> Bool -- | File opened for writing was closed. -- -- Occurs only for a file inside the watched directory -- -- Pre-release isWriteClosed :: Event -> Bool -- | File or directory opened for read but not write was closed. -- -- Can occur for watched path or a file inside it -- -- Pre-release isNonWriteClosed :: Event -> Bool -- | File/directory created in watched directory (e.g., open(2) O_CREAT, -- mkdir(2), link(2), symlink(2), bind(2) on a UNIX domain socket). -- -- Occurs only for an object inside the watched directory -- -- Pre-release isCreated :: Event -> Bool -- | File/directory deleted from watched directory. -- -- Occurs only for an object inside the watched directory -- -- Pre-release isDeleted :: Event -> Bool -- | Generated for the original path when an object is moved from under a -- monitored directory. -- -- Occurs only for an object inside the watched directory -- -- Pre-release isMovedFrom :: Event -> Bool -- | Generated for the new path when an object is moved under a monitored -- directory. -- -- Occurs only for an object inside the watched directory -- -- Pre-release isMovedTo :: Event -> Bool -- | Generated for a path that is moved from or moved to the monitored -- directory. -- --
--   >>> isMoved ev = isMovedFrom ev || isMovedTo ev
--   
-- -- Occurs only for an object inside the watched directory -- -- Pre-release isMoved :: Event -> Bool -- | Determine whether the event indicates modification of an object within -- the monitored path. This event is generated only for files and not -- directories. -- -- Occurs only for an object inside the watched directory -- -- Pre-release isModified :: Event -> Bool -- | Determine whether the event is for a directory path. -- -- Pre-release isDir :: Event -> Bool -- | Event queue overflowed (WD is invalid for this event) and we may have -- lost some events.. The user application must scan everything under the -- watched paths to know the current state. -- -- Pre-release isEventsLost :: Event -> Bool -- | Convert an Event record to a String representation. showEvent :: Event -> String instance GHC.Classes.Eq Streamly.Internal.FileSystem.Event.Linux.Toggle instance GHC.Show.Show Streamly.Internal.FileSystem.Event.Linux.Toggle instance GHC.Show.Show Streamly.Internal.FileSystem.Event.Linux.WD instance GHC.Classes.Eq Streamly.Internal.FileSystem.Event.Linux.Cookie instance GHC.Show.Show Streamly.Internal.FileSystem.Event.Linux.Cookie instance GHC.Classes.Eq Streamly.Internal.FileSystem.Event.Linux.Event instance GHC.Classes.Ord Streamly.Internal.FileSystem.Event.Linux.Event instance GHC.Show.Show Streamly.Internal.FileSystem.Event.Linux.Event -- | File system event notification API portable across Linux, macOS and -- Windows platforms. -- -- Note that recursive directory tree watch does not work reliably on -- Linux (see notes in the Linux module), therefore, recursive watch API -- is not provided in this module. However, you can use it from the -- platform specific modules. -- -- For platform specific APIs please see the following modules: -- -- module Streamly.Internal.FileSystem.Event -- | Start monitoring a list of directories or symbolic links to -- directories for file system events. Monitoring starts from the current -- time onwards. The paths are specified as UTF-8 encoded Array of -- Word8. -- -- If a watch root is a symbolic link then the target of the link is -- watched. Fails if the watched path does not exist. If the user does -- not have permissions (read and execute?) on the watch root then no -- events are generated. No events are generated if the watch root itself -- is renamed or deleted. -- -- This API watches for changes in the watch root directory only, any -- changes in the subdirectories of the watch root are not watched. -- However, on macOS the watch is always recursive, but do not rely on -- that behavior, it may change without notice in future. If you want to -- use recursive watch please use platform specific modules. -- -- Pre-release watch :: NonEmpty (Array Word8) -> SerialT IO Event -- | An Event generated by the file system. Use the accessor functions to -- examine the event. -- -- Pre-release data Event -- | Get the absolute path of the file system object for which the event is -- generated. The path is a UTF-8 encoded array of bytes. -- -- When the watch root is a symlink the behavior is different on -- different platforms: -- -- -- -- This API is subject to removal in future, to be replaced by a platform -- independent getRelPath. -- -- Pre-release getAbsPath :: Event -> Array Word8 -- | Determine whether the event indicates creation of an object within the -- monitored path. This event is generated when any file system object is -- created. -- -- For hard links the behavior is different on different operating -- systems. On macOS hard linking does not generate a create event, it -- generates an isInodeAttrsChanged event on the directory -- instead (see the Darwin module). On Linux and Windows hard linking -- generates a create event. -- -- Pre-release isCreated :: Event -> Bool -- | Determine whether the event indicates deletion of an object within the -- monitored path. On Linux and Windows hard link deletion generates a -- delete event. -- -- On Linux and Windows, this event does not occur when the watch root -- itself is deleted. On macOS it occurs on deleting the watch root when -- it is not a symbolic link. -- -- See also isRootDeleted event for Linux. -- -- Pre-release isDeleted :: Event -> Bool -- | Determine whether the event indicates rename of an object within the -- monitored path. This event is generated when an object is renamed -- within the watched directory or if it is moved out of or in the -- watched directory. Moving hard links is no different than other types -- of objects. -- -- Pre-release isMoved :: Event -> Bool -- | Determine whether the event indicates modification of an object within -- the monitored path. This event is generated on file modification on -- all platforms. -- -- On Linux and macOS this event is never generated for directories. On -- Windows (in recursive watch mode) this event is generated for -- directories as well when an object is created in or deleted from the -- directory. -- -- Pre-release isModified :: Event -> Bool -- | An event that indicates that some events before this may have been -- lost, therefore, we need to take some recovery action. -- -- Pre-release isEventsLost :: Event -> Bool -- | Convert an Event record to a String representation. Note that -- the output of this function may be different on different platforms -- because it may contain platform specific details. -- -- Internal showEvent :: Event -> String -- | Streamly is a general purpose programming framework using cocnurrent -- data flow programming paradigm. It can be considered as a -- generalization of Haskell lists to monadic streaming with concurrent -- composition capability. The serial stream type in streamly SerialT -- m a is like the list type [a] parameterized by the monad -- m. For example, SerialT IO a is a moral equivalent -- of [a] in the IO monad. Streams are constructed very much -- like lists, except that they use nil and cons instead of -- '[]' and :. -- --
--   > import Streamly
--   > import Streamly.Prelude (cons, consM)
--   > import qualified Streamly.Prelude as S
--   >
--   > S.toList $ 1 `cons` 2 `cons` 3 `cons` nil
--   [1,2,3]
--   
-- -- Unlike lists, streams can be constructed from monadic effects: -- --
--   > S.toList $ getLine `consM` getLine `consM` S.nil
--   hello
--   world
--   ["hello","world"]
--   
-- -- Streams are processed just like lists, with list like combinators, -- except that they are monadic and work in a streaming fashion. Here is -- a simple console echo program example: -- --
--   > S.drain $ S.repeatM getLine & S.mapM putStrLn
--   
-- -- SerialT Identity a is a moral equivalent of pure lists. -- Streamly utilizes fusion for high performance, therefore, we can -- represent and process strings as streams of Char, encode and -- decode the streams to/from UTF8 and serialize them to Array -- Word8 obviating the need for special purpose libraries like -- bytestring and text. -- -- For more details please see the Streamly.Tutorial module and -- the examples directory in this package. -- | Deprecated: Please use Streamly.Prelude instead. module Streamly -- | A monad that can perform concurrent or parallel IO operations. Streams -- that can be composed concurrently require the underlying monad to be -- MonadAsync. -- -- Since: 0.1.0 (Streamly) type MonadAsync m = (MonadIO m, MonadBaseControl IO m, MonadThrow m) -- | For SerialT streams: -- --
--   (<>) = serial                       -- Semigroup
--   (>>=) = flip . concatMapWith serial -- Monad
--   
-- -- A single Monad bind behaves like a for loop: -- --
--   >>> :{
--   Stream.toList $ do
--        x <- Stream.fromList [1,2] -- foreach x in stream
--        return x
--   :}
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops: -- --
--   >>> :{
--   Stream.toList $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [3,4] -- foreach y in stream
--       return (x, y)
--   :}
--   [(1,3),(1,4),(2,3),(2,4)]
--   
-- -- Since: 0.2.0 (Streamly) data SerialT m a -- | For WSerialT streams: -- --
--   (<>) = wSerial                       -- Semigroup
--   (>>=) = flip . concatMapWith wSerial -- Monad
--   
-- -- Note that <> is associative only if we disregard the -- ordering of elements in the resulting stream. -- -- A single Monad bind behaves like a for loop: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWSerial $ do
--        x <- Stream.fromList [1,2] -- foreach x in stream
--        return x
--   :}
--   [1,2]
--   
-- -- Nested monad binds behave like interleaved nested for loops: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWSerial $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [3,4] -- foreach y in stream
--       return (x, y)
--   :}
--   [(1,3),(2,3),(1,4),(2,4)]
--   
-- -- It is a result of interleaving all the nested iterations corresponding -- to element 1 in the first stream with all the nested -- iterations of element 2: -- --
--   >>> import Streamly.Prelude (wSerial)
--   
--   >>> Stream.toList $ Stream.fromList [(1,3),(1,4)] `Stream.wSerial` Stream.fromList [(2,3),(2,4)]
--   [(1,3),(2,3),(1,4),(2,4)]
--   
-- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- SerialT. -- -- Since: 0.2.0 (Streamly) data WSerialT m a -- | For AheadT streams: -- --
--   (<>) = ahead
--   (>>=) = flip . concatMapWith ahead
--   
-- -- A single Monad bind behaves like a for loop with -- iterations executed concurrently, ahead of time, producing side -- effects of iterations out of order, but results in order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAhead $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [2,1]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, ahead of time: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAhead $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,5,4,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one output stream and all the iterations corresponding to 2 -- constitute another output stream and these two output streams are -- merged using ahead. -- -- Since: 0.3.0 (Streamly) data AheadT m a -- | For AsyncT streams: -- --
--   (<>) = async
--   (>>=) = flip . concatMapWith async
--   
-- -- A single Monad bind behaves like a for loop with -- iterations of the loop executed concurrently a la the async -- combinator, producing results and side effects of iterations out of -- order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAsync $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, a la the async combinator: -- --
--   >>> :{
--   Stream.toList $ Stream.fromAsync $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,4,5,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one output stream and all the iterations corresponding to 2 -- constitute another output stream and these two output streams are -- merged using async. -- -- Since: 0.1.0 (Streamly) data AsyncT m a -- | For WAsyncT streams: -- --
--   (<>) = wAsync
--   (>>=) = flip . concatMapWith wAsync
--   
-- -- A single Monad bind behaves like a for loop with -- iterations of the loop executed concurrently a la the wAsync -- combinator, producing results and side effects of iterations out of -- order: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWAsync $ do
--        x <- Stream.fromList [2,1] -- foreach x in stream
--        Stream.fromEffect $ delay x
--   :}
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- Nested monad binds behave like nested for loops with nested -- iterations executed concurrently, a la the wAsync combinator: -- --
--   >>> :{
--   Stream.toList $ Stream.fromWAsync $ do
--       x <- Stream.fromList [1,2] -- foreach x in stream
--       y <- Stream.fromList [2,4] -- foreach y in stream
--       Stream.fromEffect $ delay (x + y)
--   :}
--   3 sec
--   4 sec
--   5 sec
--   6 sec
--   [3,4,5,6]
--   
-- -- The behavior can be explained as follows. All the iterations -- corresponding to the element 1 in the first stream constitute -- one WAsyncT output stream and all the iterations corresponding -- to 2 constitute another WAsyncT output stream and -- these two output streams are merged using wAsync. -- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- AsyncT. -- -- Since: 0.2.0 (Streamly) data WAsyncT m a -- | For ParallelT streams: -- --
--   (<>) = parallel
--   (>>=) = flip . concatMapWith parallel
--   
-- -- See AsyncT, ParallelT is similar except that all -- iterations are strictly concurrent while in AsyncT it depends -- on the consumer demand and available threads. See parallel -- for more details. -- -- Since: 0.1.0 (Streamly) -- -- Since: 0.7.0 (maxBuffer applies to ParallelT streams) data ParallelT m a -- | For ZipSerialM streams: -- --
--   (<>) = serial
--   (*) = 'Streamly.Prelude.serial.zipWith' id
--   
-- -- Applicative evaluates the streams being zipped serially: -- --
--   >>> s1 = Stream.fromFoldable [1, 2]
--   
--   >>> s2 = Stream.fromFoldable [3, 4]
--   
--   >>> s3 = Stream.fromFoldable [5, 6]
--   
--   >>> Stream.toList $ Stream.fromZipSerial $ (,,) <$> s1 <*> s2 <*> s3
--   [(1,3,5),(2,4,6)]
--   
-- -- Since: 0.2.0 (Streamly) data ZipSerialM m a -- | For ZipAsyncM streams: -- --
--   (<>) = serial
--   (*) = 'Streamly.Prelude.serial.zipAsyncWith' id
--   
-- -- Applicative evaluates the streams being zipped concurrently, the -- following would take half the time that it would take in serial -- zipping: -- --
--   >>> s = Stream.fromFoldableM $ Prelude.map delay [1, 1, 1]
--   
--   >>> Stream.toList $ Stream.fromZipAsync $ (,) <$> s <*> s
--   ...
--   [(1,1),(1,1),(1,1)]
--   
-- -- Since: 0.2.0 (Streamly) data ZipAsyncM m a -- | Parallel transform application operator; applies a stream -- transformation function t m a -> t m b to a stream t m -- a concurrently; the input stream is evaluated asynchronously in -- an independent thread yielding elements to a buffer and the -- transformation function runs in another thread consuming the input -- from the buffer. |$ is just like regular function application -- operator $ except that it is concurrent. -- -- If you read the signature as (t m a -> t m b) -> (t m a -- -> t m b) you can look at it as a transformation that converts -- a transform function to a buffered concurrent transform function. -- -- The following code prints a value every second even though each stage -- adds a 1 second delay. -- --
--   >>> :{
--   Stream.drain $
--      Stream.mapM (\x -> threadDelay 1000000 >> print x)
--        |$ Stream.replicateM 3 (threadDelay 1000000 >> return 1)
--   :}
--   1
--   1
--   1
--   
-- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|$) :: (IsStream t, MonadAsync m) => (t m a -> t m b) -> t m a -> t m b infixr 0 |$ -- | Same as |$ but with arguments reversed. -- -- (|&) = flip (|$) -- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|&) :: (IsStream t, MonadAsync m) => t m a -> (t m a -> t m b) -> t m b infixl 1 |& -- | Parallel fold application operator; applies a fold function t m a -- -> m b to a stream t m a concurrently; The the input -- stream is evaluated asynchronously in an independent thread yielding -- elements to a buffer and the folding action runs in another thread -- consuming the input from the buffer. -- -- If you read the signature as (t m a -> m b) -> (t m a -> -- m b) you can look at it as a transformation that converts a fold -- function to a buffered concurrent fold function. -- -- The . at the end of the operator is a mnemonic for -- termination of the stream. -- -- In the example below, each stage introduces a delay of 1 sec but -- output is printed every second because both stages are concurrent. -- --
--   >>> import Control.Concurrent (threadDelay)
--   
--   >>> import Streamly.Prelude ((|$.))
--   
--   >>> :{
--    Stream.foldlM' (\_ a -> threadDelay 1000000 >> print a) (return ())
--        |$. Stream.replicateM 3 (threadDelay 1000000 >> return 1)
--   :}
--   1
--   1
--   1
--   
-- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|$.) :: (IsStream t, MonadAsync m) => (t m a -> m b) -> t m a -> m b infixr 0 |$. -- | Same as |$. but with arguments reversed. -- --
--   (|&.) = flip (|$.)
--   
-- -- Concurrent -- -- Since: 0.3.0 (Streamly) (|&.) :: (IsStream t, MonadAsync m) => t m a -> (t m a -> m b) -> m b infixl 1 |&. -- | Make a stream asynchronous, triggers the computation and returns a -- stream in the underlying monad representing the output generated by -- the original computation. The returned action is exhaustible and must -- be drained once. If not drained fully we may have a thread blocked -- forever and once exhausted it will always return empty. mkAsync :: (IsStream t, MonadAsync m) => t m a -> m (t m a) -- | Appends two streams sequentially, yielding all elements from the first -- stream, and then all elements from the second stream. -- --
--   >>> import Streamly.Prelude (serial)
--   
--   >>> stream1 = Stream.fromList [1,2]
--   
--   >>> stream2 = Stream.fromList [3,4]
--   
--   >>> Stream.toList $ stream1 `serial` stream2
--   [1,2,3,4]
--   
-- -- This operation can be used to fold an infinite lazy container of -- streams. -- -- Since: 0.2.0 (Streamly) serial :: IsStream t => t m a -> t m a -> t m a infixr 6 `serial` -- | Interleaves two streams, yielding one element from each stream -- alternately. When one stream stops the rest of the other stream is -- used in the output stream. -- --
--   >>> import Streamly.Prelude (wSerial)
--   
--   >>> stream1 = Stream.fromList [1,2]
--   
--   >>> stream2 = Stream.fromList [3,4]
--   
--   >>> Stream.toList $ Stream.fromWSerial $ stream1 `wSerial` stream2
--   [1,3,2,4]
--   
-- -- Note, for singleton streams wSerial and serial are -- identical. -- -- Note that this operation cannot be used to fold a container of -- infinite streams but it can be used for very large streams as the -- state that it needs to maintain is proportional to the logarithm of -- the number of streams. -- -- Since: 0.2.0 (Streamly) wSerial :: IsStream t => t m a -> t m a -> t m a infixr 6 `wSerial` -- | Appends two streams, both the streams may be evaluated concurrently -- but the outputs are used in the same order as the corresponding -- actions in the original streams, side effects will happen in the order -- in which the streams are evaluated: -- --
--   >>> import Streamly.Prelude (ahead, SerialT)
--   
--   >>> stream1 = Stream.fromEffect (delay 4) :: SerialT IO Int
--   
--   >>> stream2 = Stream.fromEffect (delay 2) :: SerialT IO Int
--   
--   >>> Stream.toList $ stream1 `ahead` stream2 :: IO [Int]
--   2 sec
--   4 sec
--   [4,2]
--   
-- -- Multiple streams can be combined. With enough threads, all of them can -- be scheduled simultaneously: -- --
--   >>> stream3 = Stream.fromEffect (delay 1)
--   
--   >>> Stream.toList $ stream1 `ahead` stream2 `ahead` stream3
--   1 sec
--   2 sec
--   4 sec
--   [4,2,1]
--   
-- -- With 2 threads, only two can be scheduled at a time, when one of those -- finishes, the third one gets scheduled: -- --
--   >>> Stream.toList $ Stream.maxThreads 2 $ stream1 `ahead` stream2 `ahead` stream3
--   2 sec
--   1 sec
--   4 sec
--   [4,2,1]
--   
-- -- Only streams are scheduled for ahead evaluation, how actions within a -- stream are evaluated depends on the stream type. If it is a concurrent -- stream they will be evaluated concurrently. It may not make much sense -- combining serial streams using ahead. -- -- ahead can be safely used to fold an infinite lazy container of -- streams. -- -- Since: 0.3.0 (Streamly) ahead :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `ahead` -- | Merges two streams, both the streams may be evaluated concurrently, -- outputs from both are used as they arrive: -- --
--   >>> import Streamly.Prelude (async)
--   
--   >>> stream1 = Stream.fromEffect (delay 4)
--   
--   >>> stream2 = Stream.fromEffect (delay 2)
--   
--   >>> Stream.toList $ stream1 `async` stream2
--   2 sec
--   4 sec
--   [2,4]
--   
-- -- Multiple streams can be combined. With enough threads, all of them can -- be scheduled simultaneously: -- --
--   >>> stream3 = Stream.fromEffect (delay 1)
--   
--   >>> Stream.toList $ stream1 `async` stream2 `async` stream3
--   ...
--   [1,2,4]
--   
-- -- With 2 threads, only two can be scheduled at a time, when one of those -- finishes, the third one gets scheduled: -- --
--   >>> Stream.toList $ Stream.maxThreads 2 $ stream1 `async` stream2 `async` stream3
--   ...
--   [2,1,4]
--   
-- -- With a single thread, it becomes serial: -- --
--   >>> Stream.toList $ Stream.maxThreads 1 $ stream1 `async` stream2 `async` stream3
--   ...
--   [4,2,1]
--   
-- -- Only streams are scheduled for async evaluation, how actions within a -- stream are evaluated depends on the stream type. If it is a concurrent -- stream they will be evaluated concurrently. -- -- In the following example, both the streams are scheduled for -- concurrent evaluation but each individual stream is evaluated -- serially: -- --
--   >>> stream1 = Stream.fromListM $ Prelude.map delay [3,3] -- SerialT IO Int
--   
--   >>> stream2 = Stream.fromListM $ Prelude.map delay [1,1] -- SerialT IO Int
--   
--   >>> Stream.toList $ stream1 `async` stream2 -- IO [Int]
--   ...
--   [1,1,3,3]
--   
-- -- If total threads are 2, the third stream is scheduled only after one -- of the first two has finished: -- --
--   stream3 = Stream.fromListM $ Prelude.map delay [2,2] -- SerialT IO Int
--   Stream.toList $ Stream.maxThreads 2 $ stream1 `async` stream2 `async` stream3 -- IO [Int]
--   
-- -- ... [1,1,3,2,3,2] -- -- Thus async goes deep in first few streams rather than going -- wide in all streams. It prefers to evaluate the leftmost streams as -- much as possible. Because of this behavior, async can be safely -- used to fold an infinite lazy container of streams. -- -- Since: 0.2.0 (Streamly) async :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `async` -- | For singleton streams, wAsync is the same as async. See -- async for singleton stream behavior. For multi-element streams, -- while async is left biased i.e. it tries to evaluate the left -- side stream as much as possible, wAsync tries to schedule them -- both fairly. In other words, async goes deep while -- wAsync goes wide. However, outputs are always used as they -- arrive. -- -- With a single thread, async starts behaving like serial -- while wAsync starts behaving like wSerial. -- --
--   >>> import Streamly.Prelude (async, wAsync)
--   
--   >>> stream1 = Stream.fromList [1,2,3]
--   
--   >>> stream2 = Stream.fromList [4,5,6]
--   
--   >>> Stream.toList $ Stream.fromAsync $ Stream.maxThreads 1 $ stream1 `async` stream2
--   [1,2,3,4,5,6]
--   
-- --
--   >>> Stream.toList $ Stream.fromWAsync $ Stream.maxThreads 1 $ stream1 `wAsync` stream2
--   [1,4,2,5,3,6]
--   
-- -- With two threads available, and combining three streams: -- --
--   >>> stream3 = Stream.fromList [7,8,9]
--   
--   >>> Stream.toList $ Stream.fromAsync $ Stream.maxThreads 2 $ stream1 `async` stream2 `async` stream3
--   [1,2,3,4,5,6,7,8,9]
--   
-- --
--   >>> Stream.toList $ Stream.fromWAsync $ Stream.maxThreads 2 $ stream1 `wAsync` stream2 `wAsync` stream3
--   [1,4,2,7,5,3,8,6,9]
--   
-- -- This operation cannot be used to fold an infinite lazy container of -- streams, because it schedules all the streams in a round robin manner. -- -- Note that WSerialT and single threaded WAsyncT both -- interleave streams but the exact scheduling is slightly different in -- both cases. -- -- Since: 0.2.0 (Streamly) wAsync :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `wAsync` -- | Like async except that the execution is much more strict. There -- is no limit on the number of threads. While async may not -- schedule a stream if there is no demand from the consumer, -- parallel always evaluates both the streams immediately. The -- only limit that applies to parallel is maxBuffer. -- Evaluation may block if the output buffer becomes full. -- --
--   >>> import Streamly.Prelude (parallel)
--   
--   >>> stream = Stream.fromEffect (delay 2) `parallel` Stream.fromEffect (delay 1)
--   
--   >>> Stream.toList stream -- IO [Int]
--   1 sec
--   2 sec
--   [1,2]
--   
-- -- parallel guarantees that all the streams are scheduled for -- execution immediately, therefore, we could use things like starting -- timers inside the streams and relying on the fact that all timers were -- started at the same time. -- -- Unlike async this operation cannot be used to fold an infinite -- lazy container of streams, because it schedules all the streams -- strictly concurrently. -- -- Since: 0.2.0 (Streamly) parallel :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a infixr 6 `parallel` -- | Specify the maximum number of threads that can be spawned concurrently -- for any concurrent combinator in a stream. A value of 0 resets the -- thread limit to default, a negative value means there is no limit. The -- default value is 1500. maxThreads does not affect -- ParallelT streams as they can use unbounded number of -- threads. -- -- When the actions in a stream are IO bound, having blocking IO calls, -- this option can be used to control the maximum number of in-flight IO -- requests. When the actions are CPU bound this option can be used to -- control the amount of CPU used by the stream. -- -- Since: 0.4.0 (Streamly) maxThreads :: IsStream t => Int -> t m a -> t m a -- | Specify the maximum size of the buffer for storing the results from -- concurrent computations. If the buffer becomes full we stop spawning -- more concurrent tasks until there is space in the buffer. A value of 0 -- resets the buffer size to default, a negative value means there is no -- limit. The default value is 1500. -- -- CAUTION! using an unbounded maxBuffer value (i.e. a negative -- value) coupled with an unbounded maxThreads value is a recipe -- for disaster in presence of infinite streams, or very large streams. -- Especially, it must not be used when pure is used in -- ZipAsyncM streams as pure in applicative zip streams -- generates an infinite stream causing unbounded concurrent generation -- with no limit on the buffer or threads. -- -- Since: 0.4.0 (Streamly) maxBuffer :: IsStream t => Int -> t m a -> t m a -- | Specifies the stream yield rate in yields per second (Hertz). -- We keep accumulating yield credits at rateGoal. At any point of -- time we allow only as many yields as we have accumulated as per -- rateGoal since the start of time. If the consumer or the -- producer is slower or faster, the actual rate may fall behind or -- exceed rateGoal. We try to recover the gap between the two by -- increasing or decreasing the pull rate from the producer. However, if -- the gap becomes more than rateBuffer we try to recover only as -- much as rateBuffer. -- -- rateLow puts a bound on how low the instantaneous rate can go -- when recovering the rate gap. In other words, it determines the -- maximum yield latency. Similarly, rateHigh puts a bound on how -- high the instantaneous rate can go when recovering the rate gap. In -- other words, it determines the minimum yield latency. We reduce the -- latency by increasing concurrency, therefore we can say that it puts -- an upper bound on concurrency. -- -- If the rateGoal is 0 or negative the stream never yields a -- value. If the rateBuffer is 0 or negative we do not attempt to -- recover. -- -- Since: 0.5.0 (Streamly) data Rate Rate :: Double -> Double -> Double -> Int -> Rate -- | The lower rate limit [rateLow] :: Rate -> Double -- | The target rate we want to achieve [rateGoal] :: Rate -> Double -- | The upper rate limit [rateHigh] :: Rate -> Double -- | Maximum slack from the goal [rateBuffer] :: Rate -> Int -- | Specify the pull rate of a stream. A Nothing value resets the -- rate to default which is unlimited. When the rate is specified, -- concurrent production may be ramped up or down automatically to -- achieve the specified yield rate. The specific behavior for different -- styles of Rate specifications is documented under Rate. -- The effective maximum production rate achieved by a stream is governed -- by: -- -- -- -- Since: 0.5.0 (Streamly) rate :: IsStream t => Maybe Rate -> t m a -> t m a -- | Same as rate (Just $ Rate (r/2) r (2*r) maxBound) -- -- Specifies the average production rate of a stream in number of yields -- per second (i.e. Hertz). Concurrent production is ramped up -- or down automatically to achieve the specified average yield rate. The -- rate can go down to half of the specified rate on the lower side and -- double of the specified rate on the higher side. -- -- Since: 0.5.0 (Streamly) avgRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate r r (2*r) maxBound) -- -- Specifies the minimum rate at which the stream should yield values. As -- far as possible the yield rate would never be allowed to go below the -- specified rate, even though it may possibly go above it at times, the -- upper limit is double of the specified rate. -- -- Since: 0.5.0 (Streamly) minRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate (r/2) r r maxBound) -- -- Specifies the maximum rate at which the stream should yield values. As -- far as possible the yield rate would never be allowed to go above the -- specified rate, even though it may possibly go below it at times, the -- lower limit is half of the specified rate. This can be useful in -- applications where certain resource usage must not be allowed to go -- beyond certain limits. -- -- Since: 0.5.0 (Streamly) maxRate :: IsStream t => Double -> t m a -> t m a -- | Same as rate (Just $ Rate r r r 0) -- -- Specifies a constant yield rate. If for some reason the actual rate -- goes above or below the specified rate we do not try to recover it by -- increasing or decreasing the rate in future. This can be useful in -- applications like graphics frame refresh where we need to maintain a -- constant refresh rate. -- -- Since: 0.5.0 (Streamly) constRate :: IsStream t => Double -> t m a -> t m a -- | Class of types that can represent a stream of elements of some type -- a in some monad m. -- -- Since: 0.2.0 (Streamly) class (forall m a. MonadAsync m => Semigroup (t m a), forall m a. MonadAsync m => Monoid (t m a), forall m. Monad m => Functor (t m), forall m. MonadAsync m => Applicative (t m)) => IsStream t serially :: IsStream t => SerialT m a -> t m a wSerially :: IsStream t => WSerialT m a -> t m a asyncly :: IsStream t => AsyncT m a -> t m a aheadly :: IsStream t => AheadT m a -> t m a wAsyncly :: IsStream t => WAsyncT m a -> t m a parallely :: IsStream t => ParallelT m a -> t m a zipSerially :: IsStream t => ZipSerialM m a -> t m a zipAsyncly :: IsStream t => ZipAsyncM m a -> t m a -- | Adapt any specific stream type to any other specific stream type. -- -- Since: 0.1.0 (Streamly) adapt :: (IsStream t1, IsStream t2) => t1 m a -> t2 m a -- | A serial IO stream of elements of type a. See SerialT -- documentation for more details. -- -- Since: 0.2.0 (Streamly) type Serial = SerialT IO -- | An interleaving serial IO stream of elements of type a. See -- WSerialT documentation for more details. -- -- Since: 0.2.0 (Streamly) type WSerial = WSerialT IO -- | A serial IO stream of elements of type a with concurrent -- lookahead. See AheadT documentation for more details. -- -- Since: 0.3.0 (Streamly) type Ahead = AheadT IO -- | A demand driven left biased parallely composing IO stream of elements -- of type a. See AsyncT documentation for more details. -- -- Since: 0.2.0 (Streamly) type Async = AsyncT IO -- | A round robin parallely composing IO stream of elements of type -- a. See WAsyncT documentation for more details. -- -- Since: 0.2.0 (Streamly) type WAsync = WAsyncT IO -- | A parallely composing IO stream of elements of type a. See -- ParallelT documentation for more details. -- -- Since: 0.2.0 (Streamly) type Parallel = ParallelT IO -- | An IO stream whose applicative instance zips streams serially. -- -- Since: 0.2.0 (Streamly) type ZipSerial = ZipSerialM IO -- | An IO stream whose applicative instance zips streams wAsyncly. -- -- Since: 0.2.0 (Streamly) type ZipAsync = ZipAsyncM IO -- | Same as concatFoldableWith foldWith :: (IsStream t, Foldable f) => (t m a -> t m a -> t m a) -> f (t m a) -> t m a -- | Same as concatMapFoldableWith foldMapWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b -- | Same as concatForFoldableWith forEachWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b -- | The class of semigroups (types with an associative binary operation). -- -- Instances should satisfy the following: -- -- class Semigroup a -- | An associative operation. -- --
--   >>> [1,2,3] <> [4,5,6]
--   [1,2,3,4,5,6]
--   
(<>) :: Semigroup a => a -> a -> a -- | Reduce a non-empty list with <> -- -- The default definition should be sufficient, but this can be -- overridden for efficiency. -- --
--   >>> import Data.List.NonEmpty
--   
--   >>> sconcat $ "Hello" :| [" ", "Haskell", "!"]
--   "Hello Haskell!"
--   
sconcat :: Semigroup a => NonEmpty a -> a -- | Repeat a value n times. -- -- Given that this works on a Semigroup it is allowed to fail if -- you request 0 or fewer repetitions, and the default definition will do -- so. -- -- By making this a member of the class, idempotent semigroups and -- monoids can upgrade this to execute in <math> by picking -- stimes = stimesIdempotent or stimes = -- stimesIdempotentMonoid respectively. -- --
--   >>> stimes 4 [1]
--   [1,1,1,1]
--   
stimes :: (Semigroup a, Integral b) => b -> a -> a infixr 6 <> -- | Same as IsStream. -- | Deprecated: Please use IsStream instead. type Streaming = IsStream -- | Same as "Streamly.Prelude.runStream". runStream :: Monad m => SerialT m a -> m () -- | Same as runStream runStreaming :: (Monad m, IsStream t) => t m a -> m () -- | Same as runStream. runStreamT :: Monad m => SerialT m a -> m () -- | Same as drain . fromWSerial. runInterleavedT :: Monad m => WSerialT m a -> m () -- | Same as drain . fromAsync. runAsyncT :: Monad m => AsyncT m a -> m () -- | Same as drain . fromParallel. runParallelT :: Monad m => ParallelT m a -> m () -- | Same as drain . zipping. runZipStream :: Monad m => ZipSerialM m a -> m () -- | Same as drain . zippingAsync. runZipAsync :: Monad m => ZipAsyncM m a -> m () -- | Deprecated: Please use SerialT instead. type StreamT = SerialT -- | Deprecated: Please use WSerialT instead. type InterleavedT = WSerialT -- | Deprecated: Please use ZipSerialM instead. type ZipStream = ZipSerialM -- | Same as fromWSerial. -- | Deprecated: Please use fromWSerial instead. interleaving :: IsStream t => WSerialT m a -> t m a -- | Same as fromZipSerial. -- | Deprecated: Please use fromZipSerial instead. zipping :: IsStream t => ZipSerialM m a -> t m a -- | Same as fromZipAsync. -- | Deprecated: Please use fromZipAsync instead. zippingAsync :: IsStream t => ZipAsyncM m a -> t m a -- | Same as wSerial. -- | Deprecated: Please use wSerial instead. (<=>) :: IsStream t => t m a -> t m a -> t m a infixr 5 <=> -- | Same as async. -- | Deprecated: Please use async instead. (<|) :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- |

Processing Unicode Strings

-- -- A Char stream is the canonical representation to process -- Unicode strings. It can be processed efficiently using regular stream -- processing operations. A byte stream of Unicode text read from an IO -- device or from an Array in memory can be decoded into a -- Char stream using the decoding routines in this module. A -- String ([Char]) can be converted into a Char -- stream using fromList. An Array Char can be -- unfolded into a stream using the array read unfold. -- --

Storing Unicode Strings

-- -- A stream of Char can be encoded into a byte stream using the -- encoding routines in this module and then written to IO devices or to -- arrays in memory. -- -- If you have to store a Char stream in memory you can convert it -- into a String using toList or using the toList -- fold. The String type can be more efficient than pinned arrays -- for short and short lived strings. -- -- For longer or long lived streams you can fold the Char -- stream as Array Char using the array write fold. The -- Array type provides a more compact representation and pinned -- memory reducing GC overhead. If space efficiency is a concern you can -- use encodeUtf8' on the Char stream before writing it to -- an Array providing an even more compact representation. -- --

String Literals

-- -- SerialT Identity Char and Array Char are instances -- of IsString and IsList, therefore, -- OverloadedStrings and OverloadedLists extensions can -- be used for convenience when specifying unicode strings literals using -- these types. -- --

Idioms

-- -- Some simple text processing operations can be represented simply as -- operations on Char streams. Follow the links for the following idioms: -- -- -- --

Pitfalls

-- -- -- --

Experimental APIs

-- -- Some experimental APIs to conveniently process text using the -- Array Char represenation directly can be found in -- Streamly.Internal.Unicode.Array.Char. module Streamly.Unicode.Stream -- | Decode a stream of bytes to Unicode characters by mapping each byte to -- a corresponding Unicode Char in 0-255 range. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) decodeLatin1 :: (IsStream t, Monad m) => t m Word8 -> t m Char -- | Decode a UTF-8 encoded bytestream to a stream of Unicode characters. -- Any invalid codepoint encountered is replaced with the unicode -- replacement character. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) -- -- Since: 0.8.0 (Lenient Behaviour) decodeUtf8 :: (Monad m, IsStream t) => t m Word8 -> t m Char -- | Decode a UTF-8 encoded bytestream to a stream of Unicode characters. -- The function throws an error if an invalid codepoint is encountered. decodeUtf8' :: (Monad m, IsStream t) => t m Word8 -> t m Char -- | Like encodeLatin1' but silently maps input codepoints beyond -- 255 to arbitrary Latin1 chars in 0-255 range. No error or exception is -- thrown when such mapping occurs. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) -- -- Since: 0.8.0 (Lenient Behaviour) encodeLatin1 :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Encode a stream of Unicode characters to bytes by mapping each -- character to a byte in 0-255 range. Throws an error if the input -- stream contains characters beyond 255. encodeLatin1' :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Encode a stream of Unicode characters to a UTF-8 encoded bytestream. -- Any Invalid characters (U+D800-U+D8FF) in the input stream are -- replaced by the Unicode replacement character U+FFFD. -- -- Since: 0.7.0 (Streamly.Data.Unicode.Stream) -- -- Since: 0.8.0 (Lenient Behaviour) encodeUtf8 :: (Monad m, IsStream t) => t m Char -> t m Word8 -- | Encode a stream of Unicode characters to a UTF-8 encoded bytestream. -- When any invalid character (U+D800-U+D8FF) is encountered in the input -- stream the function errors out. encodeUtf8' :: (Monad m, IsStream t) => t m Char -> t m Word8 -- | Encode a stream of String using the supplied encoding scheme. -- Each string is encoded as an Array Word8. encodeStrings :: (MonadIO m, IsStream t) => (SerialT m Char -> SerialT m Word8) -> t m String -> t m (Array Word8)