-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Beautiful Streaming, Concurrent and Reactive Composition -- -- Streamly is a framework for writing programs in a high level, -- declarative data flow programming paradigm. It provides a simple API, -- very close to standard Haskell lists. A program is expressed as a -- composition of data processing pipes, generally known as streams. -- Streams can be generated, merged, chained, mapped, zipped, and -- consumed concurrently – enabling a high level, declarative yet -- concurrent composition of programs. Programs can be concurrent or -- non-concurrent without any significant change. Concurrency is auto -- scaled based on consumption rate. Programmers do not have to be aware -- of threads, locking or synchronization to write scalable concurrent -- programs. Streamly provides C like performance, orders of magnitude -- better compared to existing streaming libraries. -- -- Streamly is designed to express the full spectrum of programs with -- highest performance. Do not think that if you are writing a small and -- simple program it may not be for you. It expresses a small "hello -- world" program with the same efficiency, simplicity and elegance as a -- large scale concurrent application. It unifies many different aspects -- of special purpose libraries into a single yet simple framework. -- -- Streamly covers the functionality provided by Haskell lists as well as -- the functionality provided by streaming libraries like -- streaming, pipes, and conduit with a simpler API -- and better performance. Streamly provides advanced stream composition -- including various ways of appending, merging, zipping, splitting, -- grouping, distributing, partitioning and unzipping of streams with -- true streaming and with concurrency. Streamly subsumes the -- functionality of list transformer libraries like pipes or -- list-t and also the logic programming library logict. -- The grouping, splitting and windowing combinators in streamly can be -- compared to the window operators in Apache Flink. However, -- compared to Flink streamly has a pure functional, succinct and -- expressive API. -- -- The concurrency capabilities of streamly are much more advanced and -- powerful compared to the basic concurrency functionality provided by -- the async package. Streamly is a first class reactive -- programming library. If you are familiar with Reactive -- Extensions you will find that it is very similar. For most RxJs -- combinators you can find or write corresponding ones in streamly. -- Streamly can be used as an alternative to Yampa or -- reflex as well. -- -- Streamly focuses on practical engineering with high performance. From -- well written streamly programs one can expect performance competitive -- to C. High performance streaming eliminates the need for string and -- text libraries like bytestring, text and their lazy and -- strict flavors. The confusion and cognitive overhead arising from -- different string types is eliminated. The two fundamental types in -- streamly are arrays for storage and streams for processing. Strings -- and text are simply streams or arrays of Char as they should -- be. Arrays in streamly have performance at par with the vector -- library. -- -- Where to find more information: -- -- @package streamly @version 0.7.3.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 -- | Additional Control.Monad utilities. module Streamly.Internal.Control.Monad -- | Discard any exceptions or value returned by an effectful action. -- -- Internal 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 () -- | Arrays of unboxed primitive types. The function provided by this -- module match the behavior of those provided by -- Data.Primitive.ByteArray, and the underlying types and -- primops that back them are the same. However, the type constructors -- PrimArray and MutablePrimArray take one additional -- argument than their respective counterparts ByteArray and -- MutableByteArray. This argument is used to designate the type -- of element in the array. Consequently, all function this modules -- accepts length and incides in terms of elements, not bytes. module Streamly.Internal.Data.Prim.Array.Types -- | Arrays of unboxed elements. This accepts types like Double, -- Char, Int, and Word, as well as their -- fixed-length variants (Word8, Word16, etc.). Since -- the elements are unboxed, a PrimArray is strict in its -- elements. This differs from the behavior of Array, which is -- lazy in its elements. data PrimArray a PrimArray :: ByteArray# -> PrimArray a -- | Mutable primitive arrays associated with a primitive state token. -- These can be written to and read from in a monadic context that -- supports sequencing such as IO or ST. Typically, a -- mutable primitive array will be built and then convert to an immutable -- primitive array using unsafeFreezePrimArray. However, it is -- also acceptable to simply discard a mutable primitive array since it -- lives in managed memory and will be garbage collected when no longer -- referenced. data MutablePrimArray s a MutablePrimArray :: MutableByteArray# s -> MutablePrimArray s a -- | Create a new mutable primitive array of the given length. The -- underlying memory is left uninitialized. newPrimArray :: forall m a. (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) -- | Resize a mutable primitive array. The new size is given in elements. -- -- This will either resize the array in-place or, if not possible, -- allocate the contents into a new, unpinned array and copy the original -- array's contents. -- -- To avoid undefined behaviour, the original MutablePrimArray -- shall not be accessed anymore after a resizeMutablePrimArray -- has been performed. Moreover, no reference to the old one should be -- kept in order to allow garbage collection of the original -- MutablePrimArray in case a new MutablePrimArray had to -- be allocated. resizeMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> m (MutablePrimArray (PrimState m) a) -- | Shrink a mutable primitive array. The new size is given in elements. -- It must be smaller than the old size. The array will be resized in -- place. This function is only available when compiling with GHC 7.10 or -- newer. shrinkMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> m () -- | Write an element to the given index. writePrimArray :: (Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -> Int -> a -> m () -- | Read a primitive value from the primitive array. indexPrimArray :: forall a. Prim a => PrimArray a -> Int -> a -- | Convert a mutable byte array to an immutable one without copying. The -- array should not be modified after the conversion. unsafeFreezePrimArray :: PrimMonad m => MutablePrimArray (PrimState m) a -> m (PrimArray a) -- | Get the size, in elements, of the primitive array. sizeofPrimArray :: forall a. Prim a => PrimArray a -> Int -- | Lazy right-associated fold over the elements of a PrimArray. foldrPrimArray :: forall a b. Prim a => (a -> b -> b) -> b -> PrimArray a -> b -- | Strict left-associated fold over the elements of a PrimArray. foldlPrimArray' :: forall a b. Prim a => (b -> a -> b) -> b -> PrimArray a -> b instance (GHC.Classes.Eq a, Data.Primitive.Types.Prim a) => GHC.Classes.Eq (Streamly.Internal.Data.Prim.Array.Types.PrimArray a) instance (GHC.Classes.Ord a, Data.Primitive.Types.Prim a) => GHC.Classes.Ord (Streamly.Internal.Data.Prim.Array.Types.PrimArray a) instance (GHC.Show.Show a, Data.Primitive.Types.Prim a) => GHC.Show.Show (Streamly.Internal.Data.Prim.Array.Types.PrimArray a) module Streamly.Internal.Data.Sink.Types -- | 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. data 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.Types 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.Types.SmallArray instance GHC.Classes.Eq (Streamly.Internal.Data.SmallArray.Types.SmallMutableArray s a) instance (Data.Typeable.Internal.Typeable s, Data.Typeable.Internal.Typeable a) => Data.Data.Data (Streamly.Internal.Data.SmallArray.Types.SmallMutableArray s a) instance Data.Functor.Classes.Eq1 Streamly.Internal.Data.SmallArray.Types.SmallArray instance GHC.Classes.Eq a => GHC.Classes.Eq (Streamly.Internal.Data.SmallArray.Types.SmallArray a) instance Data.Functor.Classes.Ord1 Streamly.Internal.Data.SmallArray.Types.SmallArray instance GHC.Classes.Ord a => GHC.Classes.Ord (Streamly.Internal.Data.SmallArray.Types.SmallArray a) instance Data.Foldable.Foldable Streamly.Internal.Data.SmallArray.Types.SmallArray instance Data.Traversable.Traversable Streamly.Internal.Data.SmallArray.Types.SmallArray instance GHC.Base.Functor Streamly.Internal.Data.SmallArray.Types.SmallArray instance GHC.Base.Applicative Streamly.Internal.Data.SmallArray.Types.SmallArray instance GHC.Base.Alternative Streamly.Internal.Data.SmallArray.Types.SmallArray instance Control.Monad.Fail.MonadFail Streamly.Internal.Data.SmallArray.Types.SmallArray instance GHC.Base.MonadPlus Streamly.Internal.Data.SmallArray.Types.SmallArray instance Control.Monad.Zip.MonadZip Streamly.Internal.Data.SmallArray.Types.SmallArray instance Control.Monad.Fix.MonadFix Streamly.Internal.Data.SmallArray.Types.SmallArray instance GHC.Base.Semigroup (Streamly.Internal.Data.SmallArray.Types.SmallArray a) instance GHC.Base.Monoid (Streamly.Internal.Data.SmallArray.Types.SmallArray a) instance GHC.Exts.IsList (Streamly.Internal.Data.SmallArray.Types.SmallArray a) instance GHC.Show.Show a => GHC.Show.Show (Streamly.Internal.Data.SmallArray.Types.SmallArray a) instance Data.Functor.Classes.Show1 Streamly.Internal.Data.SmallArray.Types.SmallArray instance GHC.Read.Read a => GHC.Read.Read (Streamly.Internal.Data.SmallArray.Types.SmallArray a) instance Data.Functor.Classes.Read1 Streamly.Internal.Data.SmallArray.Types.SmallArray instance Data.Data.Data a => Data.Data.Data (Streamly.Internal.Data.SmallArray.Types.SmallArray 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 data 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 () -- | | 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.Strict data Tuple' a b Tuple' :: !a -> !b -> Tuple' a b data Tuple3' a b c Tuple3' :: !a -> !b -> !c -> Tuple3' a b c data Tuple4' a b c d Tuple4' :: !a -> !b -> !c -> !d -> Tuple4' a b c d -- | A strict Maybe data Maybe' a Just' :: !a -> Maybe' a Nothing' :: Maybe' a -- | Convert strict Maybe' to lazy Maybe toMaybe :: Maybe' a -> Maybe a -- | A strict Either data Either' a b Left' :: !a -> Either' a b Right' :: !b -> Either' a b instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Streamly.Internal.Data.Strict.Tuple' a b) instance (GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show c) => GHC.Show.Show (Streamly.Internal.Data.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.Strict.Tuple4' a b c d) instance GHC.Show.Show a => GHC.Show.Show (Streamly.Internal.Data.Strict.Maybe' a) instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (Streamly.Internal.Data.Strict.Either' a b) module Streamly.Internal.Data.Pipe.Types 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.Types.Pipe m a) instance GHC.Base.Monad m => GHC.Base.Applicative (Streamly.Internal.Data.Pipe.Types.Pipe m a) instance GHC.Base.Monad m => GHC.Base.Semigroup (Streamly.Internal.Data.Pipe.Types.Pipe m a b) instance GHC.Base.Monad m => Control.Category.Category (Streamly.Internal.Data.Pipe.Types.Pipe m) instance GHC.Base.Monad m => Control.Arrow.Arrow (Streamly.Internal.Data.Pipe.Types.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 P
--   
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 -- | 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.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 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 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 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.TimeSpec instance GHC.Read.Read Streamly.Internal.Data.Time.Units.TimeSpec instance GHC.Classes.Eq Streamly.Internal.Data.Time.Units.TimeSpec 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.Units.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 instance GHC.Classes.Ord Streamly.Internal.Data.Time.Units.TimeSpec instance GHC.Num.Num Streamly.Internal.Data.Time.Units.TimeSpec 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 instance GHC.Show.Show Streamly.Internal.Data.Time.Clock.Clock instance GHC.Read.Read Streamly.Internal.Data.Time.Clock.Clock instance GHC.Generics.Generic Streamly.Internal.Data.Time.Clock.Clock instance GHC.Enum.Enum Streamly.Internal.Data.Time.Clock.Clock instance GHC.Classes.Eq Streamly.Internal.Data.Time.Clock.Clock instance Foreign.Storable.Storable Streamly.Internal.Data.Time.Units.TimeSpec module Streamly.Internal.Data.SVar -- | A monad that can perform concurrent or parallel IO operations. Streams -- that can be composed concurrently require the underlying monad to be -- MonadAsync. type MonadAsync m = (MonadIO m, MonadBaseControl IO m, MonadThrow m) -- | 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 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 -> (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 -> 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) data Limit Unlimited :: Limit Limited :: Word -> Limit data State t m a 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 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 recordMaxWorkers :: MonadIO m => SVar t m a -> m () cleanupSVar :: SVar t m a -> IO () cleanupSVarFromWorker :: SVar t m a -> IO () 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) newParallelVar :: MonadAsync m => SVarStopStyle -> State t m a -> m (SVar t m a) captureMonadState :: MonadBaseControl IO m => m (RunInIO 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) -- | 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) 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 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 :: t m a -> AheadHeapEntry (t :: (Type -> Type) -> Type -> Type) m a -- | 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 sendToProducer :: SVar t m a -> ChildEvent a -> IO Int sendYield :: SVar t m a -> Maybe WorkerInfo -> ChildEvent a -> IO Bool sendStop :: SVar t m a -> Maybe WorkerInfo -> IO () sendStopToProducer :: MonadIO m => SVar t m a -> m () enqueueLIFO :: SVar t m a -> IORef [t m a] -> t m a -> IO () enqueueFIFO :: SVar t m a -> LinkedQueue (t m a) -> t m a -> IO () enqueueAhead :: SVar t m a -> IORef ([t m a], Int) -> t m a -> IO () reEnqueueAhead :: SVar t m a -> IORef ([t m a], Int) -> t m a -> IO () -- | 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 () handleChildException :: SVar t m a -> SomeException -> IO () handleFoldException :: SVar t m a -> SomeException -> 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 -- | 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. 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 getYieldRateInfo :: State t m a -> IO (Maybe YieldRateInfo) newSVarStats :: IO SVarStats collectLatency :: SVar t m a -> YieldRateInfo -> Bool -> IO (Count, AbsTime, NanoSecond64) workerUpdateLatency :: YieldRateInfo -> WorkerInfo -> IO () isBeyondMaxRate :: SVar t m a -> YieldRateInfo -> IO Bool workerRateControl :: SVar t m a -> YieldRateInfo -> WorkerInfo -> IO Bool updateYieldCount :: WorkerInfo -> IO Count 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 () postProcessBounded :: MonadAsync m => SVar t m a -> m Bool postProcessPaced :: MonadAsync m => SVar t m a -> m Bool readOutputQBounded :: MonadAsync m => SVar t m a -> m [ChildEvent a] readOutputQPaced :: MonadAsync m => SVar t m a -> m [ChildEvent a] readOutputQBasic :: IORef ([ChildEvent a], Int) -> IO ([ChildEvent a], Int) dispatchWorkerPaced :: MonadAsync m => SVar t m a -> m Bool sendFirstWorker :: MonadAsync m => SVar t m a -> t m a -> m (SVar t m a) delThread :: MonadIO m => SVar t m a -> ThreadId -> m () modifyThread :: MonadIO m => SVar t m a -> ThreadId -> m () doFork :: MonadBaseControl IO m => m () -> RunInIO m -> (SomeException -> IO ()) -> m ThreadId 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 -- | Write a stream to an SVar in a non-blocking manner. The stream -- can then be read back from the SVar using fromSVar. toStreamVar :: MonadAsync m => SVar t m a -> t m a -> m () 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) dumpSVar :: SVar t m a -> IO String printSVar :: SVar t m a -> String -> IO () withDiagMVar :: SVar t m a -> String -> IO () -> IO () instance GHC.Classes.Ord Streamly.Internal.Data.SVar.Count instance GHC.Real.Integral Streamly.Internal.Data.SVar.Count instance GHC.Real.Real Streamly.Internal.Data.SVar.Count instance GHC.Num.Num Streamly.Internal.Data.SVar.Count instance GHC.Enum.Bounded Streamly.Internal.Data.SVar.Count instance GHC.Enum.Enum Streamly.Internal.Data.SVar.Count instance GHC.Show.Show Streamly.Internal.Data.SVar.Count instance GHC.Read.Read Streamly.Internal.Data.SVar.Count instance GHC.Classes.Eq Streamly.Internal.Data.SVar.Count instance GHC.Show.Show Streamly.Internal.Data.SVar.ThreadAbort instance GHC.Show.Show Streamly.Internal.Data.SVar.SVarStyle instance GHC.Classes.Eq Streamly.Internal.Data.SVar.SVarStyle instance GHC.Show.Show Streamly.Internal.Data.SVar.LatencyRange instance GHC.Show.Show Streamly.Internal.Data.SVar.Limit instance GHC.Show.Show Streamly.Internal.Data.SVar.SVarStopStyle instance GHC.Classes.Eq Streamly.Internal.Data.SVar.SVarStopStyle instance GHC.Show.Show Streamly.Internal.Data.SVar.Work instance GHC.Classes.Eq Streamly.Internal.Data.SVar.Limit instance GHC.Classes.Ord Streamly.Internal.Data.SVar.Limit instance GHC.Exception.Type.Exception Streamly.Internal.Data.SVar.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 -- | Class of types that can represent a stream of elements of some type -- a in some monad m. 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 parallely 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 $ serially  $ delay |: delay |: delay |: nil
--   drain $ parallely $ delay |: delay |: delay |: nil
--   
-- -- Concurrent (do not use parallely to construct infinite -- streams) (|:) :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 `consM` infixr 5 |: -- | Adapt any specific stream type to any other specific stream type. adapt :: (IsStream t1, IsStream t2) => t1 m a -> t2 m a -- | 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. -- -- XXX remove the Stream type parameter from State as it is always -- constant. We can remove it from SVar as well 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 -- | 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 -- | Make an empty stream from a stop function. fromStopK :: IsStream t => StopK m -> t m a -- | Make a singleton stream from a callback function. The callback -- function calls the one-shot yield continuation to yield an element. fromYieldK :: IsStream t => YieldK m a -> t m a -- | Add a yield function at the head of the stream. consK :: IsStream t => YieldK m a -> t m a -> t 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 :: 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 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 -- | Lazy right fold with a monadic step function. foldrM :: IsStream t => (a -> m b -> m b) -> m b -> t m a -> m b -- | Lazy right associative fold to a stream. foldrS :: IsStream t => (a -> t m b -> t m b) -> t m b -> t m a -> t m b foldrSM :: (IsStream t, Monad m) => (m a -> t m b -> t m b) -> t m b -> t m a -> t m b build :: IsStream t => forall a. (forall b. (a -> b -> b) -> b -> b) -> t m a buildS :: IsStream t => ((a -> t m a -> t m a) -> t m a -> t m a) -> t m a buildM :: (IsStream t, MonadAsync m) => (forall r. (a -> t m a -> m r) -> (a -> m r) -> m r -> m r) -> t m a buildSM :: (IsStream t, MonadAsync m) => ((m a -> t m a -> t m a) -> t m a -> t m a) -> t m a -- | Like buildM but shares the SVar state across computations. sharedM :: (IsStream t, MonadAsync m) => (forall r. (a -> t m a -> m r) -> (a -> m r) -> m r -> m r) -> t m a augmentS :: IsStream t => ((a -> t m a -> t m a) -> t m a -> t m a) -> t m a -> t m a augmentSM :: (IsStream t, MonadAsync m) => ((m a -> t m a -> t m a) -> t m a -> t m a) -> t 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 .: consMStream :: Monad m => m a -> Stream m a -> Stream m a consMBy :: (IsStream t, MonadAsync m) => (t m a -> t m a -> t m a) -> m a -> t m a -> t m a yieldM :: (Monad m, IsStream t) => m a -> t m a yield :: IsStream t => a -> t m a -- | An empty stream. -- --
--   > toList nil
--   []
--   
nil :: IsStream t => t m a -- | An empty stream producing a side effect. -- --
--   > toList (nilM (print "nil"))
--   "nil"
--   []
--   
-- -- Internal nilM :: (IsStream t, Monad m) => m b -> t m a conjoin :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | Polymorphic version of the Semigroup operation <> -- of SerialT. Appends two streams sequentially, yielding all -- elements from the first stream, and then all elements from the second -- stream. serial :: IsStream t => t m a -> t m a -> t m a map :: IsStream t => (a -> b) -> t m a -> t m b mapM :: (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m b mapMSerial :: MonadAsync m => (a -> m b) -> Stream m a -> Stream m b -- | Detach a stream from an SVar unShare :: IsStream t => t m a -> t 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. concatMapBy :: IsStream t => (forall c. t m c -> t m c -> t m c) -> (a -> t m b) -> t m a -> t m b concatMap :: IsStream t => (a -> t m b) -> t m a -> t m b bindWith :: IsStream t => (forall c. t m c -> t m c -> t m c) -> t m a -> (a -> t m b) -> t m b -- | Same as IsStream. -- | Deprecated: Please use IsStream instead. type Streaming = IsStream instance Streamly.Internal.Data.Stream.StreamK.Type.IsStream Streamly.Internal.Data.Stream.StreamK.Type.Stream 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) -- | 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 -- | Class of types that can represent a stream of elements of some type -- a in some monad m. 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 parallely 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 $ serially  $ delay |: delay |: delay |: nil
--   drain $ parallely $ delay |: delay |: delay |: nil
--   
-- -- Concurrent (do not use parallely to construct infinite -- streams) (|:) :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 `consM` infixr 5 |: -- | Adapt any specific stream type to any other specific stream type. adapt :: (IsStream t1, IsStream t2) => t1 m a -> t2 m a -- | 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. -- -- XXX remove the Stream type parameter from State as it is always -- constant. We can remove it from SVar as well 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 -- | 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 -- | An empty stream. -- --
--   > toList nil
--   []
--   
nil :: IsStream t => t m a -- | An empty stream producing a side effect. -- --
--   > toList (nilM (print "nil"))
--   "nil"
--   []
--   
-- -- Internal 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 .: -- | 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 -- | 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 -- | Detach a stream from an SVar unShare :: IsStream t => t m a -> t m a uncons :: (IsStream t, Monad m) => t m a -> m (Maybe (a, t m a)) unfoldr :: IsStream t => (b -> Maybe (a, b)) -> b -> t m a unfoldrM :: (IsStream t, MonadAsync m) => (b -> m (Maybe (a, b))) -> b -> t m a repeat :: IsStream t => a -> t m a -- |
--   repeatM = fix . cons
--   repeatM = cycle1 . yield
--   
-- -- Generate an infinite stream by repeating a monadic value. -- -- Internal repeatM :: (IsStream t, MonadAsync m) => m a -> t m a replicate :: IsStream t => Int -> a -> t m a replicateM :: (IsStream t, MonadAsync m) => Int -> m a -> t m a fromIndices :: IsStream t => (Int -> a) -> t m a fromIndicesM :: (IsStream t, MonadAsync m) => (Int -> m a) -> t m a iterate :: IsStream t => (a -> a) -> a -> t m a iterateM :: (IsStream t, MonadAsync m) => (a -> m a) -> m a -> t m a yield :: IsStream t => a -> t m a yieldM :: (Monad m, IsStream t) => m a -> t m a -- |
--   fromFoldable = foldr cons nil
--   
-- -- Construct a stream from a Foldable containing pure values: fromFoldable :: (IsStream t, Foldable f) => f a -> t m a fromList :: IsStream t => [a] -> t m a fromStreamK :: IsStream t => Stream m a -> t m a -- | Lazy right associative fold to a stream. foldrS :: IsStream t => (a -> t m b -> t m b) -> t m b -> t m a -> t m b foldrSM :: (IsStream t, Monad m) => (m a -> t m b -> t m b) -> t m b -> t m a -> t m b buildS :: IsStream t => ((a -> t m a -> t m a) -> t m a -> t m a) -> t m a buildM :: (IsStream t, MonadAsync m) => (forall r. (a -> t m a -> m r) -> (a -> m r) -> m r -> m r) -> t m a augmentS :: IsStream t => ((a -> t m a -> t m a) -> t m a -> t m a) -> t m a -> t m a augmentSM :: (IsStream t, MonadAsync m) => ((m a -> t m a -> t m a) -> t m a -> t m a) -> t m a -> t m a -- | Lazy right associative fold. foldr :: (IsStream t, Monad m) => (a -> b -> b) -> b -> t m a -> m b foldr1 :: (IsStream t, Monad m) => (a -> a -> a) -> t m a -> m (Maybe a) -- | Lazy right fold with a monadic step function. foldrM :: IsStream t => (a -> m b -> m b) -> m b -> t m a -> m b -- | Right associative fold to an arbitrary transformer monad. 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 -- | Strict left associative fold. foldl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> m b -- | Like foldl' but with a monadic step function. foldlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> b -> t 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 an arbitrary transformer monad. foldlT :: (IsStream t, Monad m, Monad (s m), MonadTrans s) => (s m b -> a -> s m b) -> s m b -> t 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 t m a b x. (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> m b -- | Like foldx, 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 -- |
--   drain = foldl' (\_ _ -> ()) ()
--   drain = mapM_ (\_ -> return ())
--   
drain :: (Monad m, IsStream t) => t m a -> m () null :: (IsStream t, Monad m) => t m a -> m Bool head :: (IsStream t, Monad m) => t m a -> m (Maybe a) tail :: (IsStream t, Monad m) => t m a -> m (Maybe (t m a)) init :: (IsStream t, Monad m) => t m a -> m (Maybe (t m a)) elem :: (IsStream t, Monad m, Eq a) => a -> t m a -> m Bool notElem :: (IsStream t, Monad m, Eq a) => a -> t m a -> m Bool all :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> m Bool any :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> m Bool -- | Extract the last element of the stream, if any. last :: (IsStream t, Monad m) => t m a -> m (Maybe a) minimum :: (IsStream t, Monad m, Ord a) => t m a -> m (Maybe a) minimumBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> t m a -> m (Maybe a) maximum :: (IsStream t, Monad m, Ord a) => t m a -> m (Maybe a) maximumBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> t m a -> m (Maybe a) findIndices :: IsStream t => (a -> Bool) -> t m a -> t m Int lookup :: (IsStream t, Monad m, Eq a) => a -> t m (a, b) -> m (Maybe b) findM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> m (Maybe a) find :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> m (Maybe a) (!!) :: (IsStream t, Monad m) => t m a -> Int -> m (Maybe a) -- | Apply a monadic action to each element of the stream and discard the -- output of the action. mapM_ :: (IsStream t, Monad m) => (a -> m b) -> t m a -> m () toList :: (IsStream t, Monad m) => t m a -> m [a] toStreamK :: Stream m a -> Stream m a hoist :: (IsStream t, Monad m, Monad n) => (forall x. m x -> n x) -> t m a -> t n a scanl' :: IsStream t => (b -> a -> b) -> b -> t m a -> t m b scanlx' :: IsStream t => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b filter :: IsStream t => (a -> Bool) -> t m a -> t m a take :: IsStream t => Int -> t m a -> t m a takeWhile :: IsStream t => (a -> Bool) -> t m a -> t m a drop :: IsStream t => Int -> t m a -> t m a dropWhile :: IsStream t => (a -> Bool) -> t m a -> t m a map :: IsStream t => (a -> b) -> t m a -> t m b mapM :: (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m b mapMSerial :: MonadAsync m => (a -> m b) -> Stream m a -> Stream m b sequence :: (IsStream t, MonadAsync m) => t m (m a) -> t m a intersperseM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a intersperse :: (IsStream t, MonadAsync m) => a -> t m a -> t m a insertBy :: IsStream t => (a -> a -> Ordering) -> a -> t m a -> t m a deleteBy :: IsStream t => (a -> a -> Bool) -> a -> t m a -> t m a reverse :: IsStream t => t m a -> t m a mapMaybe :: IsStream t => (a -> Maybe b) -> t m a -> t m b -- | Zip two streams serially using a pure zipping function. zipWith :: IsStream t => (a -> b -> c) -> t m a -> t m b -> t m c -- | Zip two streams serially using a monadic zipping function. zipWithM :: (IsStream t, Monad m) => (a -> b -> m c) -> t m a -> t m b -> t m c mergeBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> t m a -> t m a -> t m a mergeByM :: (IsStream t, Monad m) => (a -> a -> m Ordering) -> t m a -> t m a -> t 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. concatMapBy :: IsStream t => (forall c. t m c -> t m c -> t m c) -> (a -> t m b) -> t m a -> t m b concatMap :: IsStream t => (a -> t m b) -> t m a -> t m b bindWith :: IsStream t => (forall c. t m c -> t m c -> t m c) -> t m a -> (a -> t m b) -> t m b the :: (Eq a, IsStream t, Monad m) => t m a -> m (Maybe a) -- | Polymorphic version of the Semigroup operation <> -- of SerialT. Appends two streams sequentially, yielding all -- elements from the first stream, and then all elements from the second -- stream. serial :: IsStream t => t m a -> t m a -> t m a consMStream :: Monad m => m a -> Stream m a -> Stream m a withLocal :: MonadReader r m => (r -> r) -> Stream m a -> Stream m a -- | Iterate a lazy function f of the shape `m a -> t m a` -- until it gets fully defined i.e. becomes independent of its argument -- action, then return the resulting value of the function (`t m a`). -- -- It can be used to construct a stream that uses a cyclic definition. -- For example: -- --
--   import Streamly.Internal.Prelude as S
--   import System.IO.Unsafe (unsafeInterleaveIO)
--   
--   main = do
--       S.mapM_ print $ S.mfix $ x -> do
--         a <- S.fromList [1,2]
--         b <- S.fromListM [return 3, unsafeInterleaveIO (fmap fst x)]
--         return (a, b)
--   
-- -- Note that the function f must be lazy in its argument, that's -- why we use unsafeInterleaveIO because IO monad is strict. -- -- Internal mfix :: (IsStream t, Monad m) => (m a -> t m a) -> t m a -- | Same as IsStream. -- | Deprecated: Please use IsStream instead. type Streaming = IsStream -- | Same as yieldM -- | Deprecated: Please use yieldM instead. once :: (Monad m, IsStream t) => m a -> t m a module Streamly.Internal.Data.Stream.SVar fromSVar :: (MonadAsync m, IsStream t) => SVar Stream m a -> t m a -- | Pull a stream from an SVar. fromStreamVar :: MonadAsync m => SVar Stream m a -> Stream m a -- | Pull a stream from an SVar. fromProducer :: MonadAsync m => SVar Stream m a -> Stream m a fromConsumer :: MonadAsync m => SVar Stream m a -> m Bool -- | Write a stream to an SVar in a non-blocking manner. The stream -- can then be read back from the SVar using fromSVar. toSVar :: (IsStream t, MonadAsync m) => SVar Stream m a -> t m a -> m () pushToFold :: MonadAsync m => SVar Stream m a -> a -> m Bool -- |

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 always remain partial -- and complete at the same time. It means that we can keep -- adding more input to them or at any time retrieve a consistent result. -- A sum operation is an example of an accumulator. -- -- 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 split style -- composition, as the first one itself will never terminate, therefore, -- the next one will never get to run. -- --

Splitters

-- -- Splitters are accumulators that can terminate. When applied on a -- stream splitters consume part of the stream, thereby, splitting it. -- Splitters can be used in a split style composition where one -- splitter can be applied after the other on an input stream. We can -- apply a splitter repeatedly on an input stream splitting and consuming -- it in fragments. Splitters never fail, therefore, they do not need -- backtracking, but they can lookahead and return unconsumed input. The -- take operation is an example of a splitter. It terminates after -- consuming n items. Coupled with an accumulator it can be used -- to split the stream into chunks of fixed size. -- -- 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 splitter will have to implement a way to return -- unconsumed input to the driver. -- --

Parsers

-- -- Parsers are splitters 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

-- -- We use the Fold type to implement the Accumulator and Splitter -- functionality. Parsers are represented by the Parser type. This -- is a sweet spot to balance ease of use, type safety and performance. -- Using separate Accumulator and Splitter types would encode more -- information in types but it would make ease of use, implementation, -- maintenance effort worse. Combining Accumulator, Splitter 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 Yield or -- Stop. A Yield returns the next intermediate state of -- the fold, a Stop indicates that the fold has terminated and -- returns the final value of the accumulator. -- -- Every Yield 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 Yield 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 Stop. When using this approach, the splitParse -- (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 Yield, -- 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. module Streamly.Internal.Data.Fold.Types -- | Represents a left fold over an input stream consisting of values of -- type a to a single value of type b in Monad -- m. -- -- The fold uses an intermediate state s as accumulator. The -- step function updates the state and returns the new state. -- When the fold is done the final result of the fold is extracted from -- the intermediate state using the extract function. data Fold m a b -- | Fold step initial extract Fold :: (s -> a -> m s) -> m s -> (s -> m b) -> Fold m a b -- | Experimental type to provide a side input to the fold for generating -- the initial state. For example, if we have to fold chunks of a stream -- and write each chunk to a different file, then we can generate the -- file name using a monadic action. This is a generalized version of -- Fold. data Fold2 m c a b -- | Fold step inject extract Fold2 :: (s -> a -> m s) -> (c -> m s) -> (s -> m b) -> Fold2 m c a b -- | Convert more general type Fold2 into a simpler type Fold simplify :: Fold2 m c a b -> c -> Fold m a b -- | Buffers the input stream to a list in the reverse order of the input. -- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using Streamly.Array -- instead. toListRevF :: Monad m => Fold m a [a] -- | (lmap f fold) maps the function f on the input of -- the fold. -- --
--   >>> S.fold (FL.lmap (\x -> x * x) FL.sum) (S.enumerateFromTo 1 100)
--   338350
--   
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. -- --
--   >>> S.fold (lfilter (> 5) FL.sum) [1..10]
--   40
--   
lfilter :: Monad m => (a -> Bool) -> Fold m a r -> Fold m a r -- | Like lfilter but with a monadic predicate. lfilterM :: Monad m => (a -> m Bool) -> Fold m a r -> Fold m a r -- | Transform a fold from a pure input to a Maybe input, consuming -- only Just values. lcatMaybes :: Monad m => Fold m a b -> Fold m (Maybe a) b -- | Take first n elements from the stream and discard the rest. ltake :: Monad m => Int -> Fold m a b -> Fold m a b -- | Takes elements from the input as long as the predicate succeeds. ltakeWhile :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a b -- | Group the input stream into windows of n second each and then fold -- each group using the provided fold function. -- -- For example, we can copy and distribute a stream to multiple folds -- where each fold can group the input differently e.g. by one second, -- one minute and one hour windows respectively and fold each resulting -- stream of folds. -- --
--   -----Fold m a b----|-Fold n a c-|-Fold n a c-|-...-|----Fold m a c
--   
lsessionsOf :: MonadAsync m => Double -> Fold m a b -> Fold m b c -> Fold m a c -- | For every n input items, apply the first fold and supply the result to -- the next fold. lchunksOf :: Monad m => Int -> Fold m a b -> Fold m b c -> Fold m a c lchunksOf2 :: Monad m => Int -> Fold m a b -> Fold2 m x b c -> Fold2 m x a c -- | Modify the fold such that when the fold is done, instead of returning -- the accumulator, it returns a fold. The returned fold starts from -- where we left i.e. it uses the last accumulator value as the initial -- value of the accumulator. Thus we can resume the fold later and feed -- it more input. -- --
--   > do
--       more <- S.fold (FL.duplicate FL.sum) (S.enumerateFromTo 1 10)
--       evenMore <- S.fold (FL.duplicate more) (S.enumerateFromTo 11 20)
--       S.fold evenMore (S.enumerateFromTo 21 30)
--    465
--   
duplicate :: Applicative m => Fold m a b -> Fold m a (Fold m a b) -- | Run the initialization effect of a fold. The returned fold would use -- the value returned by this effect as its initial value. initialize :: Monad m => Fold m a b -> m (Fold m a b) -- | Run one step of a fold and store the accumulator as an initial value -- in the returned fold. runStep :: Monad m => Fold m a b -> a -> m (Fold m a b) instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Fold.Types.Fold m a) instance GHC.Base.Applicative m => GHC.Base.Applicative (Streamly.Internal.Data.Fold.Types.Fold m a) instance (GHC.Base.Semigroup b, GHC.Base.Monad m) => GHC.Base.Semigroup (Streamly.Internal.Data.Fold.Types.Fold m a b) instance (GHC.Base.Semigroup b, GHC.Base.Monoid b, GHC.Base.Monad m) => GHC.Base.Monoid (Streamly.Internal.Data.Fold.Types.Fold m a b) instance (GHC.Base.Monad m, GHC.Num.Num b) => GHC.Num.Num (Streamly.Internal.Data.Fold.Types.Fold m a b) instance (GHC.Base.Monad m, GHC.Real.Fractional b) => GHC.Real.Fractional (Streamly.Internal.Data.Fold.Types.Fold m a b) instance (GHC.Base.Monad m, GHC.Float.Floating b) => GHC.Float.Floating (Streamly.Internal.Data.Fold.Types.Fold m a b) 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 fromStreamK :: Monad m => Stream m a -> Stream m a toStreamK :: Monad m => Stream m a -> Stream m a fromStreamD :: (IsStream t, Monad m) => Stream m a -> t m a 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 -- | Create a singleton Stream from a pure value. yield :: Applicative m => a -> Stream m a -- | Create a singleton Stream from a monadic action. yieldM :: Monad m => 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 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) -> 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 toList :: Monad m => Stream m a -> m [a] -- | Convert a list of pure values to a Stream fromList :: Applicative m => [a] -> Stream 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 take :: Monad m => Int -> Stream m a -> Stream m a data GroupState s fs GroupStart :: s -> GroupState s fs GroupBuffer :: s -> fs -> Int -> GroupState s fs GroupYield :: fs -> GroupState s fs -> GroupState s fs GroupFinish :: GroupState s fs groupsOf :: Monad m => Int -> Fold m a b -> Stream m a -> Stream m b groupsOf2 :: Monad m => Int -> m c -> Fold2 m c 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) instance GHC.Base.Functor (Streamly.Internal.Data.Stream.StreamD.Type.Step s) -- | 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. data 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.yield (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 module Streamly.Internal.Data.Fold -- | Represents a left fold over an input stream consisting of values of -- type a to a single value of type b in Monad -- m. -- -- The fold uses an intermediate state s as accumulator. The -- step function updates the state and returns the new state. -- When the fold is done the final result of the fold is extracted from -- the intermediate state using the extract function. data Fold m a b -- | Fold step initial extract Fold :: (s -> a -> m s) -> m s -> (s -> m b) -> Fold m a b -- | Change the underlying monad of a fold -- -- Internal hoist :: (forall x. m x -> n x) -> Fold m a b -> Fold n a b -- | Adapt a pure fold to any monad -- --
--   generally = hoist (return . runIdentity)
--   
-- -- Internal generally :: Monad m => Fold Identity a b -> Fold m a b -- | Make a fold using a pure step function, a pure initial state and a -- pure state extraction function. -- -- Internal mkPure :: Monad m => (s -> a -> s) -> s -> (s -> b) -> Fold m a b -- | Make a fold using a pure step function and a pure initial state. The -- final state extracted is identical to the intermediate state. -- -- Internal mkPureId :: Monad m => (b -> a -> b) -> b -> Fold m a b -- | Make a fold with an effectful step function and initial state, and a -- state extraction function. -- --
--   mkFold = Fold
--   
-- -- We can just use Fold but it is provided for completeness. -- -- Internal mkFold :: (s -> a -> m s) -> m s -> (s -> m b) -> Fold m a b -- | Make a fold with an effectful step function and initial state. The -- final state extracted is identical to the intermediate state. -- -- Internal mkFoldId :: Monad m => (b -> a -> m b) -> m b -> Fold m a b -- | A fold that drains all its input, running the effects and discarding -- the results. drain :: Monad m => Fold m a () -- |
--   drainBy f = lmapM f drain
--   
-- -- Drain all input after passing it through a monadic function. This is -- the dual of mapM_ on stream producers. drainBy :: Monad m => (a -> m b) -> Fold m a () drainBy2 :: Monad m => (a -> m b) -> Fold2 m c a () -- | Extract the last element of the input stream, if any. last :: Monad m => Fold m a (Maybe a) -- | Determine the length of the input stream. 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 :: (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. product :: (Monad m, Num 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 = maximumBy compare
--   
-- -- Determine the maximum element in a stream. 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 :: (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 = 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 = ltake n rollingHash
--   
rollingHashFirstN :: (Monad m, Enum a) => Int -> Fold m a Int64 -- | Fold an input stream consisting of monoidal elements using -- mappend and mempty. -- --
--   S.fold FL.mconcat (S.map Sum $ S.enumerateFromTo 1 10)
--   
mconcat :: (Monad m, Monoid a) => Fold m a a -- |
--   foldMap f = map f mconcat
--   
-- -- Make a fold from a pure function that folds the output of the function -- using mappend and mempty. -- --
--   S.fold (FL.foldMap Sum) $ S.enumerateFromTo 1 10
--   
foldMap :: (Monad m, Monoid b) => (a -> b) -> Fold m a b -- |
--   foldMapM f = mapM f mconcat
--   
-- -- Make a fold from a monadic function that folds the output of the -- function using mappend and mempty. -- --
--   S.fold (FL.foldMapM (return . Sum)) $ S.enumerateFromTo 1 10
--   
foldMapM :: (Monad m, Monoid b) => (a -> m b) -> Fold m a b -- | Folds the input stream to a list. -- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using -- Streamly.Memory.Array instead. toList :: Monad m => Fold m a [a] -- | Buffers the input stream to a list in the reverse order of the input. -- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using Streamly.Array -- instead. toListRevF :: Monad m => Fold m a [a] -- | A fold that drains the first n elements of its input, running the -- effects and discarding the results. drainN :: Monad m => Int -> Fold m a () -- | A fold that drains elements of its input as long as the predicate -- succeeds, running the effects and discarding the results. drainWhile :: Monad m => (a -> Bool) -> Fold m a () -- | Lookup the element at the given index. 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 :: (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 :: (Eq a, Monad m) => a -> Fold m a (Maybe Int) -- | Return True if the input stream is empty. null :: Monad m => Fold m a Bool -- | Return True if the given element is present in the stream. elem :: (Eq a, Monad m) => a -> Fold m a Bool -- | Returns True if the given element is not present in the stream. notElem :: (Eq a, Monad m) => a -> Fold m a Bool -- |
--   all p = lmap p and
--   
-- -- | Returns True if all elements of a stream satisfy a predicate. all :: Monad m => (a -> Bool) -> Fold m a Bool -- |
--   any p = lmap p or
--   
-- -- | Returns True if any of the elements of a stream satisfies a -- predicate. any :: Monad m => (a -> Bool) -> Fold m a Bool -- | Returns True if all elements are True, False -- otherwise and :: Monad m => Fold m Bool Bool -- | Returns True if any element is True, False -- otherwise or :: Monad m => Fold m Bool Bool -- | Flatten the monadic output of a fold to pure output. sequence :: Monad m => Fold m a (m b) -> Fold m a b -- | Map a monadic function on the output of a fold. mapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c -- | Apply a transformation on a Fold using a Pipe. 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. -- --
--   >>> S.fold (FL.lmap (\x -> x * x) FL.sum) (S.enumerateFromTo 1 100)
--   338350
--   
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. -- --
--   >>> S.fold (lfilter (> 5) FL.sum) [1..10]
--   40
--   
lfilter :: Monad m => (a -> Bool) -> Fold m a r -> Fold m a r -- | Like lfilter but with a monadic predicate. lfilterM :: Monad m => (a -> m Bool) -> Fold m a r -> Fold m a r -- | Transform a fold from a pure input to a Maybe input, consuming -- only Just values. lcatMaybes :: Monad m => Fold m a b -> Fold m (Maybe a) b -- | Take first n elements from the stream and discard the rest. ltake :: Monad m => Int -> Fold m a b -> Fold m a b -- | Takes elements from the input as long as the predicate succeeds. ltakeWhile :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a b -- | Group the input stream into windows of n second each and then fold -- each group using the provided fold function. -- -- For example, we can copy and distribute a stream to multiple folds -- where each fold can group the input differently e.g. by one second, -- one minute and one hour windows respectively and fold each resulting -- stream of folds. -- --
--   -----Fold m a b----|-Fold n a c-|-Fold n a c-|-...-|----Fold m a c
--   
lsessionsOf :: MonadAsync m => Double -> Fold m a b -> Fold m b c -> Fold m a c -- | For every n input items, apply the first fold and supply the result to -- the next fold. lchunksOf :: Monad m => Int -> Fold m a b -> Fold m b c -> Fold m a c -- | 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 = S.fold (FL.splitAt n FL.toList FL.toList) $ S.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],[])
--   
-- -- Internal splitAt :: Monad m => Int -> Fold m a b -> Fold m a c -> Fold m a (b, c) -- | 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 = S.fold (S.span p FL.toList FL.toList) $ S.fromList xs
--   
-- --
--   >>> span_ (< 1) [1,2,3]
--   > ([],[1,2,3])
--   
-- --
--   >>> span_ (< 2) [1,2,3]
--   > ([1],[2,3])
--   
-- --
--   >>> span_ (< 4) [1,2,3]
--   > ([1,2,3],[])
--   
-- -- Internal span :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a c -> Fold m a (b, c) -- |
--   break p = span (not . p)
--   
-- -- Break as soon as the predicate becomes True. break p f1 -- f2 composes folds f1 and f2 such that -- f1 stops consuming input as soon as the predicate p -- becomes True. The rest of the input is consumed f2. -- -- This is the binary version of splitBy. -- --
--   let break_ p xs = S.fold (S.break p FL.toList FL.toList) $ S.fromList xs
--   
-- --
--   >>> break_ (< 1) [3,2,1]
--   > ([3,2,1],[])
--   
-- --
--   >>> break_ (< 2) [3,2,1]
--   > ([3,2],[1])
--   
-- --
--   >>> break_ (< 4) [3,2,1]
--   > ([],[3,2,1])
--   
-- -- Internal break :: Monad m => (a -> Bool) -> Fold m a b -> Fold m a c -> Fold 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. -- -- Internal spanBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Fold 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. -- -- Internal spanByRolling :: Monad m => (a -> a -> Bool) -> Fold m a b -> Fold m a c -> Fold m a (b, 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--------|
--   
-- --
--   >>> S.fold (FL.tee FL.sum FL.length) (S.enumerateFromTo 1.0 100.0)
--   (5050.0,100)
--   
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--------|
--                   |                         |
--                              ...
--   
-- --
--   >>> S.fold (FL.distribute [FL.sum, FL.length]) (S.enumerateFromTo 1 5)
--   [15,5]
--   
-- -- This is the consumer side dual of the producer side sequence -- operation. distribute :: Monad m => [Fold m a b] -> Fold m a [b] -- | Like distribute but for folds that return (), this can be more -- efficient than distribute as it does not need to maintain -- state. distribute_ :: Monad m => [Fold m a ()] -> Fold m a () -- | 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. -- --
--   > let table = Data.Map.fromList [("SUM", FL.sum), ("PRODUCT", FL.product)]
--         input = S.fromList [("SUM",1),("PRODUCT",2),("SUM",3),("PRODUCT",4)]
--     in S.fold (FL.demux table) input
--   fromList [(PRODUCT,8),(SUM,4)]
--   
demux :: (Monad m, Ord k) => Map k (Fold m a b) -> Fold m (k, a) (Map k b) -- | Given a stream of key value pairs and a map from keys to folds, fold -- the values for each key using the corresponding folds, discarding the -- outputs. -- --
--   > let prn = FL.drainBy print
--   > let table = Data.Map.fromList [("ONE", prn), ("TWO", prn)]
--         input = S.fromList [("ONE",1),("TWO",2)]
--     in S.fold (FL.demux_ table) input
--   One 1
--   Two 2
--   
demux_ :: (Monad m, Ord k) => Map k (Fold m a ()) -> Fold m (k, a) () demuxDefault_ :: (Monad m, Ord k) => Map k (Fold m a ()) -> Fold m (k, a) () -> Fold m (k, a) () demuxWithDefault_ :: (Monad m, Ord k) => (a -> (k, a')) -> Map k (Fold m a' b) -> Fold m (k, a') b -> Fold m a () -- | 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 = S.fromList [("ONE",1),("ONE",1.1),("TWO",2), ("TWO",2.2)]
--     in S.fold (FL.classify FL.toList) input
--   fromList [("ONE",[1.1,1.0]),("TWO",[2.2,2.0])]
--   
classify :: (Monad m, Ord k) => Fold m a b -> Fold m (k, 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--------|
--   
-- -- 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) -- | Apply a terminating fold repeatedly to the input of another fold. -- -- Compare with: Streamly.Prelude.concatMap, Streamly.Prelude.foldChunks -- -- Unimplemented foldChunks :: Fold m a b -> Fold m b c -> Fold m a c -- | Modify the fold such that when the fold is done, instead of returning -- the accumulator, it returns a fold. The returned fold starts from -- where we left i.e. it uses the last accumulator value as the initial -- value of the accumulator. Thus we can resume the fold later and feed -- it more input. -- --
--   > do
--       more <- S.fold (FL.duplicate FL.sum) (S.enumerateFromTo 1 10)
--       evenMore <- S.fold (FL.duplicate more) (S.enumerateFromTo 11 20)
--       S.fold evenMore (S.enumerateFromTo 21 30)
--    465
--   
duplicate :: Applicative m => Fold m a b -> Fold m a (Fold m a b) -- | Run the initialization effect of a fold. The returned fold would use -- the value returned by this effect as its initial value. initialize :: Monad m => Fold m a b -> m (Fold m a b) -- | Run one step of a fold and store the accumulator as an initial value -- in the returned fold. runStep :: Monad m => Fold m a b -> a -> m (Fold m a b) toParallelSVar :: MonadIO m => SVar t m a -> Maybe WorkerInfo -> Fold m a () toParallelSVarLimited :: MonadIO m => SVar t m a -> Maybe WorkerInfo -> Fold m a () -- | Streaming and backtracking parsers. -- -- Parsers just extend folds. Please read the Fold design notes in -- Streamly.Internal.Data.Fold.Types 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. Skip: hold (buffer) the input or go back to a previous -- position in the stream
  2. --
  3. Yield, Stop: tell how much input is unconsumed
  4. --
  5. Error: indicates that the parser has failed without a -- result
  6. --
-- --

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 Skip 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 Stop 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 -- Yield 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 -- Stop for termination after the first Yield, 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 iterminate by -- either a Stop 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.Types -- | The return type of a Parser step. -- -- A parser is driven by a parse driver one step at a time, at any time -- the driver may extract the result of the parser. The parser -- may ask the driver to backtrack at any point, therefore, the driver -- holds the input up to a point of no return in a backtracking buffer. -- The buffer grows or shrinks based on the return values of the parser -- step execution. -- -- When a parser step is executed it generates a new intermediate state -- of the parse result along with a command to the driver. The command -- tells the driver whether to keep the input stream for a potential -- backtracking later on or drop it, and how much to keep. The -- constructors of Step represent the commands to the driver. -- -- Internal data Step s b -- | Yield offset state indicates that the parser has yielded a -- new result which is a point of no return. The result can be extracted -- using extract. The driver drops the buffer except -- offset elements before the current position in stream. The -- rule is that if a parser has yielded at least once it cannot return a -- failure result. Yield :: Int -> s -> Step s b -- | Skip offset state indicates that the parser has consumed the -- current input but no new result has been generated. A new -- state is generated. However, if we use extract on -- state it will generate a result from the previous -- Yield. When offset is non-zero it is a backward -- offset from the current position in the stream from which the driver -- will feed the next input to the parser. The offset cannot be beyond -- the latest point of no return created by Yield. Skip :: Int -> s -> Step s b -- | Stop offset result asks the driver to stop driving the parser -- because it has reached a fixed point and further input will not change -- the result. offset is the count of unused elements which -- includes the element on which Stop occurred. Stop :: Int -> b -> Step s b -- | An error makes the parser backtrack to the last checkpoint 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. It may result in an error or an output value. -- -- Internal data Parser m a b Parser :: (s -> a -> m (Step s b)) -> m s -> (s -> m b) -> Parser m a b -- | This exception is used for two purposes: -- -- -- -- Internal newtype ParseError ParseError :: String -> ParseError -- | A parser that always yields a pure value without consuming any input. -- -- Internal yield :: Monad m => b -> Parser m a b -- | A parser that always yields the result of an effectful action without -- consuming any input. -- -- Internal yieldM :: Monad m => m b -> Parser m a b -- | Sequential 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. -- -- This undoes an "append" of two streams, it splits the streams using -- two parsers and zips the results. -- -- This implementation is strict in the second argument, therefore, the -- following will fail: -- --
--   >>> S.parse (PR.satisfy (> 0) *> undefined) $ S.fromList [1]
--   
-- -- Internal splitWith :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | A parser that always fails with an error message without consuming any -- input. -- -- Internal die :: MonadThrow m => String -> Parser m a b -- | A parser that always fails with an effectful error message and without -- consuming any input. -- -- Internal dieM :: MonadThrow m => m String -> Parser m a b -- | See documentation of some. -- -- Internal splitSome :: MonadCatch m => Fold m b c -> Parser m a b -> Parser m a c -- | See documentation of many. -- -- Internal splitMany :: MonadCatch m => Fold m b c -> Parser m a b -> Parser m a c -- | 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: -- --
--   >>> S.parse (PR.satisfy (> 0) `PR.alt` undefined) $ S.fromList [1..10]
--   
-- -- Internal alt :: Monad m => Parser m x a -> Parser m x a -> Parser m x a instance GHC.Show.Show Streamly.Internal.Data.Parser.Types.ParseError instance GHC.Base.Monad m => GHC.Base.Monad (Streamly.Internal.Data.Parser.Types.Parser m a) instance GHC.Exception.Type.Exception Streamly.Internal.Data.Parser.Types.ParseError instance GHC.Base.Functor m => GHC.Base.Functor (Streamly.Internal.Data.Parser.Types.Parser m a) instance GHC.Base.Monad m => GHC.Base.Applicative (Streamly.Internal.Data.Parser.Types.Parser m a) instance Control.Monad.Catch.MonadCatch m => GHC.Base.Alternative (Streamly.Internal.Data.Parser.Types.Parser m a) instance Control.Monad.Catch.MonadCatch m => GHC.Base.MonadPlus (Streamly.Internal.Data.Parser.Types.Parser m a) instance GHC.Base.Functor (Streamly.Internal.Data.Parser.Types.Step s) -- | 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.Tee -- | teeWith f p1 p2 distributes its input to both p1 and -- p2 until both of them succeed or fail and combines their -- output using f. The parser succeeds if both the parsers -- succeed. -- -- Internal teeWith :: Monad 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. -- -- Internal teeWithFst :: Monad 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 :: (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | 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. -- -- Internal shortest :: Monad 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. -- -- Internal longest :: MonadCatch m => Parser m x a -> Parser m x a -> Parser m x a -- | Fast streaming parsers. -- -- 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 generic 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. -- -- Failing parsers in this module throw the ParseError exception. module Streamly.Internal.Data.Parser -- | 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. It may result in an error or an output value. -- -- Internal data Parser m a b Parser :: (s -> a -> m (Step s b)) -> m s -> (s -> m b) -> Parser m a b -- | The resulting parse never terminates and never errors out. fromFold :: Monad m => Fold m a b -> Parser m a b -- |
--   >>> S.parse (PR.any (== 0)) $ S.fromList [1,0,1]
--   > Right True
--   
any :: Monad m => (a -> Bool) -> Parser m a Bool -- |
--   >>> S.parse (PR.all (== 0)) $ S.fromList [1,0,1]
--   > Right False
--   
all :: Monad m => (a -> Bool) -> Parser m a Bool -- | A parser that always yields a pure value without consuming any input. -- -- Internal yield :: Monad m => b -> Parser m a b -- | A parser that always yields the result of an effectful action without -- consuming any input. -- -- Internal yieldM :: Monad m => m b -> Parser m a b -- | A parser that always fails with an error message without consuming any -- input. -- -- Internal die :: MonadThrow m => String -> Parser m a b -- | A parser that always fails with an effectful error message and without -- consuming any input. -- -- Internal dieM :: MonadThrow m => m String -> Parser m a b -- | Peek the head element of a stream, without consuming it. Fails if it -- encounters end of input. -- --
--   >>> S.parse ((,) <$> PR.peek <*> PR.satisfy (> 0)) $ S.fromList [1]
--   (1,1)
--   
-- --
--   peek = lookAhead (satisfy True)
--   
-- -- Internal peek :: MonadThrow m => Parser m a a -- | Succeeds if we are at the end of input, fails otherwise. -- --
--   >>> S.parse ((,) <$> PR.satisfy (> 0) <*> PR.eof) $ S.fromList [1]
--   > (1,())
--   
-- -- Internal eof :: Monad m => Parser m a () -- | Returns the next element if it passes the predicate, fails otherwise. -- --
--   >>> S.parse (PR.satisfy (== 1)) $ S.fromList [1,0,1]
--   > 1
--   
-- -- Internal satisfy :: MonadThrow m => (a -> Bool) -> Parser m a a -- | Take at most n input elements and fold them using the -- supplied fold. -- -- Stops after n elements. Never fails. -- --
--   >>> S.parse (PR.take 1 FL.toList) $ S.fromList [1]
--   [1]
--   
-- --
--   S.chunksOf n f = S.splitParse (FL.take n f)
--   
-- -- Internal take :: Monad m => Int -> Fold m a b -> Parser m a b -- | Stops after taking exactly n input elements. -- -- -- --
--   >>> S.parse (PR.takeEQ 4 FL.toList) $ S.fromList [1,0,1]
--   > "takeEQ: Expecting exactly 4 elements, got 3"
--   
-- -- Internal takeEQ :: MonadThrow m => Int -> Fold m a b -> Parser m a b -- | Take at least n input elements, but can collect more. -- -- -- --
--   >>> S.parse (PR.takeGE 4 FL.toList) $ S.fromList [1,0,1]
--   > "takeGE: Expecting at least 4 elements, got only 3"
--   
-- --
--   >>> S.parse (PR.takeGE 4 FL.toList) $ S.fromList [1,0,1,0,1]
--   > [1,0,1,0,1]
--   
-- -- Internal takeGE :: MonadThrow m => Int -> Fold m a b -> Parser m a b lookAhead :: MonadThrow m => 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. -- -- -- --
--   >>> S.parse (PR.takeWhile (== 0) FL.toList) $ S.fromList [0,0,1,0,1]
--   > [0,0]
--   
-- -- We can implement a breakOn using takeWhile: -- --
--   breakOn p = takeWhile (not p)
--   
-- -- Internal takeWhile :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b -- | Like takeWhile but takes at least one element otherwise fails. -- -- Internal takeWhile1 :: MonadThrow m => (a -> Bool) -> Fold m a b -> Parser m a b -- | Collect stream elements until an element succeeds the predicate. Drop -- the element on which the predicate succeeded. The succeeding element -- is treated as an infix separator which is dropped from the output. -- -- -- --
--   >>> S.parse (PR.sliceSepBy (== 1) FL.toList) $ S.fromList [0,0,1,0,1]
--   > [0,0]
--   
-- -- S.splitOn pred f = S.splitParse (PR.sliceSepBy pred f) -- --
--   >>> S.toList $ S.splitParse (PR.sliceSepBy (== 1) FL.toList) $ S.fromList [0,0,1,0,1]
--   > [[0,0],[0],[]]
--   
-- -- Internal sliceSepBy :: Monad m => (a -> Bool) -> Fold m a b -> Parser m a b -- | Split using a condition or a count whichever occurs first. This is a -- hybrid of splitOn and take. The element on which the -- condition succeeds is dropped. -- -- Internal sliceSepByMax :: Monad m => (a -> Bool) -> Int -> Fold m a b -> Parser m a b -- | Collect stream elements until an element succeeds the predicate. Also -- take the element on which the predicate succeeded. The succeeding -- element is treated as a suffix separator which is kept in the output -- segement. -- -- -- -- S.splitWithSuffix pred f = S.splitParse (PR.sliceEndWith pred f) -- -- Unimplemented sliceEndWith :: (a -> Bool) -> Fold 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 it -- is kept in the stream and we continue collecting. The succeeding -- element is treated as a prefix separator which is kept in the output -- segement. -- -- -- -- S.splitWithPrefix pred f = S.splitParse (PR.sliceBeginWith pred f) -- -- Unimplemented sliceBeginWith :: (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.splitParse (PR.wordBy pred f)
--   
-- -- Unimplemented wordBy :: (a -> Bool) -> Fold m a b -> Parser m a b -- | groupBy cmp f $ S.fromList [a,b,c,...] 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 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. -- -- -- --
--   S.groupsBy cmp f = S.splitParse (PR.groupBy cmp f)
--   
-- -- Unimplemented groupBy :: (a -> a -> Bool) -> Fold m a b -> Parser m a b -- | Match the given sequence of elements using the given comparison -- function. -- -- Internal eqBy :: MonadThrow m => (a -> a -> Bool) -> [a] -> Parser m a () -- | Sequential 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. -- -- This undoes an "append" of two streams, it splits the streams using -- two parsers and zips the results. -- -- This implementation is strict in the second argument, therefore, the -- following will fail: -- --
--   >>> S.parse (PR.satisfy (> 0) *> undefined) $ S.fromList [1]
--   
-- -- Internal splitWith :: Monad m => (a -> b -> c) -> Parser m x a -> Parser m x b -> Parser m x c -- | teeWith f p1 p2 distributes its input to both p1 and -- p2 until both of them succeed or fail and combines their -- output using f. The parser succeeds if both the parsers -- succeed. -- -- Internal teeWith :: Monad 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. -- -- Internal teeWithFst :: Monad 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 :: (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) -- | 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. -- -- Internal shortest :: Monad 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. -- -- Internal longest :: MonadCatch m => Parser m x a -> Parser m x a -> Parser m x a -- | sequence 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. -- -- Unimplemented sequence :: Fold m b c -> t (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 -> Fold m b c -> Parser m a b -> 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 -> Fold m b c -> Parser m a b -> Parser m a c -- | Collect zero or more parses. Apply the parser repeatedly on the input -- stream, stop when the parser fails, accumulate zero or more parse -- results using the supplied Fold. This parser never fails, in -- case the first application of parser fails it returns an empty result. -- -- Compare with many. -- -- Internal many :: MonadCatch m => Fold m b c -> Parser m a b -> Parser m a c -- | Collect one or more parses. Apply the supplied parser repeatedly on -- the input stream and accumulate the parse results as long as the -- parser succeeds, stop when it fails. This parser fails if not even one -- result is collected. -- -- Compare with some. -- -- Internal some :: MonadCatch m => Fold m b c -> Parser m a b -> 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. -- -- Internal manyTill :: MonadCatch m => Fold m b c -> Parser m a b -> Parser m a x -> Parser m a c -- | choice parsers applies the parsers in order and -- returns the first successful parse. choice :: t (Parser m a b) -> Parser m a b -- | Fold type represents an effectful action that consumes a value -- from an input stream and combines it with a single final value often -- called an accumulator, returning the resulting output accumulator. -- Values from a stream can be pushed to the fold and consumed one -- at a time. It can also be called a consumer of stream or a sink. It is -- a data representation of the standard foldl' function. A -- Fold can be turned into an effect (m b) using -- fold by supplying it the input stream. -- -- Using this representation multiple folds can be combined efficiently -- using combinators; a stream can then be supplied to the combined fold -- and it would distribute the input to constituent folds according to -- the composition. For example, an applicative composition distributes -- the same input to the constituent folds and then combines the -- resulting fold outputs. Similarly, a partitioning combinator divides -- the input among constituent folds. -- --

Performance Notes

-- -- Fold representation is more efficient than using streams when -- splitting streams. Fold m a b can be considered roughly -- equivalent to a fold action m b -> t m a -> m b (where -- t is a stream type and m is a Monad). Instead -- of using a Fold type one could just use a fold action of the -- shape m b -> t m a -> m b for folding streams. However, -- multiple such actions cannot be composed into a single fold function -- in an efficient manner. Using the Fold type we can efficiently -- split the stream across mutliple folds because it allows the compiler -- to perform stream fusion optimizations. -- -- On the other hand, transformation operations (e.g. map) on -- stream types can be as efficient as transformations on Fold -- (e.g. lmap). -- --

Left folds vs Right Folds

-- -- The folds in this module are left folds, therefore, even partial -- folds, e.g. head in this module, would drain the whole -- stream. On the other hand, the partial folds in -- Streamly.Prelude module are lazy right folds and would -- terminate as soon as the result is determined. However, the folds in -- this module can be composed but the folds in Streamly.Prelude -- cannot be composed. -- --

Programmer Notes

-- --
--   import qualified Streamly.Data.Fold as FL
--   
-- -- More, not yet exposed, fold combinators can be found in -- Streamly.Internal.Data.Fold. module Streamly.Data.Fold -- | Represents a left fold over an input stream consisting of values of -- type a to a single value of type b in Monad -- m. -- -- The fold uses an intermediate state s as accumulator. The -- step function updates the state and returns the new state. -- When the fold is done the final result of the fold is extracted from -- the intermediate state using the extract function. data Fold m a b -- | A fold that drains all its input, running the effects and discarding -- the results. drain :: Monad m => Fold m a () -- |
--   drainBy f = lmapM f drain
--   
-- -- Drain all input after passing it through a monadic function. This is -- the dual of mapM_ on stream producers. drainBy :: Monad m => (a -> m b) -> Fold m a () -- | Extract the last element of the input stream, if any. last :: Monad m => Fold m a (Maybe a) -- | Determine the length of the input stream. 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 :: (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. product :: (Monad m, Num 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 = maximumBy compare
--   
-- -- Determine the maximum element in a stream. 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 :: (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 -- | Fold an input stream consisting of monoidal elements using -- mappend and mempty. -- --
--   S.fold FL.mconcat (S.map Sum $ S.enumerateFromTo 1 10)
--   
mconcat :: (Monad m, Monoid a) => Fold m a a -- |
--   foldMap f = map f mconcat
--   
-- -- Make a fold from a pure function that folds the output of the function -- using mappend and mempty. -- --
--   S.fold (FL.foldMap Sum) $ S.enumerateFromTo 1 10
--   
foldMap :: (Monad m, Monoid b) => (a -> b) -> Fold m a b -- |
--   foldMapM f = mapM f mconcat
--   
-- -- Make a fold from a monadic function that folds the output of the -- function using mappend and mempty. -- --
--   S.fold (FL.foldMapM (return . Sum)) $ S.enumerateFromTo 1 10
--   
foldMapM :: (Monad m, Monoid b) => (a -> m b) -> Fold m a b -- | Folds the input stream to a list. -- -- Warning! working on large lists accumulated as buffers in -- memory could be very inefficient, consider using -- Streamly.Memory.Array instead. toList :: Monad m => Fold m a [a] -- | Lookup the element at the given index. 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 :: (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 :: (Eq a, Monad m) => a -> Fold m a (Maybe Int) -- | Return True if the input stream is empty. null :: Monad m => Fold m a Bool -- | Return True if the given element is present in the stream. elem :: (Eq a, Monad m) => a -> Fold m a Bool -- | Returns True if the given element is not present in the stream. notElem :: (Eq a, Monad m) => a -> Fold m a Bool -- |
--   all p = lmap p and
--   
-- -- | Returns True if all elements of a stream satisfy a predicate. all :: Monad m => (a -> Bool) -> Fold m a Bool -- |
--   any p = lmap p or
--   
-- -- | Returns True if any of the elements of a stream satisfies a -- predicate. any :: Monad m => (a -> Bool) -> Fold m a Bool -- | Returns True if all elements are True, False -- otherwise and :: Monad m => Fold m Bool Bool -- | Returns True if any element is True, False -- otherwise or :: Monad m => Fold m Bool Bool -- | Flatten the monadic output of a fold to pure output. sequence :: Monad m => Fold m a (m b) -> Fold m a b -- | Map a monadic function on the output of a fold. mapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a 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--------|
--   
-- --
--   >>> S.fold (FL.tee FL.sum FL.length) (S.enumerateFromTo 1.0 100.0)
--   (5050.0,100)
--   
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--------|
--                   |                         |
--                              ...
--   
-- --
--   >>> S.fold (FL.distribute [FL.sum, FL.length]) (S.enumerateFromTo 1 5)
--   [15,5]
--   
-- -- This is the consumer side dual of the producer side sequence -- operation. 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--------|
--   
-- -- 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) module Streamly.Internal.Data.Unfold.Types -- | 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 module Streamly.Internal.Data.Unicode.Char -- | Select alphabetic characters in the ascii character set. -- -- Internal isAsciiAlpha :: Char -> Bool -- | A mutable variable in a mutation capable monad (IO/ST) 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 -- Var 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.Mutable.Prim.Var -- | A Var holds a single Prim value. data Var m a -- | A monad that allows mutable operations using a state token. type MonadMut = PrimMonad -- | 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 mutable variable. newVar :: forall m a. (MonadMut m, Prim a) => a -> m (Var m a) -- | Write a value to a mutable variable. writeVar :: (MonadMut m, Prim a) => Var m a -> a -> m () -- | Modify the value of a mutable variable using a function with strict -- application. modifyVar' :: (MonadMut m, Prim a) => Var m a -> (a -> a) -> m () -- | Read a value from a variable. readVar :: (MonadMut m, Prim a) => Var m a -> m a module Streamly.Internal.Memory.Array.Types data Array a Array :: {-# UNPACK #-} !ForeignPtr a -> {-# UNPACK #-} !Ptr a -> {-# UNPACK #-} !Ptr a -> Array a [aStart] :: Array a -> {-# UNPACK #-} !ForeignPtr a [aEnd] :: Array a -> {-# UNPACK #-} !Ptr a [aBound] :: Array a -> {-# UNPACK #-} !Ptr a -- | Allocate an Array of the given size and run an IO action passing the -- array start pointer. withNewArray :: forall a. Storable a => Int -> (Ptr a -> IO ()) -> IO (Array a) -- | Allocate an array that 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 a. Storable a => Int -> IO (Array a) unsafeSnoc :: forall a. Storable a => Array a -> a -> IO (Array a) snoc :: forall a. Storable a => Array a -> a -> IO (Array a) spliceWithDoubling :: (MonadIO m, Storable a) => Array a -> Array a -> m (Array a) spliceTwo :: (MonadIO m, Storable a) => Array a -> Array a -> m (Array a) -- | Create an Array from a list. The list must be of finite size. 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. fromListN :: Storable a => Int -> [a] -> Array a fromStreamDN :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> m (Array a) -- | fromStreamArraysOf n stream groups the input stream into a -- stream of arrays of size n. fromStreamDArraysOf :: forall m a. (MonadIO m, Storable a) => Int -> Stream m a -> Stream m (Array a) data FlattenState s a OuterLoop :: s -> FlattenState s a InnerLoop :: s -> !ForeignPtr a -> !Ptr a -> !Ptr a -> FlattenState s a flattenArrays :: forall m a. (MonadIO m, Storable a) => Stream m (Array a) -> Stream m a flattenArraysRev :: forall m a. (MonadIO m, Storable a) => Stream m (Array a) -> Stream m a -- | 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) lpackArraysChunksOf :: (MonadIO m, Storable 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. splitOn :: MonadIO m => Word8 -> Stream m (Array Word8) -> Stream m (Array Word8) 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 length of the array i.e. the number of elements in -- the array. length :: forall a. Storable a => Array a -> Int -- | O(1) Get the byte length of the array. byteLength :: Array a -> Int byteCapacity :: 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) 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 t m a. (IsStream t, Storable a) => Array a -> t m a toStreamKRev :: forall t m a. (IsStream t, Storable a) => Array a -> t m a -- | Convert an Array into a list. toList :: Storable a => Array a -> [a] toArrayMinChunk :: forall m a. (MonadIO m, Storable a) => Int -> Int -> Fold m a (Array a) -- | writeN n folds a maximum of n elements from the -- input stream to an 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) -- | writeNAligned alignment n folds a maximum of n -- elements from the input stream to an Array aligned to the given -- size. -- -- Internal 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. -- -- Internal 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. write :: forall m a. (MonadIO m, Storable a) => Fold m a (Array a) -- | Like write but the array memory is aligned according to the -- specified alignment size. This could be useful when we have specific -- alignment, for example, cache aligned arrays for lookup table etc. -- -- Caution! Do not use this on infinite streams. writeAligned :: forall m a. (MonadIO m, Storable a) => Int -> Fold m a (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 mkChunkSize :: Int -> Int mkChunkSizeKB :: Int -> Int unsafeInlineIO :: IO a -> a realloc :: forall a. Storable a => Int -> Array a -> IO (Array a) -- | Remove the free space from an Array. shrinkToFit :: forall a. Storable a => Array a -> IO (Array a) memcpy :: Ptr Word8 -> Ptr Word8 -> Int -> IO () memcmp :: Ptr Word8 -> Ptr Word8 -> Int -> IO Bool bytesToElemCount :: Storable a => a -> Int -> Int unlines :: forall m a. (MonadIO m, Storable a) => a -> Stream m (Array a) -> Stream m a instance (GHC.Show.Show a, Foreign.Storable.Storable a) => GHC.Show.Show (Streamly.Internal.Memory.Array.Types.Array a) instance (Foreign.Storable.Storable a, GHC.Read.Read a, GHC.Show.Show a) => GHC.Read.Read (Streamly.Internal.Memory.Array.Types.Array a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString (Streamly.Internal.Memory.Array.Types.Array a) instance Foreign.Storable.Storable a => GHC.Exts.IsList (Streamly.Internal.Memory.Array.Types.Array a) instance (Foreign.Storable.Storable a, GHC.Classes.Eq a) => GHC.Classes.Eq (Streamly.Internal.Memory.Array.Types.Array a) instance (Foreign.Storable.Storable a, Control.DeepSeq.NFData a) => Control.DeepSeq.NFData (Streamly.Internal.Memory.Array.Types.Array a) instance (Foreign.Storable.Storable a, GHC.Classes.Ord a) => GHC.Classes.Ord (Streamly.Internal.Memory.Array.Types.Array a) instance Foreign.Storable.Storable a => GHC.Base.Semigroup (Streamly.Internal.Memory.Array.Types.Array a) instance Foreign.Storable.Storable a => GHC.Base.Monoid (Streamly.Internal.Memory.Array.Types.Array a) -- | Direct style re-implementation of CPS style stream in StreamK module. -- 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 -- | 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. nil :: Monad m => Stream m a -- | An empty Stream with a side effect. nilM :: Monad m => m b -> Stream m a -- | Can fuse but has O(n^2) complexity. cons :: Monad m => a -> Stream m a -> Stream m a uncons :: Monad m => Stream m a -> m (Maybe (a, Stream m a)) unfoldr :: Monad m => (s -> Maybe (a, s)) -> s -> Stream m a unfoldrM :: Monad m => (s -> m (Maybe (a, s))) -> s -> Stream m a -- | Convert an Unfold into a Stream by supplying it a seed. unfold :: Monad m => Unfold m a b -> a -> Stream m b 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 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 -- | 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 enumerateFromToIntegral :: (Monad m, Integral a) => a -> a -> Stream m a enumerateFromThenToIntegral :: (Monad m, Integral a) => a -> a -> a -> Stream m a enumerateFromStepNum :: (Monad m, Num a) => a -> a -> Stream m a numFrom :: (Monad m, Num a) => a -> Stream m a numFromThen :: (Monad m, Num a) => a -> a -> Stream m a 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 currentTime :: MonadAsync m => Double -> Stream m AbsTime -- | Create a singleton Stream from a pure value. yield :: Applicative m => a -> Stream m a -- | Create a singleton Stream from a monadic action. yieldM :: Monad m => 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 fromStreamK :: Monad m => Stream m a -> Stream m a fromStreamD :: (IsStream t, Monad m) => Stream m a -> t m a fromPrimVar :: (MonadIO m, Prim a) => Var IO a -> Stream m a fromSVar :: MonadAsync m => SVar t 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 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 foldr1 :: Monad m => (a -> a -> a) -> Stream m a -> m (Maybe a) foldl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b foldlM' :: Monad m => (b -> a -> m b) -> b -> Stream m a -> 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 reverse :: Monad m => Stream m a -> Stream m a reverse' :: forall m a. (MonadIO m, Storable a) => Stream m a -> Stream m a 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 runFold :: Monad m => Fold m a b -> Stream m a -> m b -- | Run a Parse over a stream. parselMx' :: MonadThrow m => (s -> a -> m (Step s b)) -> m s -> (s -> m b) -> Stream m a -> m b splitParse :: MonadThrow m => Parser m a b -> Stream m a -> Stream m b 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 tapAsync :: MonadAsync m => 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 -- | Run a streaming composition, discard the results. drain :: Monad m => 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) findIndices :: Monad m => (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) -- | Fold the supplied stream to the SVar asynchronously using Parallel -- concurrency style. {-# INLINE [1] toSVarParallel #-} toSVarParallel :: MonadAsync m => State t m a -> SVar t m a -> Stream m a -> m () concatMapM :: Monad m => (a -> m (Stream m b)) -> Stream m a -> Stream m b concatMap :: Monad m => (a -> Stream m b) -> Stream m a -> Stream m b data ConcatMapUState o i ConcatMapUOuter :: o -> ConcatMapUState o i ConcatMapUInner :: o -> i -> ConcatMapUState o i -- | concatMapU unfold stream uses unfold to map the -- input stream elements to streams and then flattens the generated -- streams into a single output stream. concatMapU :: 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 concatUnfoldInterleave :: Monad m => Unfold m a b -> Stream m a -> Stream m b concatUnfoldRoundrobin :: Monad m => Unfold m a b -> Stream m a -> Stream m b 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 -- | 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 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 interpose :: Monad m => m c -> Unfold m b c -> Stream m b -> Stream m c groupsOf :: Monad m => Int -> Fold m a b -> Stream m a -> Stream m b groupsOf2 :: Monad m => Int -> m c -> Fold2 m c 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 splitBy :: Monad m => (a -> Bool) -> Fold m a b -> Stream m a -> Stream m b splitSuffixBy :: Monad m => (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 splitSuffixBy' :: Monad m => (a -> Bool) -> Fold m a b -> Stream m a -> Stream m b splitOn :: forall m a b. (MonadIO m, Storable a, Enum a, Eq a) => Array a -> Fold m a b -> Stream m a -> Stream m b splitSuffixOn :: 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 -- | 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) 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)) -- | Execute a monadic action for each element of the Stream mapM_ :: Monad m => (a -> m b) -> Stream m a -> m () toList :: Monad m => Stream m a -> m [a] toListRev :: Monad m => Stream m a -> m [a] toStreamK :: Monad m => Stream m a -> Stream m a toStreamD :: (IsStream t, Monad m) => t m a -> Stream m a 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 => s -> Stream (ReaderT s m) a -> Stream m a evalStateT :: Monad m => s -> Stream (StateT s m) a -> Stream m a runStateT :: Monad m => s -> Stream (StateT s m) a -> Stream m (s, a) transform :: Monad m => Pipe m a b -> Stream m a -> Stream m b scanlM' :: Monad m => (b -> a -> m b) -> 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) -> 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) -> 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) -> 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 uniq :: (Eq a, Monad m) => Stream m a -> Stream m a take :: Monad 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 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 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 intersperseM :: Monad m => m a -> Stream m a -> Stream m a intersperse :: Monad 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 insertBy :: Monad m => (a -> a -> Ordering) -> a -> Stream m a -> Stream m a deleteBy :: Monad m => (a -> a -> Bool) -> a -> Stream m a -> Stream m a 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 indexed :: Monad m => Stream m a -> Stream m (Int, a) indexedR :: Monad m => Int -> Stream m a -> Stream m (Int, 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 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 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 the :: (Eq a, Monad m) => Stream m a -> m (Maybe a) -- | Create an IORef holding a finalizer that is called automatically when -- the IORef is garbage collected. The IORef can be written to with a -- Nothing value to deactivate the finalizer. newFinalizedIORef :: (MonadIO m, MonadBaseControl IO m) => m a -> m (IORef (Maybe (IO ()))) -- | Run the finalizer stored in an IORef and deactivate it so that it is -- run only once. runIORefFinalizer :: MonadIO m => IORef (Maybe (IO ())) -> m () -- | Deactivate the finalizer stored in an IORef without running it. clearIORefFinalizer :: MonadIO m => IORef (Maybe (IO ())) -> m () -- | The most general bracketing and exception combinator. All other -- combinators can be expressed in terms of this combinator. This can -- also be used for cases which are not covered by the standard -- combinators. -- -- Internal gbracket :: Monad m => m c -> (forall s. m s -> m (Either e s)) -> (c -> m d) -> (c -> e -> Stream m b) -> (c -> Stream m b) -> Stream m b -- | Run a side effect before the stream yields its first element. before :: Monad m => m b -> Stream m a -> Stream m a -- | Run a side effect whenever the stream stops normally. after :: Monad m => m b -> Stream m a -> Stream m a afterIO :: (MonadIO m, MonadBaseControl IO m) => m b -> Stream m a -> Stream m a -- | Run the first action before the stream starts and remember its output, -- generate a stream using the output, run the second action providing -- the remembered value as an argument whenever the stream ends normally -- or due to an exception. bracket :: MonadCatch m => m b -> (b -> m c) -> (b -> Stream m a) -> Stream m a bracketIO :: (MonadAsync m, MonadCatch m) => m b -> (b -> m c) -> (b -> Stream m a) -> Stream m a -- | Run a side effect whenever the stream aborts due to an exception. The -- exception is not caught, simply rethrown. onException :: MonadCatch m => m b -> Stream m a -> Stream m a -- | Run a side effect whenever the stream stops normally or aborts due to -- an exception. finally :: MonadCatch m => m b -> Stream m a -> Stream m a finallyIO :: (MonadAsync m, MonadCatch m) => m b -> Stream m a -> Stream 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. handle :: (MonadCatch m, Exception e) => (e -> Stream m a) -> Stream m a -> Stream 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. -- -- Internal mkParallel :: (IsStream t, MonadAsync m) => t m a -> t m a mkParallelD :: MonadAsync m => 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. -- -- Internal newCallbackStream :: (IsStream t, MonadAsync m) => m (a -> m (), t m a) -- | Take last n elements from the stream and discard the rest. lastN :: (Storable a, MonadIO m) => Int -> Fold m a (Array a) -- | 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 -- | 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 -- | Map a function on the input argument of the Unfold. -- --
--   lmap f = concat (singleton f)
--   
-- -- Internal lmap :: (a -> c) -> Unfold m c b -> Unfold m a b -- | Map an action on the input argument of the Unfold. -- --
--   lmapM f = concat (singletonM f)
--   
-- -- Internal 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. -- -- Internal supply :: Unfold m a b -> a -> 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. -- -- Internal supplyFirst :: Unfold m (a, b) c -> a -> 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. -- -- Internal supplySecond :: Unfold m (a, b) c -> b -> 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. -- -- Internal 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. -- -- Internal 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. -- -- Internal 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. -- -- Internal fold :: Monad m => Unfold m a b -> Fold m b c -> a -> m c -- | 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. -- -- Internal fromStream :: (IsStream t, Monad m) => t m b -> Unfold m Void b -- | Convert a single argument stream generator function into an -- Unfold. Note that a stream converted to an Unfold may -- not be as efficient as an Unfold in some situations. -- -- Internal fromStream1 :: (IsStream t, Monad m) => (a -> t m b) -> Unfold m a b -- | Convert a two argument stream generator function into an -- Unfold. Note that a stream converted to an Unfold may -- not be as efficient as an Unfold in some situations. -- -- Internal fromStream2 :: (IsStream t, Monad m) => (a -> b -> t m c) -> Unfold m (a, b) c -- | Lift a monadic function into an unfold generating a nil stream with a -- side effect. nilM :: Monad m => (a -> m c) -> Unfold m a b -- | Prepend a monadic single element generator function to an -- Unfold. -- -- Internal consM :: Monad m => (a -> m b) -> Unfold m a b -> Unfold m a b -- | Lift a monadic effect into an unfold generating a singleton stream. effect :: Monad m => m b -> Unfold m Void b -- | Lift a monadic function into an unfold generating a singleton stream. singletonM :: Monad m => (a -> m b) -> Unfold m a b -- | Lift a pure function into an unfold generating a singleton stream. singleton :: Monad m => (a -> b) -> Unfold m a b -- | Identity unfold. Generates a singleton stream with the seed as the -- only element in the stream. -- --
--   identity = singletonM return
--   
identity :: Monad m => Unfold m a a const :: Monad m => m b -> Unfold m a b -- | Generates a stream replicating the seed n times. replicateM :: Monad m => Int -> Unfold m a a -- | Generates an infinite stream repeating the seed. repeatM :: Monad m => Unfold m a a -- | Convert a list of pure values to a Stream fromList :: Monad m => Unfold m [a] a -- | Convert a list of monadic values to a Stream fromListM :: Monad m => Unfold m [m a] a -- | Can be used to enumerate unbounded integrals. This does not check for -- overflow or underflow for bounded integrals. enumerateFromStepIntegral :: (Integral a, Monad m) => Unfold m (a, a) a enumerateFromToIntegral :: (Monad m, Integral a) => a -> Unfold m a a enumerateFromIntegral :: (Monad m, Integral a, Bounded a) => Unfold m a a map :: Monad m => (b -> c) -> Unfold m a b -> Unfold m a c 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 takeWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b takeWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b take :: Monad m => Int -> Unfold m a b -> Unfold m a b filter :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b filterM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b zipWithM :: Monad m => (a -> b -> m c) -> Unfold m x a -> Unfold m y b -> Unfold m (x, y) c zipWith :: Monad m => (a -> b -> c) -> Unfold m x a -> Unfold m y b -> Unfold m (x, y) c -- | Distribute the input to two unfolds and then zip the outputs to a -- single stream. -- --
--   S.mapM_ print $ S.concatUnfold (UF.teeZipWith (,) UF.identity (UF.singleton sqrt)) $ S.fromList [1..10]
--   
-- -- Internal teeZipWith :: Monad m => (a -> b -> c) -> Unfold m x a -> Unfold m x b -> Unfold m x c -- | Apply the second unfold to each output element of the first unfold and -- flatten the output in a single stream. -- -- Internal concat :: 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 -- flattern the results into a single stream. concatMapM :: Monad m => (b -> m (Unfold m () c)) -> Unfold m a b -> Unfold m a c -- | Create an outer product (vector product or cartesian product) of the -- output streams of two unfolds. outerProduct :: Monad m => Unfold m a b -> Unfold m c d -> Unfold m (a, c) (b, d) -- | The most general bracketing and exception combinator. All other -- combinators can be expressed in terms of this combinator. This can -- also be used for cases which are not covered by the standard -- combinators. -- -- Internal 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 -- | The most general bracketing and exception combinator. All other -- combinators can be expressed in terms of this combinator. This can -- also be used for cases which are not covered by the standard -- combinators. -- -- Internal gbracketIO :: (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 before the unfold yields its first element. -- -- Internal before :: Monad m => (a -> m c) -> Unfold m a b -> Unfold m a b -- | Run a side effect whenever the unfold stops normally. -- -- Prefer afterIO over this as the after action in this -- combinator is not executed if the unfold is partially evaluated lazily -- and then garbage collected. -- -- Internal after :: Monad m => (a -> m c) -> Unfold m a b -> Unfold m a b -- | Run a side effect whenever the unfold stops normally or is garbage -- collected after a partial lazy evaluation. -- -- Internal afterIO :: (MonadIO m, MonadBaseControl IO m) => (a -> m c) -> Unfold m a b -> Unfold m a b -- | Run a side effect whenever the unfold aborts due to an exception. -- -- Internal onException :: MonadCatch m => (a -> m c) -> Unfold m a b -> Unfold m a b -- | Run a side effect whenever the unfold stops normally or aborts due to -- an exception. -- -- Prefer finallyIO over this as the after action in this -- combinator is not executed if the unfold is partially evaluated lazily -- and then garbage collected. -- -- Internal finally :: MonadCatch m => (a -> m c) -> Unfold m a b -> Unfold m a b -- | Run a side effect whenever the unfold stops normally, aborts due to an -- exception or if it is garbage collected after a partial lazy -- evaluation. -- -- Internal finallyIO :: (MonadAsync m, MonadCatch m) => (a -> m c) -> Unfold m a b -> Unfold m a b -- | bracket before after between runs the before action -- and then unfolds its output using the between unfold. When -- the between unfold is done or if an exception occurs then the -- after action is run with the output of before as -- argument. -- -- Prefer bracketIO over this as the after action in this -- combinator is not executed if the unfold is partially evaluated lazily -- and then garbage collected. -- -- Internal bracket :: MonadCatch m => (a -> m c) -> (c -> m d) -> Unfold m c b -> Unfold m a b -- | bracket before after between runs the before action -- and then unfolds its output using the between unfold. When -- the between unfold is done or if an exception occurs then the -- after action is run with the output of before as -- argument. The after action is also executed if the unfold is paritally -- evaluated and then garbage collected. -- -- Internal bracketIO :: (MonadAsync m, MonadCatch m) => (a -> m c) -> (c -> m d) -> Unfold m c b -> Unfold m a b -- | When unfolding if an exception occurs, unfold the exception using the -- exception unfold supplied as the first argument to handle. -- -- Internal handle :: (MonadCatch m, Exception e) => Unfold m e b -> Unfold m a b -> Unfold m a b -- | Unfold type represents an effectful action that generates a -- stream of values from a single starting value often called a seed -- value. Values can be generated and pulled from the -- Unfold one at a time. It can also be called a producer or a -- source of stream. It is a data representation of the standard -- unfoldr function. An Unfold can be converted into a -- stream type using unfold by supplying the seed. -- --

Performance Notes

-- -- Unfold representation is more efficient than using streams when -- combining streams. Unfold type allows multiple unfold actions -- to be composed into a single unfold function in an efficient manner by -- enabling the compiler to perform stream fusion optimization. -- Unfold m a b can be considered roughly equivalent to an -- action a -> t m b (where t is a stream type). -- Instead of using an Unfold one could just use a function of the -- shape a -> t m b. However, working with stream types like -- SerialT does not allow the compiler to perform stream fusion -- optimization when merging, appending or concatenating multiple -- streams. Even though stream based combinator have excellent -- performance, they are much less efficient when compared to combinators -- using Unfold. For example, the concatMap combinator -- which uses a -> t m b (where t is a stream type) -- to generate streams is much less efficient compared to -- concatUnfold. -- -- On the other hand, transformation operations on stream types are as -- efficient as transformations on Unfold. -- -- We should note that in some cases working with stream types may be -- more convenient compared to working with the Unfold type. -- However, if extra performance boost is important then Unfold -- based composition should be preferred compared to stream based -- composition when merging or concatenating streams. -- --

Programmer Notes

-- --
--   import qualified Streamly.Data.Unfold as UF
--   
-- -- More, not yet exposed, unfold combinators can be found in -- Streamly.Internal.Data.Unfold. 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 module Streamly.Internal.Data.Stream.Prelude fromStreamS :: (IsStream t, Monad m) => Stream m a -> t m a toStreamS :: (IsStream t, Monad m) => t m a -> Stream m a 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 :: (Monad m, IsStream t) => t m a -> m [a] foldrM :: (Monad m, IsStream t) => (a -> m b -> m b) -> m b -> t m a -> m b foldrMx :: (Monad m, IsStream t) => (a -> m x -> m x) -> m x -> (m x -> m b) -> t m a -> m b foldr :: (Monad m, IsStream t) => (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' :: (Monad m, IsStream t) => (b -> a -> b) -> b -> t m a -> m b runFold :: (Monad m, IsStream t) => Fold m a b -> t m a -> m b parselMx' :: (IsStream t, MonadThrow m) => (s -> a -> m (Step s b)) -> m s -> (s -> m b) -> t m a -> m b 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 -- | 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. scanlx' :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b scanlMx' :: (IsStream t, Monad m) => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> t m b postscanlx' :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b postscanlMx' :: (IsStream t, Monad m) => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> t 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 minimum :: (IsStream t, Monad m, Ord a) => t m a -> m (Maybe a) maximum :: (IsStream t, Monad m, Ord a) => t m a -> m (Maybe 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. concatMapBy :: IsStream t => (forall c. t m c -> t m c -> t m c) -> (a -> t m b) -> t m a -> t m b concatMap :: IsStream t => (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. -- --
--   foldWith async $ map return [1..3]
--   
-- -- Equivalent to: -- --
--   foldWith f = S.foldMapWith f id
--   
-- -- Since: 0.1.0 (Streamly) foldWith :: (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. -- --
--   foldMapWith async return [1..3]
--   
-- -- Equivalent to: -- --
--   foldMapWith f g xs = S.concatMapWith f g (S.fromFoldable xs)
--   
-- -- Since: 0.1.0 (Streamly) foldMapWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b -- | Like foldMapWith but with the last two arguments reversed i.e. -- the monadic streaming function is the last argument. -- -- Equivalent to: -- --
--   forEachWith = flip S.foldMapWith
--   
-- -- Since: 0.1.0 (Streamly) forEachWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b module Streamly.Internal.Data.Stream.Zip -- | The applicative instance of ZipSerialM zips a number of streams -- serially i.e. it produces one element from each stream serially and -- then zips all those elements. -- --
--   main = (toList . zipSerially $ (,,) <$> s1 <*> s2 <*> s3) >>= print
--       where s1 = fromFoldable [1, 2]
--             s2 = fromFoldable [3, 4]
--             s3 = fromFoldable [5, 6]
--   
-- --
--   [(1,3,5),(2,4,6)]
--   
-- -- The Semigroup instance of this type works the same way as that -- of SerialT. data ZipSerialM m a -- | An IO stream whose applicative instance zips streams serially. type ZipSerial = ZipSerialM IO -- | Fix the type of a polymorphic stream as ZipSerialM. zipSerially :: IsStream t => ZipSerialM m a -> t m a -- | Like ZipSerialM but zips in parallel, it generates all the -- elements to be zipped concurrently. -- --
--   main = (toList . zipAsyncly $ (,,) <$> s1 <*> s2 <*> s3) >>= print
--       where s1 = fromFoldable [1, 2]
--             s2 = fromFoldable [3, 4]
--             s3 = fromFoldable [5, 6]
--   
-- --
--   [(1,3,5),(2,4,6)]
--   
-- -- The Semigroup instance of this type works the same way as that -- of SerialT. data ZipAsyncM m a -- | An IO stream whose applicative instance zips streams wAsyncly. type ZipAsync = ZipAsyncM IO -- | Fix the type of a polymorphic stream as ZipAsyncM. zipAsyncly :: IsStream t => ZipAsyncM m a -> t m a -- | Zip two streams serially using a pure zipping function. -- --
--   > 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 generated concurrently. zipAsyncWith :: (IsStream t, MonadAsync m) => (a -> b -> c) -> t m a -> t m b -> t m c -- | Like zipWithM but zips concurrently i.e. both the streams being -- zipped are generated concurrently. zipAsyncWithM :: (IsStream t, MonadAsync m) => (a -> b -> m c) -> t m a -> t m b -> t m c -- | Deprecated: Please use ZipSerialM instead. type ZipStream = ZipSerialM -- | Same as zipSerially. -- | Deprecated: Please use zipSerially instead. zipping :: IsStream t => ZipSerialM m a -> t m a -- | Same as zipAsyncly. -- | Deprecated: Please use zipAsyncly instead. zippingAsync :: IsStream t => ZipAsyncM m a -> t m a 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 Streamly.Internal.Data.Stream.StreamK.Type.IsStream Streamly.Internal.Data.Stream.Zip.ZipAsyncM instance GHC.Base.Monad m => GHC.Base.Functor (Streamly.Internal.Data.Stream.Zip.ZipAsyncM m) instance Streamly.Internal.Data.SVar.MonadAsync m => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Zip.ZipAsyncM m) instance Streamly.Internal.Data.Stream.StreamK.Type.IsStream Streamly.Internal.Data.Stream.Zip.ZipSerialM 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.Serial -- | The Semigroup operation for SerialT behaves like a -- regular append operation. Therefore, when a <> b is -- evaluated, stream a is evaluated first until it exhausts and -- then stream b is evaluated. In other words, the elements of -- stream b are appended to the elements of stream a. -- This operation can be used to fold an infinite lazy container of -- streams. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   
--   main = (S.toList . serially $ (S.fromList [1,2]) <> (S.fromList [3,4])) >>= print
--   
-- --
--   [1,2,3,4]
--   
-- -- The Monad instance runs the monadic continuation for -- each element of the stream, serially. -- --
--   main = S.drain . serially $ do
--       x <- return 1 <> return 2
--       S.yieldM $ print x
--   
-- --
--   1
--   2
--   
-- -- SerialT nests streams serially in a depth first manner. -- --
--   main = S.drain . serially $ do
--       x <- return 1 <> return 2
--       y <- return 3 <> return 4
--       S.yieldM $ print (x, y)
--   
-- --
--   (1,3)
--   (1,4)
--   (2,3)
--   (2,4)
--   
-- -- We call the monadic code being run for each element of the stream a -- monadic continuation. In imperative paradigm we can think of this -- composition as nested for loops and the monadic continuation -- is the body of the loop. The loop iterates for all elements of the -- stream. -- -- Note that the behavior and semantics of SerialT, including -- Semigroup and Monad instances are exactly like Haskell -- lists except that SerialT can contain effectful actions while -- lists are pure. -- -- In the code above, the serially combinator can be omitted as -- the default stream type is SerialT. data SerialT m a -- | A serial IO stream of elements of type a. See SerialT -- documentation for more details. type Serial = SerialT IO -- | Polymorphic version of the Semigroup operation <> -- of SerialT. Appends two streams sequentially, yielding all -- elements from the first stream, and then all elements from the second -- stream. serial :: IsStream t => t m a -> t m a -> t m a -- | Fix the type of a polymorphic stream as SerialT. serially :: IsStream t => SerialT m a -> t m a -- | The Semigroup operation for WSerialT interleaves the -- elements from the two streams. Therefore, when a <> b -- is evaluated, stream a is evaluated first to produce the -- first element of the combined stream and then stream b is -- evaluated to produce the next element of the combined stream, and then -- we go back to evaluating stream a and so on. In other words, -- the elements of stream a are interleaved with the elements of -- stream b. -- -- Note that evaluation of a <> b <> c does not -- schedule a, b and c with equal priority. -- This expression is equivalent to a <> (b <> c), -- therefore, it fairly interleaves a with the result of b -- <> c. For example, S.fromList [1,2] <> S.fromList -- [3,4] <> S.fromList [5,6] :: WSerialT Identity Int would -- result in [1,3,2,5,4,6]. In other words, the leftmost stream gets the -- same scheduling priority as the rest of the streams taken together. -- The same is true for each subexpression on the right. -- -- Note that this operation cannot be used to fold a container of -- infinite streams as the state that it needs to maintain is -- proportional to the number of streams. -- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- SerialT. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   
--   main = (S.toList . wSerially $ (S.fromList [1,2]) <> (S.fromList [3,4])) >>= print
--   
-- --
--   [1,3,2,4]
--   
-- -- Similarly, the Monad instance interleaves the iterations of the -- inner and the outer loop, nesting loops in a breadth first manner. -- --
--   main = S.drain . wSerially $ do
--       x <- return 1 <> return 2
--       y <- return 3 <> return 4
--       S.yieldM $ print (x, y)
--   
-- --
--   (1,3)
--   (2,3)
--   (1,4)
--   (2,4)
--   
data WSerialT m a -- | An interleaving serial IO stream of elements of type a. See -- WSerialT documentation for more details. type WSerial = WSerialT IO -- | Polymorphic version of the Semigroup operation <> -- of WSerialT. 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 :: IsStream t => t m a -> t m a -> t m a -- | Like wSerial but stops interleaving as soon as the first stream -- stops. wSerialFst :: IsStream t => t m a -> t m a -> t m a -- | Like wSerial but stops interleaving as soon as any of the two -- streams stops. wSerialMin :: IsStream t => t m a -> t m a -> t m a -- | Fix the type of a polymorphic stream as WSerialT. wSerially :: IsStream t => WSerialT m a -> 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 > 3
--           then return Nothing
--           else print b >> return (Just (b, b + 1))
--   in drain $ unfoldrM f 0
--   
-- --
--   0
--   1
--   2
--   3
--   
-- -- Internal unfoldrM :: (IsStream t, Monad m) => (b -> m (Maybe (a, b))) -> b -> 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 mapM :: (IsStream t, Monad m) => (a -> m b) -> t m a -> t m b -- | Deprecated: Please use SerialT instead. type StreamT = SerialT -- | Deprecated: Please use WSerialT instead. type InterleavedT = WSerialT -- | Same as wSerial. -- | Deprecated: Please use wSerial instead. (<=>) :: IsStream t => t m a -> t m a -> t m a infixr 5 <=> -- | Same as wSerially. -- | Deprecated: Please use wSerially instead. interleaving :: IsStream t => WSerialT m a -> t m a 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 Streamly.Internal.Data.Stream.StreamK.Type.IsStream 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 Streamly.Internal.Data.Stream.StreamK.Type.IsStream Streamly.Internal.Data.Stream.Serial.SerialT 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) -- | 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.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. fromListN :: Storable a => Int -> [a] -> Array a -- | Create an Array from a list. The list must be of finite size. 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. -- -- Internal 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. -- -- Internal 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. 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. -- -- Internal 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. write :: forall m a. (MonadIO m, Storable a) => Fold m a (Array a) -- | Convert an Array into a list. toList :: Storable a => Array a -> [a] -- | Convert an Array into a stream. -- -- Internal toStream :: (Monad m, IsStream t, Storable a) => Array a -> t m a -- | Convert an Array into a stream in reverse order. -- -- Internal toStreamRev :: (Monad m, IsStream t, Storable a) => Array a -> t m a -- | Unfold an array into a stream. 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. -- -- Internal unsafeRead :: 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. length :: forall a. Storable a => Array a -> Int -- |
--   null arr = length arr == 0
--   
-- -- Internal null :: Storable a => Array a -> Bool -- |
--   last arr = readIndex arr (length arr - 1)
--   
-- -- Internal last :: Storable a => Array a -> Maybe a -- | O(1) Lookup the element at the given index, starting from 0. -- -- Internal readIndex :: 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 -- | O(1) Write the given element at the given index in the array. -- Performs in-place mutation of the array. -- -- Internal writeIndex :: (MonadIO m, Storable a) => Array a -> Int -> a -> m () -- | Transform an array into another array using a stream transformation -- operation. -- -- Internal 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. -- -- Internal streamFold :: (MonadIO m, Storable a) => (SerialT m a -> m b) -> Array a -> m b -- | Fold an array using a Fold. -- -- Internal fold :: forall m a b. (MonadIO m, Storable a) => Fold m a b -> Array a -> m b -- | Take last n elements from the stream and discard the rest. lastN :: (Storable a, MonadIO m) => Int -> Fold m a (Array a) -- | 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.Memory.Array. 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. fromListN :: Storable a => Int -> [a] -> Array a -- | Create an Array from a list. The list must be of finite size. fromList :: Storable a => [a] -> Array a -- | writeN n folds a maximum of n elements from the -- input stream to an 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. write :: forall m a. (MonadIO m, Storable a) => Fold m a (Array a) -- | Convert an Array into a list. toList :: Storable a => Array a -> [a] -- | Unfold an array into a stream. 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. length :: forall a. Storable a => Array a -> Int module Streamly.Internal.Data.Stream.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. 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. 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: -- -- 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. 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. 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. 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. constRate :: IsStream t => Double -> t m a -> t m a -- | Print debug information about an SVar when the stream ends -- -- Internal 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.Parallel -- | Async composition with strict concurrent execution of all streams. -- -- The Semigroup instance of ParallelT executes both the -- streams concurrently without any delay or without waiting for the -- consumer demand and merges the results as they arrive. If the -- consumer does not consume the results, they are buffered upto a -- configured maximum, controlled by the maxBuffer primitive. If -- the buffer becomes full the concurrent tasks will block until there is -- space in the buffer. -- -- Both WAsyncT and ParallelT, evaluate the constituent -- streams fairly in a round robin fashion. The key difference is that -- WAsyncT might wait for the consumer demand before it executes -- the tasks whereas ParallelT starts executing all the tasks -- immediately without waiting for the consumer demand. For -- WAsyncT the maxThreads limit applies whereas for -- ParallelT it does not apply. In other words, WAsyncT -- can be lazy whereas ParallelT is strict. -- -- ParallelT is useful for cases when the streams are required to -- be evaluated simultaneously irrespective of how the consumer consumes -- them e.g. when we want to race two tasks and want to start both -- strictly at the same time or if we have timers in the parallel tasks -- and our results depend on the timers being started at the same time. -- If we do not have such requirements then AsyncT or -- AheadT are recommended as they can be more efficient than -- ParallelT. -- --
--   main = (toList . parallely $ (fromFoldable [1,2]) <> (fromFoldable [3,4])) >>= print
--   
-- --
--   [1,3,2,4]
--   
-- -- When streams with more than one element are merged, it yields -- whichever stream yields first without any bias, unlike the -- Async style streams. -- -- Any exceptions generated by a constituent stream are propagated to the -- output stream. The output and exceptions from a single stream are -- guaranteed to arrive in the same order in the resulting stream as they -- were generated in the input stream. However, the relative ordering of -- elements from different streams in the resulting stream can vary -- depending on scheduling and generation delays. -- -- Similarly, the Monad instance of ParallelT runs -- all iterations of the loop concurrently. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   import Control.Concurrent
--   
--   main = drain . parallely $ do
--       n <- return 3 <> return 2 <> return 1
--       S.yieldM $ do
--            threadDelay (n * 1000000)
--            myThreadId >>= \tid -> putStrLn (show tid ++ ": Delay " ++ show n)
--   
-- --
--   ThreadId 40: Delay 1
--   ThreadId 39: Delay 2
--   ThreadId 38: Delay 3
--   
-- -- Note that parallel composition can only combine a finite number of -- streams as it needs to retain state for each unfinished stream. -- -- Since: 0.7.0 (maxBuffer applies to ParallelT streams) -- -- Since: 0.1.0 data ParallelT m a -- | A parallely composing IO stream of elements of type a. See -- ParallelT documentation for more details. type Parallel = ParallelT IO -- | Fix the type of a polymorphic stream as ParallelT. parallely :: IsStream t => ParallelT m a -> t m a -- | Polymorphic version of the Semigroup operation <> -- of ParallelT Merges two streams concurrently. parallel :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | Like parallel but stops the output as soon as the first stream -- stops. -- -- Internal 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. -- -- Internal parallelMin :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | Generate a stream asynchronously to keep it buffered, lazily consume -- from the buffer. -- -- Internal mkParallel :: (IsStream t, MonadAsync m) => 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. -- -- Internal tapAsync :: (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. -- --
--   >>> S.drain $ distributeAsync_ [S.mapM_ print, S.mapM_ print] (S.enumerateFromTo 1 2)
--   
-- --
--   distributeAsync_ = flip (foldr tapAsync)
--   
-- -- Internal distributeAsync_ :: (Foldable f, IsStream t, MonadAsync m) => f (t m a -> m b) -> t m a -> t m a instance Control.Monad.Trans.Class.MonadTrans Streamly.Internal.Data.Stream.Parallel.ParallelT instance Streamly.Internal.Data.Stream.StreamK.Type.IsStream Streamly.Internal.Data.Stream.Parallel.ParallelT instance Streamly.Internal.Data.SVar.MonadAsync m => GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Parallel.ParallelT m a) instance Streamly.Internal.Data.SVar.MonadAsync m => GHC.Base.Monoid (Streamly.Internal.Data.Stream.Parallel.ParallelT m a) instance (GHC.Base.Monad m, Streamly.Internal.Data.SVar.MonadAsync m) => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance Streamly.Internal.Data.SVar.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.Data.SVar.MonadAsync m) => Control.Monad.Base.MonadBase b (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance (Control.Monad.IO.Class.MonadIO m, Streamly.Internal.Data.SVar.MonadAsync m) => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance (Control.Monad.Catch.MonadThrow m, Streamly.Internal.Data.SVar.MonadAsync m) => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.Parallel.ParallelT m) instance (Control.Monad.Reader.Class.MonadReader r m, Streamly.Internal.Data.SVar.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.Data.SVar.MonadAsync m) => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Stream.Parallel.ParallelT m) -- | 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.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. -- --
--   > S.toList $ S.take 4 $ S.enumerateFrom (0 :: Int)
--   [0,1,2,3]
--   
-- -- For Fractional types, enumeration is numerically stable. -- However, no overflow or underflow checks are performed. -- --
--   > S.toList $ S.take 4 $ S.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. -- --
--   > S.toList $ S.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. -- --
--   > S.toList $ S.enumerateFromTo 1.1 4
--   [1.1,2.1,3.1,4.1]
--   > S.toList $ S.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. -- --
--   > S.toList $ S.take 4 $ S.enumerateFromThen 0 2
--   [0,2,4,6]
--   > S.toList $ S.take 4 $ S.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. -- --
--   > S.toList $ S.enumerateFromThenTo 0 2 6
--   [0,2,4,6]
--   > S.toList $ S.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. -- --
--   > S.toList $ S.take 4 $ S.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. -- --
--   > S.toList $ S.take 4 $ S.enumerateFromThenIntegral (0 :: Int) 2
--   [0,2,4,6]
--   > S.toList $ S.take 4 $ S.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. -- --
--   > S.toList $ S.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. -- --
--   > S.toList $ S.enumerateFromThenToIntegral 0 2 6
--   [0,2,4,6]
--   > S.toList $ S.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. -- --
--   > S.toList $ S.take 4 $ S.enumerateFromStepIntegral 0 2
--   [0,2,4,6]
--   > S.toList $ S.take 3 $ S.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: -- --
--   > S.toList $ S.take 4 $ S.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: -- --
--   > S.toList $ S.enumerateFromToFractional 1.1 4
--   [1.1,2.1,3.1,4.1]
--   > S.toList $ S.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: -- --
--   > S.toList $ S.take 4 $ S.enumerateFromThenFractional 1.1 2.1
--   [1.1,2.1,3.1,4.1]
--   > S.toList $ S.take 4 $ S.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: -- --
--   > S.toList $ S.enumerateFromThenToFractional 0.1 2 6
--   [0.1,2.0,3.9,5.799999999999999]
--   > S.toList $ S.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.Enumeration.Enumerable () instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Types.Bool instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Types.Ordering instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Types.Char instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Types.Int instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Int.Int8 instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Int.Int16 instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Int.Int32 instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Int.Int64 instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Types.Word instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Word.Word8 instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Word.Word16 instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Word.Word32 instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Word.Word64 instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Num.Integer.Integer instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Num.Natural.Natural instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Types.Float instance Streamly.Internal.Data.Stream.Enumeration.Enumerable GHC.Types.Double instance Data.Fixed.HasResolution a => Streamly.Internal.Data.Stream.Enumeration.Enumerable (Data.Fixed.Fixed a) instance GHC.Real.Integral a => Streamly.Internal.Data.Stream.Enumeration.Enumerable (GHC.Real.Ratio a) instance Streamly.Internal.Data.Stream.Enumeration.Enumerable a => Streamly.Internal.Data.Stream.Enumeration.Enumerable (Data.Functor.Identity.Identity a) -- | This is an Internal module consisting of released, unreleased and -- unimplemented APIs. For stable and released APIs please see -- Streamly.Prelude module. This module provides documentation -- only for the unreleased and unimplemented APIs. For documentation on -- released APIs please see Streamly.Prelude module. module Streamly.Internal.Prelude -- | An empty stream. -- --
--   > toList nil
--   []
--   
nil :: IsStream t => t m a -- | An empty stream producing a side effect. -- --
--   > toList (nilM (print "nil"))
--   "nil"
--   []
--   
-- -- Internal 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 parallely 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 $ serially  $ delay |: delay |: delay |: nil
--   drain $ parallely $ delay |: delay |: delay |: nil
--   
-- -- Concurrent (do not use parallely to construct infinite -- streams) (|:) :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 |: -- |
--   yield a = a `cons` nil
--   
-- -- Create a singleton stream from a pure value. -- -- The following holds in monadic streams, but not in Zip streams: -- --
--   yield = pure
--   yield = yieldM . pure
--   
-- -- In Zip applicative streams yield is not the same as pure -- because in that case pure is equivalent to repeat -- instead. yield and pure are equally efficient, in other -- cases yield may be slightly more efficient than the other -- equivalent definitions. yield :: IsStream t => a -> t m a -- |
--   yieldM m = m `consM` nil
--   
-- -- Create a singleton stream from a monadic action. -- --
--   > toList $ yieldM getLine
--   hello
--   ["hello"]
--   
yieldM :: (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 . yieldM
--   
-- -- Generate a stream by repeatedly executing a monadic action forever. -- --
--   drain $ serially $ S.take 10 $ S.repeatM $ (threadDelay 1000000 >> print 1)
--   drain $ asyncly  $ S.take 10 $ S.repeatM $ (threadDelay 1000000 >> print 1)
--   
-- -- Concurrent, infinite (do not use with parallely) repeatM :: (IsStream t, MonadAsync m) => m a -> t m a -- |
--   replicate = take n . repeat
--   
-- -- Generate a stream of length n by repeating a value n -- times. replicate :: (IsStream t, Monad m) => Int -> a -> t m a -- |
--   replicateM = take n . repeatM
--   
-- -- Generate a stream by performing a monadic action n times. -- Same as: -- --
--   drain $ serially $ S.replicateM 10 $ (threadDelay 1000000 >> print 1)
--   drain $ asyncly  $ S.replicateM 10 $ (threadDelay 1000000 >> print 1)
--   
-- -- Concurrent replicateM :: (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. -- --
--   > S.toList $ S.take 4 $ S.enumerateFrom (0 :: Int)
--   [0,1,2,3]
--   
-- -- For Fractional types, enumeration is numerically stable. -- However, no overflow or underflow checks are performed. -- --
--   > S.toList $ S.take 4 $ S.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. -- --
--   > S.toList $ S.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. -- --
--   > S.toList $ S.enumerateFromTo 1.1 4
--   [1.1,2.1,3.1,4.1]
--   > S.toList $ S.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. -- --
--   > S.toList $ S.take 4 $ S.enumerateFromThen 0 2
--   [0,2,4,6]
--   > S.toList $ S.take 4 $ S.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. -- --
--   > S.toList $ S.enumerateFromThenTo 0 2 6
--   [0,2,4,6]
--   > S.toList $ S.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 -- |
--   unfoldr step s =
--       case step s of
--           Nothing -> nil
--           Just (a, b) -> a `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 > 3
--           then Nothing
--           else Just (b, b + 1)
--   in toList $ unfoldr f 0
--   
-- --
--   [0,1,2,3]
--   
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 > 3
--           then return Nothing
--           else print b >> return (Just (b, b + 1))
--   in drain $ unfoldrM f 0
--   
-- --
--   0
--   1
--   2
--   3
--   
-- -- 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. -- --
--   (asyncly $ S.unfoldrM (\n -> liftIO (threadDelay 1000000) >> return (Just (n, n + 1))) 0)
--       & S.foldlM' (\_ a -> threadDelay 1000000 >> print a) ()
--   
-- -- Concurrent -- -- Since: 0.1.0 unfoldrM :: (IsStream t, MonadAsync m) => (b -> m (Maybe (a, b))) -> b -> t m a -- | Convert an Unfold into a stream by supplying it an input seed. -- --
--   >>> unfold (UF.replicateM 10) (putStrLn "hello")
--   
-- -- Since: 0.7.0 unfold :: (IsStream t, Monad m) => Unfold m a b -> a -> t m b -- |
--   iterate f x = x `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. -- --
--   > S.toList $ S.take 5 $ S.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 `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. -- -- 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. -- --
--   drain $ serially $ S.take 10 $ S.iterateM
--        (\x -> threadDelay 1000000 >> print x >> return (x + 1)) (return 0)
--   
--   drain $ asyncly  $ S.take 10 $ S.iterateM
--        (\x -> threadDelay 1000000 >> print x >> return (x + 1)) (return 0)
--   
-- -- Concurrent -- -- Since: 0.7.0 (signature change) -- -- Since: 0.1.2 iterateM :: (IsStream t, MonadAsync m) => (a -> m a) -> m a -> t m a -- |
--   fromIndices f = let g i = f i `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. -- --
--   > S.toList $ S.take 5 $ S.fromIndices id
--   [0,1,2,3,4]
--   
fromIndices :: (IsStream t, Monad m) => (Int -> a) -> t m a -- |
--   fromIndicesM f = let g i = f i `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 :: (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 = foldr consM 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 = foldr cons nil
--   
-- -- Construct a stream from a Foldable containing pure values: fromFoldable :: (IsStream t, Foldable f) => f a -> t m a -- |
--   fromFoldableM = foldr consM nil
--   
-- -- Construct a stream from a Foldable containing monadic actions. -- --
--   drain $ serially $ S.fromFoldableM $ replicateM 10 (threadDelay 1000000 >> print 1)
--   drain $ asyncly  $ S.fromFoldableM $ replicateM 10 (threadDelay 1000000 >> print 1)
--   
-- -- Concurrent (do not use with parallely on infinite -- containers) fromFoldableM :: (IsStream t, MonadAsync m, Foldable f) => f (m a) -> t m a -- | Construct a stream by reading a Prim Var repeatedly. -- -- Internal fromPrimVar :: (IsStream t, MonadIO m, Prim a) => Var IO 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. -- -- Internal fromCallback :: MonadAsync m => ((a -> m ()) -> m ()) -> SerialT m a -- | currentTime 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. -- -- Note: This API is not safe on 32-bit machines. -- -- Internal currentTime :: (IsStream t, MonadAsync m) => Double -> t m AbsTime -- | 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. uncons :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (a, t m a)) -- |
--   tail = fmap (fmap snd) . 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: -- --
--   >>> S.foldrM (\x xs -> if odd x then return True else xs) (return False) $ S.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 to a streaming monad. -- --
--   foldrS S.cons S.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. -- --
--   >>> S.toList $ S.foldrS S.cons S.nil $ S.fromList [1..5]
--   > [1,2,3,4,5]
--   
-- -- Find if any element in the stream is True: -- --
--   >>> S.toList $ S.foldrS (\x xs -> if odd x then return True else xs) (return False) $ (S.fromList (2:4:5:undefined) :: SerialT IO Int)
--   > [True]
--   
-- -- Map (+2) on odd elements and filter out the even elements: -- --
--   >>> S.toList $ S.foldrS (\x xs -> if odd x then (x + 2) `S.cons` xs else xs) S.nil $ (S.fromList [1..5] :: 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
--   
-- -- Internal foldrS :: 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. -- -- Internal 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 -- | 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. foldlM' :: Monad m => (b -> a -> m b) -> b -> SerialT m a -> m b -- | Fold a stream using the supplied left fold. -- --
--   >>> S.fold FL.sum (S.enumerateFromTo 1 100)
--   5050
--   
fold :: Monad m => Fold m a b -> SerialT m a -> m b -- | Parse a stream using the supplied Parse. -- -- Internal parse :: MonadThrow m => Parser m a b -> SerialT m a -> m b -- | 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. -- --
--   S.foldlM' (\_ a -> threadDelay 1000000 >> print a) ()
--      |$. S.repeatM (threadDelay 1000000 >> return 1)
--   
-- -- Concurrent (|$.) :: (IsStream t, MonadAsync m) => (t m a -> m b) -> t m a -> m b infixr 0 |$. -- | Parallel reverse function application operator for applying a run or -- fold functions to a stream. Just like |$. except that the -- operands are reversed. -- --
--       S.repeatM (threadDelay 1000000 >> return 1)
--   |&. S.foldlM' (\_ a -> threadDelay 1000000 >> print a) ()
--   
-- -- Concurrent (|&.) :: (IsStream t, MonadAsync m) => t m a -> (t m a -> m b) -> m b infixl 1 |&. -- |
--   drain = mapM_ (\_ -> return ())
--   
-- -- 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 drain . asyncly. drain :: Monad m => SerialT m a -> m () -- | Extract the last element of the stream, if any. -- --
--   last xs = xs !! (length xs - 1)
--   
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 :: (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 :: (Monad m, Num a) => SerialT m a -> m a -- | Fold a stream of monoid elements by appending them. -- -- Internal mconcat :: (Monad m, Monoid a) => SerialT m a -> m a -- | Determine the maximum element in a stream using the supplied -- comparison function. maximumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) -- |
--   maximum = maximumBy compare
--   
-- -- 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 :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) -- |
--   minimum = minimumBy compare
--   
-- -- 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) -- |
--   toList = S.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 = S.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. -- -- Internal toListRev :: Monad m => SerialT m a -> m [a] -- | Convert a stream to a pure stream. -- --
--   toPure = foldr cons nil
--   
-- -- Internal toPure :: Monad m => SerialT m a -> m (SerialT Identity a) -- | Convert a stream to a pure stream in reverse order. -- --
--   toPureRev = foldl' (flip cons) nil
--   
-- -- Internal toPureRev :: Monad m => SerialT m a -> m (SerialT Identity 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.Array -- instead. -- -- Internal toStream :: Monad m => Fold m a (SerialT Identity a) -- | Buffers the input stream to a pure stream in the reverse order of the -- input. -- -- Warning! working on large streams accumulated as buffers in -- memory could be very inefficient, consider using Streamly.Array -- instead. -- -- Internal toStreamRev :: Monad m => Fold m a (SerialT Identity a) -- |
--   drainN n = drain . take n
--   
-- -- Run maximum up to n iterations of a stream. drainN :: Monad m => Int -> SerialT m a -> m () -- |
--   drainWhile p = drain . 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 :: 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. -- -- Internal headElse :: Monad m => a -> SerialT m a -> m a -- | Returns the first element that satisfies the given predicate. 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 :: 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 <$> find ((==) . fst)
--   
lookup :: (Monad m, Eq a) => a -> SerialT m (a, b) -> m (Maybe b) -- | Returns the first index that satisfies the given predicate. 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 = findIndex (== a)
--   
elemIndex :: (Monad m, Eq a) => a -> SerialT m a -> m (Maybe Int) -- | Determine whether the stream is empty. null :: Monad m => SerialT m a -> m Bool -- | Determine whether an element is present in the stream. elem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool -- | Determine whether an element is not present in the stream. notElem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool -- | Determine whether all elements of a stream satisfy a predicate. all :: Monad m => (a -> Bool) -> SerialT m a -> m Bool -- | Determine whether any of the elements of a stream satisfy a predicate. any :: Monad m => (a -> Bool) -> SerialT m a -> m Bool -- | Determines if all elements of a boolean stream are True. and :: Monad m => SerialT m Bool -> m Bool -- | Determines whether at least one element of a boolean stream is True. or :: Monad m => SerialT m Bool -> m Bool -- | 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. -- --
--   > S.isPrefixOf (S.fromList "hello") (S.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 a suffix of the second. A -- stream is considered a suffix of itself. -- --
--   > S.isSuffixOf (S.fromList "hello") (S.fromList "hello" :: SerialT IO Char)
--   True
--   
-- -- Space: O(n), buffers entire input stream and the suffix. -- -- Internal -- -- Suboptimal - Help wanted. isSuffixOf :: (Monad m, Eq a) => SerialT m a -> SerialT m a -> m Bool -- | Returns True if the first stream is an infix of the second. A -- stream is considered an infix of itself. -- --
--   > S.isInfixOf (S.fromList "hello") (S.fromList "hello" :: SerialT IO Char)
--   True
--   
-- -- Space: O(n) worst case where n is the length of the -- infix. -- -- Internal -- -- Requires Storable constraint - Help wanted. isInfixOf :: (MonadIO m, Eq a, Enum a, Storable 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. -- --
--   > S.isSubsequenceOf (S.fromList "hlo") (S.fromList "hello" :: SerialT IO Char)
--   True
--   
isSubsequenceOf :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m Bool -- | Strip prefix if present and tell whether it was stripped or not. -- 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. -- -- 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. -- -- Space: O(n), buffers the entire input stream as well as the -- suffix -- -- Internal stripSuffix :: (Monad m, Eq a) => SerialT m a -> SerialT m a -> m (Maybe (SerialT m a)) -- | 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 -- | Use a Pipe to transform a stream. -- -- Internal transform :: (IsStream t, Monad m) => Pipe m a b -> t m a -> t 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 $ S.sequence $ S.fromList [putStr "a", putStr "b", putStrLn "c"]
--   abc
--   
--   drain $ S.replicateM 10 (return $ threadDelay 1000000 >> print 1)
--             & (serially . S.sequence)
--   
--   drain $ S.replicateM 10 (return $ threadDelay 1000000 >> print 1)
--             & (asyncly . S.sequence)
--   
-- -- Concurrent (do not use with parallely 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 $ S.mapM putStr $ S.fromList ["a", "b", "c"]
--   abc
--   
--   drain $ S.replicateM 10 (return 1)
--             & (serially . S.mapM (\x -> threadDelay 1000000 >> print x))
--   
--   drain $ S.replicateM 10 (return 1)
--             & (asyncly . S.mapM (\x -> threadDelay 1000000 >> print x))
--   
-- -- Concurrent (do not use with parallely on infinite -- streams) mapM :: (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m b -- |
--   mapM_ = drain . 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. -- --
--   > S.drain $ S.trace print (S.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-----
--   
-- --
--   > S.drain $ S.tap (FL.drainBy print) (S.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. -- --
--   >>> S.drain $ S.tapOffsetEvery 0 2 (FL.mapM print FL.toList) $ S.enumerateFromTo 0 10
--   > [0,2,4,6,8,10]
--   
-- -- Internal 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-----
--   
-- --
--   > 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. -- -- Internal tapAsync :: (IsStream t, MonadAsync m) => Fold m a 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
--   > S.drain $ S.tapRate 2 (\n -> print $ show n ++ " elements processed") (delay 1 S.|: delay 0.5 S.|: delay 0.5 S.|: S.nil)
--   2 elements processed
--   1 elements processed
--   
-- -- Note: This may not work correctly on 32-bit machines. -- -- Internal 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: -- --
--   > S.drain $ S.pollCounts (const True) (S.rollingMap (-) . S.delayPost 1) (FL.drainBy print)
--             $ S.enumerateFrom 0
--   
-- -- Note: This may not work correctly on 32-bit machines. -- -- Internal pollCounts :: (IsStream t, MonadAsync m) => (a -> Bool) -> (t m Int -> t m Int) -> Fold m Int b -> 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. -- --
--   > S.toList $ S.scanl' (+) 0 $ fromList [1,2,3,4]
--   [0,1,3,6,10]
--   
-- --
--   > S.toList $ S.scanl' (flip (:)) [] $ S.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': -- --
--   > S.foldl' (\(s, p) x -> (s + x, p * x)) (0,1) $ S.fromList [1,2,3,4]
--   (10,24)
--   
-- -- 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: -- --
--   >   S.foldl' (\(_, p) (s, x) -> (s, p * x)) (0,1)
--     $ S.scanl' (\(s, _) x -> (s + x, x)) (0,1)
--     $ S.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' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b -- | Like scanl' but with a monadic fold function. scanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> b -> t m a -> t m b -- | Like scanl' but does not stream the initial value of the -- accumulator. -- --
--   postscanl' f z xs = S.drop 1 $ S.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. postscanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> b -> t m a -> t m b -- | Like scanl' but does not stream the final value of the accumulator. -- -- Internal prescanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b -- | Like postscanl' but with a monadic step function. -- -- Internal 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. -- --
--   > S.toList $ S.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. scan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | Postscan a stream using the given monadic fold. postscan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | 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. -- -- Internal 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. -- --
--   drain $
--      S.mapM (\x -> threadDelay 1000000 >> print x)
--        |$ S.repeatM (threadDelay 1000000 >> return 1)
--   
-- -- Concurrent (|$) :: (IsStream t, MonadAsync m) => (t m a -> t m b) -> t m a -> t m b infixr 0 |$ -- | Parallel reverse function application operator for streams; just like -- the regular reverse function application operator & -- except that it is concurrent. -- --
--   drain $
--         S.repeatM (threadDelay 1000000 >> return 1)
--      |& S.mapM (\x -> threadDelay 1000000 >> print x)
--   
-- -- Concurrent (|&) :: (IsStream t, MonadAsync m) => t m a -> (t m a -> t m b) -> t m b infixl 1 |& -- | 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 -- | 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 = S.map fromJust . S.filter isJust . S.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 = S.map fromJust . S.filter isJust . S.mapM f
--   
-- -- Concurrent (do not use with parallely on infinite -- streams) mapMaybeM :: (IsStream t, MonadAsync m, Functor (t m)) => (a -> m (Maybe b)) -> t m a -> t m b -- | Deletes the first occurrence of the element in the stream that -- satisfies the given equality predicate. -- --
--   > S.toList $ S.deleteBy (==) 3 $ S.fromList [1,3,3,5]
--   [1,3,5]
--   
deleteBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> a -> 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 -- | 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 (yield x)
--   
-- --
--   > S.toList $ S.insertBy compare 2 $ S.fromList [1,3,5]
--   [1,2,3,5]
--   
insertBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> a -> t m a -> t m a -- | Generate a stream by inserting the result of a monadic action between -- consecutive elements of the given stream. Note that the monadic action -- is performed after the stream action before which its result is -- inserted. -- --
--   > S.toList $ S.intersperseM (return ',') $ S.fromList "hello"
--   "h,e,l,l,o"
--   
intersperseM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a -- | Generate a stream by inserting a given element between consecutive -- elements of the given stream. -- --
--   > S.toList $ S.intersperse ',' $ S.fromList "hello"
--   "h,e,l,l,o"
--   
intersperse :: (IsStream t, MonadAsync m) => a -> t m a -> t m a -- | Insert a monadic action after each element in the stream. -- -- Internal intersperseSuffix :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a -- | Like intersperseSuffix but intersperses a monadic action into -- the input stream after every n elements and after the last -- element. -- --
--   > S.toList $ S.intersperseSuffixBySpan 2 (return ',') $ S.fromList "hello"
--   "he,ll,o,"
--   
-- -- Internal intersperseSuffixBySpan :: (IsStream t, MonadAsync m) => Int -> m a -> t m a -> t m a -- | Intersperse a monadic action into the input stream after every -- n seconds. -- --
--   > S.drain $ S.interjectSuffix 1 (putChar ',') $ S.mapM (\x -> threadDelay 1000000 >> putChar x) $ S.fromList "hello"
--   "h,e,l,l,o"
--   
-- -- Internal interjectSuffix :: (IsStream t, MonadAsync m) => Double -> m a -> t m a -> t m a -- | Introduces a delay of specified seconds after each element of a -- stream. -- -- Internal delayPost :: (IsStream t, MonadIO m) => Double -> t m a -> t m a -- |
--   indexed = S.postscanl' (\(i, _) x -> (i + 1, x)) (-1,undefined)
--   indexed = S.zipWith (,) (S.enumerateFrom 0)
--   
-- -- Pair each element in a stream with its index, starting from index 0. -- --
--   > S.toList $ S.indexed $ S.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 = S.postscanl' (\(i, _) x -> (i - 1, x)) (n + 1,undefined)
--   indexedR n = S.zipWith (,) (S.enumerateFromThen n (n - 1))
--   
-- -- Pair each element in a stream with its index, starting from the given -- index n and counting down. -- --
--   > S.toList $ S.indexedR 10 $ S.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) -- | Returns the elements of the stream in reverse order. The stream must -- be finite. Note that this necessarily buffers the entire stream in -- memory. -- -- 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. -- -- Internal reverse' :: (IsStream t, MonadIO m, Storable a) => t m a -> t m a -- | Apply a Parse repeatedly on a stream and emit the parsed -- values in the output stream. -- --
--   >>> S.toList $ S.splitParse (PR.take 2 $ PR.fromFold FL.sum) $ S.fromList [1..10]
--   > [3,7,11,15,19]
--   
-- --
--   >>> S.toList $ S.splitParse (PR.line FL.toList) $ S.fromList "hello\nworld"
--   > ["hello\n","world"]
--   
splitParse :: (IsStream t, MonadThrow m) => Parser m a b -> 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 -- | takeByTime 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. -- -- Internal takeByTime :: (MonadIO m, IsStream t, TimeUnit64 d) => d -> 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 -- | dropByTime 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. -- -- Internal dropByTime :: (MonadIO m, IsStream t, TimeUnit64 d) => d -> 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 -- | Group the input stream into groups of n elements each and -- then fold each group using the provided fold function. -- --
--   > S.toList $ S.chunksOf 2 FL.sum (S.enumerateFromTo 1 10)
--    [3,7,11,15,19]
--   
-- -- This can be considered as an n-fold version of ltake where we -- apply ltake repeatedly on the leftover stream until the -- stream exhausts. chunksOf :: (IsStream t, Monad m) => Int -> Fold m a b -> t m a -> t m b -- | Internal chunksOf2 :: (IsStream t, Monad m) => Int -> m c -> Fold2 m c 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 = S.chunksOf n (A.writeN n)
--   
-- -- Internal 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. intervalsOf :: (IsStream t, MonadAsync m) => Double -> Fold m a b -> t m a -> t m b -- | Find all the indices where the element in the stream satisfies the -- given predicate. 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 :: (IsStream t, Eq a, Monad m) => a -> t m a -> t m Int -- | Split on an infixed separator element, dropping the separator. Splits -- the stream on separator elements determined by the supplied predicate, -- separator is considered as infixed between two segments, if one side -- of the separator is missing then it is parsed as an empty stream. The -- supplied Fold is applied on the split segments. With - -- representing non-separator elements and . as separator, -- splitOn splits as follows: -- --
--   "--.--" => "--" "--"
--   "--."   => "--" ""
--   ".--"   => ""   "--"
--   
-- -- splitOn (== x) is an inverse of intercalate (S.yield -- x) -- -- Let's use the following definition for illustration: -- --
--   splitOn' p xs = S.toList $ S.splitOn p (FL.toList) (S.fromList xs)
--   
-- --
--   >>> splitOn' (== '.') ""
--   [""]
--   
-- --
--   >>> splitOn' (== '.') "."
--   ["",""]
--   
-- --
--   >>> splitOn' (== '.') ".a"
--   > ["","a"]
--   
-- --
--   >>> splitOn' (== '.') "a."
--   > ["a",""]
--   
-- --
--   >>> splitOn' (== '.') "a.b"
--   > ["a","b"]
--   
-- --
--   >>> splitOn' (== '.') "a..b"
--   > ["a","","b"]
--   
splitOn :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b -- | Like splitOn but the separator is considered as suffixed to the -- segments in the stream. A missing suffix at the end is allowed. A -- separator at the beginning is parsed as empty segment. With - -- representing elements and . as separator, splitOnSuffix -- splits as follows: -- --
--   "--.--." => "--" "--"
--   "--.--"  => "--" "--"
--   ".--."   => "" "--"
--   
-- --
--   splitOnSuffix' p xs = S.toList $ S.splitSuffixBy p (FL.toList) (S.fromList xs)
--   
-- --
--   >>> splitOnSuffix' (== '.') ""
--   []
--   
-- --
--   >>> splitOnSuffix' (== '.') "."
--   [""]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a"
--   ["a"]
--   
-- --
--   >>> splitOnSuffix' (== '.') ".a"
--   > ["","a"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a."
--   > ["a"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a.b"
--   > ["a","b"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a.b."
--   > ["a","b"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a..b.."
--   > ["a","","b",""]
--   
-- --
--   lines = splitOnSuffix (== '\n')
--   
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 = S.toList $ S.splitWithSuffix p (FL.toList) (S.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 = S.toList $ S.wordsBy p (FL.toList) (S.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 -- | 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 = S.toList $ S.splitOnSeq (A.fromList pat) (FL.toList) (S.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 . splitOn == id
--   
-- -- The following law holds when the separator is non-empty and contains -- none of the elements present in the input lists: -- --
--   splitOn . intercalate == id
--   
-- -- Internal 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. -- --
--   splitSuffixOn_ pat xs = S.toList $ S.splitSuffixOn (A.fromList pat) (FL.toList) (S.fromList xs)
--   
-- --
--   >>> splitSuffixOn_ "." ""
--   [""]
--   
-- --
--   >>> splitSuffixOn_ "." "."
--   [""]
--   
-- --
--   >>> splitSuffixOn_ "." "a"
--   ["a"]
--   
-- --
--   >>> splitSuffixOn_ "." ".a"
--   > ["","a"]
--   
-- --
--   >>> splitSuffixOn_ "." "a."
--   > ["a"]
--   
-- --
--   >>> splitSuffixOn_ "." "a.b"
--   > ["a","b"]
--   
-- --
--   >>> splitSuffixOn_ "." "a.b."
--   > ["a","b"]
--   
-- --
--   >>> splitSuffixOn_ "." "a..b.."
--   > ["a","","b",""]
--   
-- --
--   lines = splitSuffixOn "\n"
--   
-- -- Internal splitOnSuffixSeq :: (IsStream t, MonadIO m, Storable a, Enum a, Eq a) => Array a -> 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 = S.toList $ S.splitOn' (A.fromList pat) (FL.toList) (S.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"]
--   
-- -- Internal splitBySeq :: (IsStream t, MonadAsync m, Storable a, Enum a, Eq a) => Array a -> Fold m a b -> t m a -> t m b -- | Like splitSuffixOn but keeps the suffix intact in the splits. -- --
--   splitSuffixOn'_ pat xs = S.toList $ FL.splitSuffixOn' (A.fromList pat) (FL.toList) (S.fromList xs)
--   
-- --
--   >>> splitSuffixOn'_ "." ""
--   [""]
--   
-- --
--   >>> splitSuffixOn'_ "." "."
--   ["."]
--   
-- --
--   >>> splitSuffixOn'_ "." "a"
--   ["a"]
--   
-- --
--   >>> splitSuffixOn'_ "." ".a"
--   > [".","a"]
--   
-- --
--   >>> splitSuffixOn'_ "." "a."
--   > ["a."]
--   
-- --
--   >>> splitSuffixOn'_ "." "a.b"
--   > ["a.","b"]
--   
-- --
--   >>> splitSuffixOn'_ "." "a.b."
--   > ["a.","b."]
--   
-- --
--   >>> splitSuffixOn'_ "." "a..b.."
--   > ["a.",".","b.","."]
--   
-- -- Internal splitWithSuffixSeq :: (IsStream t, MonadIO m, Storable a, Enum a, Eq a) => Array a -> 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. -- -- Internal 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. -- -- Internal 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) -- |
--   groups = groupsBy (==)
--   groups = groupsByRolling (==)
--   
-- -- Groups contiguous spans of equal elements together in individual -- groups. -- --
--   >>> S.toList $ S.groups FL.toList $ S.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 a `cmp` b is True -- then 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 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. -- --
--   >>> S.toList $ S.groupsBy (>) FL.toList $ S.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. -- --
--   >>> S.toList $ S.groupsByRolling (\a b -> a + 1 == b) FL.toList $ S.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 -- | Like rollingMap but with an effectful map function. -- -- Internal 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. -- -- Internal rollingMap :: (IsStream t, Monad m) => (a -> a -> b) -> t m a -> t m b -- | classifySessionsBy tick timeout idle pred f stream groups -- timestamped events in an input event stream into sessions based on a -- session key. Each element in the stream is an event consisting of a -- triple (session key, sesssion data, timestamp). session -- key is a key that uniquely identifies the session. All the events -- belonging to a session are folded using the fold f until the -- fold returns a Left result or a timeout has occurred. The -- session key and the result of the fold are emitted in the output -- stream when the session is purged. -- -- When idle is False, timeout is the maximum -- lifetime of a session in seconds, measured from the timestamp -- of the first event in that session. When idle is True -- then the timeout is an idle timeout, it is reset after every event -- received in the session. -- -- timestamp in an event characterizes the time when the input -- event was generated, this is an absolute time measured from some -- Epoch. 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 -- tick duration specified by tick. This timer is used to detect -- session timeouts in the absence of new events. -- -- The predicate pred is invoked with the current session count, -- if it returns True a session is ejected from the session cache -- before inserting a new session. This could be useful to alert or eject -- sessions when the number of sessions becomes too high. -- -- Internal classifySessionsBy :: (IsStream t, MonadAsync m, Ord k) => Double -> Double -> Bool -> (Int -> m Bool) -> Fold m a (Either b b) -> t m (k, a, AbsTime) -> t m (k, b) -- | Split the stream into fixed size time windows of specified interval in -- seconds. Within each such window, fold the elements in sessions -- identified by the session keys. The fold result is emitted in the -- output stream if the fold returns a Left result or if the time -- window ends. -- -- Session timestamp in the input stream is an absolute time -- from some epoch, characterizing the time when the input element was -- generated. To detect session window end, a monotonic event time clock -- is maintained synced with the timestamps with a clock resolution of 1 -- second. -- -- If the ejection predicate returns True, the session with the -- longest lifetime is ejected before inserting a new session. -- --
--   classifySessionsOf interval pred = classifySessionsBy 1 interval False pred
--   
-- -- Internal classifySessionsOf :: (IsStream t, MonadAsync m, Ord k) => Double -> (Int -> m Bool) -> Fold m a (Either b b) -> t m (k, a, AbsTime) -> t m (k, b) -- | Like classifySessionsOf but the session is kept alive if an -- event is received within the session window. The session times out and -- gets closed only if no event is received within the specified session -- window size. -- -- If the ejection predicate returns True, the session that was -- idle for the longest time is ejected before inserting a new session. -- --
--   classifyKeepAliveSessions timeout pred = classifySessionsBy 1 timeout True pred
--   
-- -- Internal classifyKeepAliveSessions :: (IsStream t, MonadAsync m, Ord k) => Double -> (Int -> m Bool) -> Fold m a (Either b b) -> t m (k, a, AbsTime) -> t m (k, b) -- | 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. -- -- Internal append :: (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. If any of the -- streams finishes early the other stream continues alone until it too -- finishes. -- --
--   >>> :set -XOverloadedStrings
--   
--   >>> interleave "ab" ",,,," :: SerialT Identity Char
--   fromList "a,b,,,"
--   
--   >>> interleave "abcd" ",," :: SerialT Identity Char
--   fromList "a,b,cd"
--   
-- -- interleave is dual to interleaveMin, it can be called -- interleaveMax. -- -- Do not use at scale in concatMapWith. -- -- Internal 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
--   
--   >>> interleaveMin "ab" ",,,," :: SerialT Identity Char
--   fromList "a,b,"
--   
--   >>> interleaveMin "abcd" ",," :: SerialT Identity Char
--   fromList "a,b,c"
--   
-- -- interleaveMin is dual to interleave. -- -- Do not use at scale in concatMapWith. -- -- Internal 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
--   
--   >>> interleaveSuffix "abc" ",,,," :: SerialT Identity Char
--   fromList "a,b,c,"
--   
--   >>> interleaveSuffix "abc" "," :: SerialT Identity Char
--   fromList "a,bc"
--   
-- -- interleaveSuffix is a dual of interleaveInfix. -- -- Do not use at scale in concatMapWith. -- -- Internal 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
--   
--   >>> interleaveInfix "abc" ",,,," :: SerialT Identity Char
--   fromList "a,b,c"
--   
--   >>> interleaveInfix "abc" "," :: SerialT Identity Char
--   fromList "a,bc"
--   
-- -- interleaveInfix is a dual of interleaveSuffix. -- -- Do not use at scale in concatMapWith. -- -- Internal interleaveInfix :: (IsStream t, Monad m) => t m b -> t m b -> t m b -- | Like wSerial but stops interleaving as soon as the first stream -- stops. wSerialFst :: IsStream t => t m a -> t m a -> t m a -- | Like wSerial but stops interleaving as soon as any of the two -- streams stops. wSerialMin :: IsStream t => t m a -> t m a -> t m a -- | 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. -- -- Internal roundrobin :: (IsStream t, Monad m) => t m b -> t m b -> t m b -- | Like parallel but stops the output as soon as the first stream -- stops. -- -- Internal 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. -- -- Internal parallelMin :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | 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. -- --
--   > S.toList $ S.mergeBy compare (S.fromList [1,3,5]) (S.fromList [2,4,6,8])
--   [1,2,3,4,5,6,8]
--   
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
--   > S.toList $ S.mergeByM randomly (S.fromList [1,1,1,1]) (S.fromList [2,2,2,2])
--   [2,1,2,2,2,1,1,1]
--   
-- -- Merge two streams in a proportion of 2:1: -- --
--   proportionately m n = do
--    ref <- newIORef $ cycle $ concat [replicate m LT, replicate n GT]
--    return $ \_ _ -> do
--        r <- readIORef ref
--        writeIORef ref $ tail r
--        return $ head r
--   
--   main = do
--    f <- proportionately 2 1
--    xs <- S.toList $ S.mergeByM f (S.fromList [1,1,1,1,1,1]) (S.fromList [2,2,2])
--    print xs
--   
-- --
--   [1,1,2,1,1,2,1,1,2]
--   
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 -- | Zip two streams serially using a pure zipping function. -- --
--   > 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 generated concurrently. zipAsyncWith :: (IsStream t, MonadAsync m) => (a -> b -> c) -> t m a -> t m b -> t m c -- | Like zipWithM but zips concurrently i.e. both the streams being -- zipped are generated concurrently. zipAsyncWithM :: (IsStream t, MonadAsync m) => (a -> b -> m c) -> t m a -> t m b -> t m c -- | A variant of fold that allows you to fold a Foldable -- container of streams using the specified stream sum operation. -- --
--   foldWith async $ map return [1..3]
--   
-- -- Equivalent to: -- --
--   foldWith f = S.foldMapWith f id
--   
-- -- Since: 0.1.0 (Streamly) foldWith :: (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. -- --
--   foldMapWith async return [1..3]
--   
-- -- Equivalent to: -- --
--   foldMapWith f g xs = S.concatMapWith f g (S.fromFoldable xs)
--   
-- -- Since: 0.1.0 (Streamly) foldMapWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b -- | Like foldMapWith but with the last two arguments reversed i.e. -- the monadic streaming function is the last argument. -- -- Equivalent to: -- --
--   forEachWith = flip S.foldMapWith
--   
-- -- Since: 0.1.0 (Streamly) forEachWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b -- | Flatten a stream of streams to a single stream. -- --
--   concat = concatMap id
--   
-- -- Internal concat :: (IsStream t, Monad m) => t m (t m a) -> t m a -- | Given a stream value in the underlying monad, lift and join the -- underlying monad with the stream monad. -- -- Compare with concat and sequence. -- -- Internal concatM :: (IsStream t, Monad m) => m (t m a) -> t m a -- | Map a stream producing function on each element of the stream and then -- flatten the results into a single stream. -- --
--   concatMap = concatMapWith serial
--   concatMap f = concatMapM (return . f)
--   
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 -- | concatMapWith merge map stream is a two dimensional looping -- combinator. The first argument specifies a merge or concat function -- that is used to merge the streams generated by applying the second -- argument i.e. the map function to each element of the input -- stream. The concat function could be serial, -- parallel, async, ahead or any other zip or -- merge function and the second argument could be any stream generation -- function using a seed. -- -- Compare foldMapWith concatMapWith :: IsStream t => (forall c. t m c -> t m c -> t m c) -> (a -> t m b) -> t m a -> t m b -- | 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. concatUnfold :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b -- | Like concatUnfold but interleaves the streams in the same way -- as interleave behaves instead of appending them. -- -- Internal concatUnfoldInterleave :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b -- | Like concatUnfold but executes the streams in the same way as -- roundrobin. -- -- Internal concatUnfoldRoundrobin :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b -- | Like iterateM but using a stream generator function. -- -- Internal concatMapIterateWith :: IsStream t => (forall c. t m c -> t m c -> t m c) -> (a -> t m a) -> t m a -> t m a -- | Traverse a forest with recursive tree structures whose non-leaf nodes -- are of type a and leaf nodes are of type b, -- flattening all the trees into streams and combining the streams into a -- single stream consisting of both leaf and non-leaf nodes. -- -- concatMapTreeWith is a generalization of concatMap, -- using a recursive feedback loop to append the non-leaf nodes back to -- the input stream enabling recursive traversal. concatMap -- flattens a single level nesting whereas concatMapTreeWith -- flattens a recursively nested structure. -- -- Traversing a directory tree recursively is a canonical use case of -- concatMapTreeWith. -- --
--   concatMapTreeWith combine f xs = concatMapIterateWith combine g xs
--        where
--        g (Left tree)  = f tree
--        g (Right leaf) = nil
--   
-- -- Internal concatMapTreeWith :: IsStream t => (forall c. t m c -> t m c -> t m c) -> (a -> t m (Either a b)) -> t m (Either a b) -> t m (Either a b) -- | Flatten a stream with a feedback loop back into the input. -- -- For example, exceptions generated by the output stream can be fed back -- to the input to take any corrective action. The corrective action may -- be to retry the action or do nothing or log the errors. For the retry -- case we need a feedback loop. -- -- Internal concatMapLoopWith :: (IsStream t, MonadAsync m) => (forall x. t m x -> t m x -> t m x) -> (a -> t m (Either b c)) -> (b -> t m a) -> t m a -> t m c -- | Concat a stream of trees, generating only leaves. -- -- Compare with concatMapTreeWith. While the latter returns all -- nodes in the tree, this one returns only the leaves. -- -- Traversing a directory tree recursively and yielding on the files is a -- canonical use case of concatMapTreeYieldLeavesWith. -- --
--   concatMapTreeYieldLeavesWith combine f = concatMapLoopWith combine f yield
--   
-- -- Internal concatMapTreeYieldLeavesWith :: (IsStream t, MonadAsync m) => (forall x. t m x -> t m x -> t m x) -> (a -> t m (Either a b)) -> t m a -> t m b -- | Iterate a lazy function f of the shape `m a -> t m a` -- until it gets fully defined i.e. becomes independent of its argument -- action, then return the resulting value of the function (`t m a`). -- -- It can be used to construct a stream that uses a cyclic definition. -- For example: -- --
--   import Streamly.Internal.Prelude as S
--   import System.IO.Unsafe (unsafeInterleaveIO)
--   
--   main = do
--       S.mapM_ print $ S.mfix $ x -> do
--         a <- S.fromList [1,2]
--         b <- S.fromListM [return 3, unsafeInterleaveIO (fmap fst x)]
--         return (a, b)
--   
-- -- Note that the function f must be lazy in its argument, that's -- why we use unsafeInterleaveIO because IO monad is strict. -- -- Internal mfix :: (IsStream t, Monad m) => (m a -> t m a) -> t m a -- | interleaveInfix followed by unfold and concat. -- -- Internal 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. -- -- Internal gintercalateSuffix :: (IsStream t, Monad m) => Unfold m a c -> t m a -> Unfold m b c -> t m b -> t m c -- | intersperse followed by unfold and concat. -- --
--   unwords = intercalate " " UF.fromList
--   
-- --
--   >>> intercalate " " UF.fromList ["abc", "def", "ghi"]
--   > "abc def ghi"
--   
-- -- Internal intercalate :: (IsStream t, Monad m) => b -> Unfold m b c -> t m b -> t m c -- | intersperseSuffix followed by unfold and concat. -- --
--   unlines = intercalateSuffix "\n" UF.fromList
--   
-- --
--   >>> intercalate "\n" UF.fromList ["abc", "def", "ghi"]
--   > "abc\ndef\nghi\n"
--   
-- -- Internal intercalateSuffix :: (IsStream t, Monad m) => b -> Unfold m b c -> t m b -> t m c -- | 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 ' '
--   
-- -- Internal 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'
--   
-- -- Internal interposeSuffix :: (IsStream t, Monad m) => c -> Unfold m b c -> t m b -> t m c -- | Run a side effect before the stream yields its first element. before :: (IsStream t, Monad m) => m b -> t m a -> t m a -- | Run a side effect whenever the stream stops normally. -- -- Prefer afterIO over this as the after action in this -- combinator is not executed if the unfold is partially evaluated lazily -- and then garbage collected. after :: (IsStream t, Monad m) => m b -> t m a -> t m a -- | Run a side effect whenever the stream stops normally or is garbage -- collected after a partial lazy evaluation. -- -- Internal afterIO :: (IsStream t, MonadIO m, MonadBaseControl IO m) => m b -> t m a -> t m a -- | Run the first action before the stream starts and remember its output, -- generate a stream using the output, run the second action using the -- remembered value as an argument whenever the stream ends normally or -- due to an exception. -- -- Prefer bracketIO over this as the after action in this -- combinator is not executed if the unfold is partially evaluated lazily -- and then garbage collected. bracket :: (IsStream t, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a -- | Run the first action before the stream starts and remember its output, -- generate a stream using the output, run the second action using the -- remembered value as an argument whenever the stream ends normally, due -- to an exception or if it is garbage collected after a partial lazy -- evaluation. -- -- Internal bracketIO :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a -- | Run a side effect whenever the stream aborts due to an exception. onException :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a -- | Run a side effect whenever the stream stops normally or aborts due to -- an exception. -- -- Prefer finallyIO over this as the after action in this -- combinator is not executed if the unfold is partially evaluated lazily -- and then garbage collected. finally :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a -- | Run a side effect whenever the stream stops normally, aborts due to an -- exception or if it is garbage collected after a partial lazy -- evaluation. -- -- Internal finallyIO :: (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. handle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a) -> t m a -> t m a -- | 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 of a stream using a monad transformer. -- -- Internal 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. -- -- Internal usingReaderT :: (Monad m, IsStream t) => 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. -- -- Internal runReaderT :: (IsStream t, Monad 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. -- -- Internal evalStateT :: Monad 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. -- -- Internal usingStateT :: Monad 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. -- -- Internal runStateT :: Monad m => s -> SerialT (StateT s m) a -> SerialT m (s, a) -- | Print debug information about an SVar when the stream ends -- -- Internal inspectMode :: IsStream t => t m a -> t m a -- | Same as yieldM -- | Deprecated: Please use yieldM instead. once :: (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.7.0 (Monad m constraint) -- -- Since 0.2.0 -- | 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 . -- asyncly. -- | 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 () -- | Combinators to efficiently manipulate streams of arrays. module Streamly.Internal.Memory.ArrayStream -- | arraysOf n stream groups the elements in the input stream -- into arrays of n elements each. -- -- Same as the following but more efficient: -- --
--   arraysOf n = S.chunksOf n (A.writeN n)
--   
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 = S.concatMap A.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 :: (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. -- -- Internal 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 -- | 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) -- | 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) -- | 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) 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. -- -- Internal toStream :: (IsStream t, MonadIO m) => String -> t m String -- | Read directories as Left and files as Right. Filter out "." and ".." -- entries. -- -- Internal 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 module Streamly.Internal.Data.Stream.Async -- | The Semigroup operation (<>) for AsyncT -- merges two streams concurrently with priority given to the first -- stream. In s1 <> s2 <> s3 ... the streams s1, s2 -- and s3 are scheduled for execution in that order. Multiple scheduled -- streams may be executed concurrently and the elements generated by -- them are served to the consumer as and when they become available. -- This behavior is similar to the scheduling and execution behavior of -- actions in a single async stream. -- -- Since only a finite number of streams are executed concurrently, this -- operation can be used to fold an infinite lazy container of streams. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   import Control.Concurrent
--   
--   main = (S.toList . asyncly $ (S.fromList [1,2]) <> (S.fromList [3,4])) >>= print
--   
-- --
--   [1,2,3,4]
--   
-- -- Any exceptions generated by a constituent stream are propagated to the -- output stream. The output and exceptions from a single stream are -- guaranteed to arrive in the same order in the resulting stream as they -- were generated in the input stream. However, the relative ordering of -- elements from different streams in the resulting stream can vary -- depending on scheduling and generation delays. -- -- Similarly, the monad instance of AsyncT may run each -- iteration concurrently based on demand. More concurrent iterations are -- started only if the previous iterations are not able to produce enough -- output for the consumer. -- --
--   main = drain . asyncly $ do
--       n <- return 3 <> return 2 <> return 1
--       S.yieldM $ do
--            threadDelay (n * 1000000)
--            myThreadId >>= \tid -> putStrLn (show tid ++ ": Delay " ++ show n)
--   
-- --
--   ThreadId 40: Delay 1
--   ThreadId 39: Delay 2
--   ThreadId 38: Delay 3
--   
data AsyncT m a -- | A demand driven left biased parallely composing IO stream of elements -- of type a. See AsyncT documentation for more details. type Async = AsyncT IO -- | Fix the type of a polymorphic stream as AsyncT. asyncly :: IsStream t => AsyncT m a -> t m a -- | Polymorphic version of the Semigroup operation <> -- of AsyncT. Merges two streams possibly concurrently, preferring -- the elements from the left one when available. async :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | Same as async. -- | Deprecated: Please use async instead. (<|) :: (IsStream t, MonadAsync m) => t m 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. -- -- Internal mkAsync :: (IsStream t, MonadAsync m) => t m a -> t m a -- | Generate a stream asynchronously to keep it buffered, lazily consume -- from the buffer. -- -- Internal mkAsyncK :: (IsStream t, MonadAsync m) => t m a -> t m a -- | WAsyncT is similar to WSerialT but with concurrent -- execution. The Semigroup operation (<>) for -- WAsyncT merges two streams concurrently interleaving the -- actions from both the streams. In s1 <> s2 <> s3 -- ..., the individual actions from streams s1, s2 -- and s3 are scheduled for execution in a round-robin fashion. -- Multiple scheduled actions may be executed concurrently, the results -- from concurrent executions are consumed in the order in which they -- become available. -- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- AsyncT. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   import Control.Concurrent
--   
--   main = (S.toList . wAsyncly . maxThreads 1 $ (S.fromList [1,2]) <> (S.fromList [3,4])) >>= print
--   
-- --
--   [1,3,2,4]
--   
-- -- For this example, we are using maxThreads 1 so that -- concurrent thread scheduling does not affect the results and make them -- unpredictable. Let's now take a more general example: -- --
--   main = (S.toList . wAsyncly . maxThreads 1 $ (S.fromList [1,2,3]) <> (S.fromList [4,5,6]) <> (S.fromList [7,8,9])) >>= print
--   
-- --
--   [1,4,2,7,5,3,8,6,9]
--   
-- -- This is how the execution of the above stream proceeds: -- --
    --
  1. The scheduler queue is initialized with [S.fromList [1,2,3], -- (S.fromList [4,5,6]) <> (S.fromList [7,8,9])] assuming the -- head of the queue is represented by the rightmost item.
  2. --
  3. S.fromList [1,2,3] is executed, yielding the element -- 1 and putting [2,3] at the back of the scheduler -- queue. The scheduler queue now looks like [(S.fromList [4,5,6]) -- <> (S.fromList [7,8,9]), S.fromList [2,3]].
  4. --
  5. Now (S.fromList [4,5,6]) <> (S.fromList [7,8,9]) is -- picked up for execution, S.fromList [7,8,9] is added at the -- back of the queue and S.fromList [4,5,6] is executed, -- yielding the element 4 and adding S.fromList [5,6] -- at the back of the queue. The queue now looks like [S.fromList -- [2,3], S.fromList [7,8,9], S.fromList [5,6]].
  6. --
  7. Note that the scheduler queue expands by one more stream component -- in every pass because one more <> is broken down into -- two components. At this point there are no more <> -- operations to be broken down further and the queue has reached its -- maximum size. Now these streams are scheduled in round-robin fashion -- yielding [2,7,5,3,8,8,9].
  8. --
-- -- As we see above, in a right associated expression composed with -- <>, only one <> operation is broken down -- into two components in one execution, therefore, if we have n -- streams composed using <> it will take n -- scheduler passes to expand the whole expression. By the time -- n-th component is added to the scheduler queue, the first -- component would have received n scheduler passes. -- -- Since all streams get interleaved, this operation is not suitable for -- folding an infinite lazy container of infinite size streams. However, -- if the streams are small, the streams on the left may get finished -- before more streams are added to the scheduler queue from the right -- side of the expression, so it may be possible to fold an infinite lazy -- container of streams. For example, if the streams are of size -- n then at most n streams would be in the scheduler -- queue at a time. -- -- Note that WSerialT and WAsyncT differ in their -- scheduling behavior, therefore the output of WAsyncT even with -- a single thread of execution is not the same as that of -- WSerialT See notes in WSerialT for details about its -- scheduling behavior. -- -- Any exceptions generated by a constituent stream are propagated to the -- output stream. The output and exceptions from a single stream are -- guaranteed to arrive in the same order in the resulting stream as they -- were generated in the input stream. However, the relative ordering of -- elements from different streams in the resulting stream can vary -- depending on scheduling and generation delays. -- -- Similarly, the Monad instance of WAsyncT runs all -- iterations fairly concurrently using a round robin scheduling. -- --
--   main = drain . wAsyncly $ do
--       n <- return 3 <> return 2 <> return 1
--       S.yieldM $ do
--            threadDelay (n * 1000000)
--            myThreadId >>= \tid -> putStrLn (show tid ++ ": Delay " ++ show n)
--   
-- --
--   ThreadId 40: Delay 1
--   ThreadId 39: Delay 2
--   ThreadId 38: Delay 3
--   
data WAsyncT m a -- | A round robin parallely composing IO stream of elements of type -- a. See WAsyncT documentation for more details. type WAsync = WAsyncT IO -- | Fix the type of a polymorphic stream as WAsyncT. wAsyncly :: IsStream t => WAsyncT m a -> t m a -- | Polymorphic version of the Semigroup operation <> -- of WAsyncT. Merges two streams concurrently choosing elements -- from both fairly. wAsync :: (IsStream t, MonadAsync m) => t m a -> t m a -> t 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.Data.Stream.StreamK.Type.IsStream Streamly.Internal.Data.Stream.Async.WAsyncT instance Streamly.Internal.Data.SVar.MonadAsync m => GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Async.WAsyncT m a) instance Streamly.Internal.Data.SVar.MonadAsync m => GHC.Base.Monoid (Streamly.Internal.Data.Stream.Async.WAsyncT m a) instance (GHC.Base.Monad m, Streamly.Internal.Data.SVar.MonadAsync m) => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance Streamly.Internal.Data.SVar.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.Data.SVar.MonadAsync m) => Control.Monad.Base.MonadBase b (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance (Control.Monad.IO.Class.MonadIO m, Streamly.Internal.Data.SVar.MonadAsync m) => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance (Control.Monad.Catch.MonadThrow m, Streamly.Internal.Data.SVar.MonadAsync m) => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance (Control.Monad.Reader.Class.MonadReader r m, Streamly.Internal.Data.SVar.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.Data.SVar.MonadAsync m) => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Stream.Async.WAsyncT m) instance Streamly.Internal.Data.Stream.StreamK.Type.IsStream Streamly.Internal.Data.Stream.Async.AsyncT instance Streamly.Internal.Data.SVar.MonadAsync m => GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Async.AsyncT m a) instance Streamly.Internal.Data.SVar.MonadAsync m => GHC.Base.Monoid (Streamly.Internal.Data.Stream.Async.AsyncT m a) instance (GHC.Base.Monad m, Streamly.Internal.Data.SVar.MonadAsync m) => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Async.AsyncT m) instance Streamly.Internal.Data.SVar.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.Data.SVar.MonadAsync m) => Control.Monad.Base.MonadBase b (Streamly.Internal.Data.Stream.Async.AsyncT m) instance (Control.Monad.IO.Class.MonadIO m, Streamly.Internal.Data.SVar.MonadAsync m) => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Stream.Async.AsyncT m) instance (Control.Monad.Catch.MonadThrow m, Streamly.Internal.Data.SVar.MonadAsync m) => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.Async.AsyncT m) instance (Control.Monad.Reader.Class.MonadReader r m, Streamly.Internal.Data.SVar.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.Data.SVar.MonadAsync m) => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Stream.Async.AsyncT m) module Streamly.Internal.Data.Stream.Ahead -- | The Semigroup operation for AheadT appends two streams. -- The combined stream behaves like a single stream with the actions from -- the second stream appended to the first stream. The combined stream is -- evaluated in the speculative style. This operation can be used to fold -- an infinite lazy container of streams. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   import Control.Concurrent
--   
--   main = do
--    xs <- S.toList . aheadly $ (p 1 |: p 2 |: nil) <> (p 3 |: p 4 |: nil)
--    print xs
--    where p n = threadDelay 1000000 >> return n
--   
-- --
--   [1,2,3,4]
--   
-- -- Any exceptions generated by a constituent stream are propagated to the -- output stream. -- -- The monad instance of AheadT may run each monadic continuation -- (bind) concurrently in a speculative manner, performing side effects -- in a partially ordered manner but producing the outputs in an ordered -- manner like SerialT. -- --
--   main = S.drain . aheadly $ do
--       n <- return 3 <> return 2 <> return 1
--       S.yieldM $ do
--            threadDelay (n * 1000000)
--            myThreadId >>= \tid -> putStrLn (show tid ++ ": Delay " ++ show n)
--   
-- --
--   ThreadId 40: Delay 1
--   ThreadId 39: Delay 2
--   ThreadId 38: Delay 3
--   
data AheadT m a -- | A serial IO stream of elements of type a with concurrent -- lookahead. See AheadT documentation for more details. type Ahead = AheadT IO -- | Fix the type of a polymorphic stream as AheadT. aheadly :: IsStream t => AheadT m a -> t m a -- | Polymorphic version of the Semigroup operation <> -- of AheadT. Merges two streams sequentially but with concurrent -- lookahead. ahead :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a instance Control.Monad.Trans.Class.MonadTrans Streamly.Internal.Data.Stream.Ahead.AheadT instance Streamly.Internal.Data.Stream.StreamK.Type.IsStream Streamly.Internal.Data.Stream.Ahead.AheadT instance Streamly.Internal.Data.SVar.MonadAsync m => GHC.Base.Semigroup (Streamly.Internal.Data.Stream.Ahead.AheadT m a) instance Streamly.Internal.Data.SVar.MonadAsync m => GHC.Base.Monoid (Streamly.Internal.Data.Stream.Ahead.AheadT m a) instance (GHC.Base.Monad m, Streamly.Internal.Data.SVar.MonadAsync m) => GHC.Base.Applicative (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance Streamly.Internal.Data.SVar.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.Data.SVar.MonadAsync m) => Control.Monad.Base.MonadBase b (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance (Control.Monad.IO.Class.MonadIO m, Streamly.Internal.Data.SVar.MonadAsync m) => Control.Monad.IO.Class.MonadIO (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance (Control.Monad.Catch.MonadThrow m, Streamly.Internal.Data.SVar.MonadAsync m) => Control.Monad.Catch.MonadThrow (Streamly.Internal.Data.Stream.Ahead.AheadT m) instance (Control.Monad.Reader.Class.MonadReader r m, Streamly.Internal.Data.SVar.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.Data.SVar.MonadAsync m) => Control.Monad.State.Class.MonadState s (Streamly.Internal.Data.Stream.Ahead.AheadT m) 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.Memory.Array. 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, IsStream t) => SmallArray a -> t m a toStreamRev :: (Monad m, IsStream t) => SmallArray a -> t 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.Memory.Array 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.Types.SmallArray a) module Streamly.Internal.Data.Prim.Array -- | Arrays of unboxed elements. This accepts types like Double, -- Char, Int, and Word, as well as their -- fixed-length variants (Word8, Word16, etc.). Since -- the elements are unboxed, a PrimArray is strict in its -- elements. This differs from the behavior of Array, which is -- lazy in its elements. data PrimArray a PrimArray :: ByteArray# -> PrimArray 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 -- | Size of values of type a. The argument is not used. sizeOf# :: Prim a => a -> Int# -- | Alignment of values of type a. The argument is not used. alignment# :: Prim a => a -> Int# -- | Read a value from the array. The offset is in elements of type -- a rather than in bytes. indexByteArray# :: Prim a => ByteArray# -> Int# -> a -- | Read a value from the mutable array. The offset is in elements of type -- a rather than in bytes. readByteArray# :: Prim a => MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) -- | Write a value to the mutable array. The offset is in elements of type -- a rather than in bytes. writeByteArray# :: Prim a => MutableByteArray# s -> Int# -> a -> State# s -> State# s -- | Fill a slice of the mutable array with a value. The offset and length -- of the chunk are in elements of type a rather than in bytes. setByteArray# :: Prim a => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s -- | Read a value from a memory position given by an address and an offset. -- The memory block the address refers to must be immutable. The offset -- is in elements of type a rather than in bytes. indexOffAddr# :: Prim a => Addr# -> Int# -> a -- | Read a value from a memory position given by an address and an offset. -- The offset is in elements of type a rather than in bytes. readOffAddr# :: Prim a => Addr# -> Int# -> State# s -> (# State# s, a #) -- | Write a value to a memory position given by an address and an offset. -- The offset is in elements of type a rather than in bytes. writeOffAddr# :: Prim a => Addr# -> Int# -> a -> State# s -> State# s -- | Fill a memory block given by an address, an offset and a length. The -- offset and length are in elements of type a rather than in -- bytes. setOffAddr# :: Prim a => Addr# -> Int# -> Int# -> a -> State# s -> State# s foldl' :: Prim a => (b -> a -> b) -> b -> PrimArray a -> b foldr :: Prim a => (a -> b -> b) -> b -> PrimArray a -> b length :: Prim a => PrimArray a -> Int writeN :: (MonadIO m, Prim a) => Int -> Fold m a (PrimArray a) write :: (MonadIO m, Prim a) => Fold m a (PrimArray a) toStreamD :: (Prim a, Monad m) => PrimArray a -> Stream m a toStreamDRev :: (Prim a, Monad m) => PrimArray a -> Stream m a toStream :: (Prim a, Monad m, IsStream t) => PrimArray a -> t m a toStreamRev :: (Prim a, Monad m, IsStream t) => PrimArray a -> t m a read :: (Prim a, Monad m) => Unfold m (PrimArray a) a readSlice :: (Prim a, Monad m) => Int -> Int -> Unfold m (PrimArray a) a fromListN :: Prim a => Int -> [a] -> PrimArray a fromList :: Prim a => [a] -> PrimArray a fromStreamDN :: (MonadIO m, Prim a) => Int -> Stream m a -> m (PrimArray a) fromStreamD :: (MonadIO m, Prim a) => Stream m a -> m (PrimArray a) fromStreamN :: (MonadIO m, Prim a) => Int -> SerialT m a -> m (PrimArray a) fromStream :: (MonadIO m, Prim a) => SerialT m a -> m (PrimArray a) streamFold :: (Prim a, Monad m) => (SerialT m a -> m b) -> PrimArray a -> m b fold :: (Prim a, Monad m) => Fold m a b -> PrimArray a -> m b instance Data.Primitive.Types.Prim a => Control.DeepSeq.NFData (Streamly.Internal.Data.Prim.Array.Types.PrimArray a) module Streamly.Internal.Data.Array -- | Boxed arrays. data Array a Array :: Array# a -> Array a [array#] :: Array a -> Array# a foldl' :: (b -> a -> b) -> b -> Array a -> b foldr :: (a -> b -> b) -> b -> Array a -> b length :: Array a -> Int writeN :: MonadIO m => Int -> Fold m a (Array a) write :: MonadIO m => Fold m a (Array a) toStreamD :: Monad m => Array a -> Stream m a toStreamDRev :: Monad m => Array a -> Stream m a toStream :: (Monad m, IsStream t) => Array a -> t m a toStreamRev :: (Monad m, IsStream t) => Array a -> t m a read :: Monad m => Unfold m (Array a) a fromListN :: Int -> [a] -> Array a fromList :: [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) streamFold :: Monad m => (SerialT m a -> m b) -> Array a -> m b fold :: Monad m => Fold m a b -> Array a -> m b -- | This module is designed to be imported qualified: -- --
--   import qualified Streamly.Prelude as S
--   
-- -- 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. -- -- Functions having a MonadAsync constraint work concurrently -- when used with appropriate stream type combinator. Please be careful -- to not use parallely with infinite streams. -- -- Deconstruction and folds accept a SerialT type instead of a -- polymorphic type to ensure that streams always have a concrete -- monomorphic type by default, reducing type errors. In case you want to -- use any other type of stream you can use one of the type combinators -- provided in the Streamly module to convert the stream type. module Streamly.Prelude -- | An empty stream. -- --
--   > toList nil
--   []
--   
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 parallely 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 $ serially  $ delay |: delay |: delay |: nil
--   drain $ parallely $ delay |: delay |: delay |: nil
--   
-- -- Concurrent (do not use parallely to construct infinite -- streams) (|:) :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 |: -- |
--   yield a = a `cons` nil
--   
-- -- Create a singleton stream from a pure value. -- -- The following holds in monadic streams, but not in Zip streams: -- --
--   yield = pure
--   yield = yieldM . pure
--   
-- -- In Zip applicative streams yield is not the same as pure -- because in that case pure is equivalent to repeat -- instead. yield and pure are equally efficient, in other -- cases yield may be slightly more efficient than the other -- equivalent definitions. yield :: IsStream t => a -> t m a -- |
--   yieldM m = m `consM` nil
--   
-- -- Create a singleton stream from a monadic action. -- --
--   > toList $ yieldM getLine
--   hello
--   ["hello"]
--   
yieldM :: (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 . yieldM
--   
-- -- Generate a stream by repeatedly executing a monadic action forever. -- --
--   drain $ serially $ S.take 10 $ S.repeatM $ (threadDelay 1000000 >> print 1)
--   drain $ asyncly  $ S.take 10 $ S.repeatM $ (threadDelay 1000000 >> print 1)
--   
-- -- Concurrent, infinite (do not use with parallely) repeatM :: (IsStream t, MonadAsync m) => m a -> t m a -- |
--   replicate = take n . repeat
--   
-- -- Generate a stream of length n by repeating a value n -- times. replicate :: (IsStream t, Monad m) => Int -> a -> t m a -- |
--   replicateM = take n . repeatM
--   
-- -- Generate a stream by performing a monadic action n times. -- Same as: -- --
--   drain $ serially $ S.replicateM 10 $ (threadDelay 1000000 >> print 1)
--   drain $ asyncly  $ S.replicateM 10 $ (threadDelay 1000000 >> print 1)
--   
-- -- Concurrent replicateM :: (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. -- --
--   > S.toList $ S.take 4 $ S.enumerateFrom (0 :: Int)
--   [0,1,2,3]
--   
-- -- For Fractional types, enumeration is numerically stable. -- However, no overflow or underflow checks are performed. -- --
--   > S.toList $ S.take 4 $ S.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. -- --
--   > S.toList $ S.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. -- --
--   > S.toList $ S.enumerateFromTo 1.1 4
--   [1.1,2.1,3.1,4.1]
--   > S.toList $ S.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. -- --
--   > S.toList $ S.take 4 $ S.enumerateFromThen 0 2
--   [0,2,4,6]
--   > S.toList $ S.take 4 $ S.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. -- --
--   > S.toList $ S.enumerateFromThenTo 0 2 6
--   [0,2,4,6]
--   > S.toList $ S.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 -- |
--   unfoldr step s =
--       case step s of
--           Nothing -> nil
--           Just (a, b) -> a `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 > 3
--           then Nothing
--           else Just (b, b + 1)
--   in toList $ unfoldr f 0
--   
-- --
--   [0,1,2,3]
--   
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 > 3
--           then return Nothing
--           else print b >> return (Just (b, b + 1))
--   in drain $ unfoldrM f 0
--   
-- --
--   0
--   1
--   2
--   3
--   
-- -- 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. -- --
--   (asyncly $ S.unfoldrM (\n -> liftIO (threadDelay 1000000) >> return (Just (n, n + 1))) 0)
--       & S.foldlM' (\_ a -> threadDelay 1000000 >> print a) ()
--   
-- -- Concurrent -- -- Since: 0.1.0 unfoldrM :: (IsStream t, MonadAsync m) => (b -> m (Maybe (a, b))) -> b -> t m a -- | Convert an Unfold into a stream by supplying it an input seed. -- --
--   >>> unfold (UF.replicateM 10) (putStrLn "hello")
--   
-- -- Since: 0.7.0 unfold :: (IsStream t, Monad m) => Unfold m a b -> a -> t m b -- |
--   iterate f x = x `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. -- --
--   > S.toList $ S.take 5 $ S.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 `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. -- -- 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. -- --
--   drain $ serially $ S.take 10 $ S.iterateM
--        (\x -> threadDelay 1000000 >> print x >> return (x + 1)) (return 0)
--   
--   drain $ asyncly  $ S.take 10 $ S.iterateM
--        (\x -> threadDelay 1000000 >> print x >> return (x + 1)) (return 0)
--   
-- -- Concurrent -- -- Since: 0.7.0 (signature change) -- -- Since: 0.1.2 iterateM :: (IsStream t, MonadAsync m) => (a -> m a) -> m a -> t m a -- |
--   fromIndices f = let g i = f i `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. -- --
--   > S.toList $ S.take 5 $ S.fromIndices id
--   [0,1,2,3,4]
--   
fromIndices :: (IsStream t, Monad m) => (Int -> a) -> t m a -- |
--   fromIndicesM f = let g i = f i `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 :: (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 = foldr consM 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 = foldr cons nil
--   
-- -- Construct a stream from a Foldable containing pure values: fromFoldable :: (IsStream t, Foldable f) => f a -> t m a -- |
--   fromFoldableM = foldr consM nil
--   
-- -- Construct a stream from a Foldable containing monadic actions. -- --
--   drain $ serially $ S.fromFoldableM $ replicateM 10 (threadDelay 1000000 >> print 1)
--   drain $ asyncly  $ S.fromFoldableM $ replicateM 10 (threadDelay 1000000 >> print 1)
--   
-- -- Concurrent (do not use with parallely on infinite -- containers) fromFoldableM :: (IsStream t, MonadAsync m, Foldable f) => f (m a) -> t 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. uncons :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (a, t m a)) -- |
--   tail = fmap (fmap snd) . 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: -- --
--   >>> S.foldrM (\x xs -> if odd x then return True else xs) (return False) $ S.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. foldlM' :: Monad m => (b -> a -> m b) -> b -> SerialT m a -> m b -- | Fold a stream using the supplied left fold. -- --
--   >>> S.fold FL.sum (S.enumerateFromTo 1 100)
--   5050
--   
fold :: Monad m => Fold m a b -> SerialT m a -> m b -- |
--   drain = mapM_ (\_ -> return ())
--   
-- -- 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 drain . asyncly. drain :: Monad m => SerialT m a -> m () -- | Extract the last element of the stream, if any. -- --
--   last xs = xs !! (length xs - 1)
--   
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 :: (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 :: (Monad m, Num a) => SerialT m a -> m a -- | Determine the maximum element in a stream using the supplied -- comparison function. maximumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) -- |
--   maximum = maximumBy compare
--   
-- -- 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 :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) -- |
--   minimum = minimumBy compare
--   
-- -- 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) -- |
--   toList = S.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] -- |
--   drainN n = drain . take n
--   
-- -- Run maximum up to n iterations of a stream. drainN :: Monad m => Int -> SerialT m a -> m () -- |
--   drainWhile p = drain . 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 :: Monad m => SerialT m a -> m (Maybe a) -- | Returns the first element that satisfies the given predicate. 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 :: 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 <$> find ((==) . fst)
--   
lookup :: (Monad m, Eq a) => a -> SerialT m (a, b) -> m (Maybe b) -- | Returns the first index that satisfies the given predicate. 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 = findIndex (== a)
--   
elemIndex :: (Monad m, Eq a) => a -> SerialT m a -> m (Maybe Int) -- | Determine whether the stream is empty. null :: Monad m => SerialT m a -> m Bool -- | Determine whether an element is present in the stream. elem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool -- | Determine whether an element is not present in the stream. notElem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool -- | Determine whether all elements of a stream satisfy a predicate. all :: Monad m => (a -> Bool) -> SerialT m a -> m Bool -- | Determine whether any of the elements of a stream satisfy a predicate. any :: Monad m => (a -> Bool) -> SerialT m a -> m Bool -- | Determines if all elements of a boolean stream are True. and :: Monad m => SerialT m Bool -> m Bool -- | Determines whether at least one element of a boolean stream is True. or :: Monad m => SerialT m Bool -> m Bool -- | 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. -- --
--   > S.isPrefixOf (S.fromList "hello") (S.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. -- --
--   > S.isSubsequenceOf (S.fromList "hlo") (S.fromList "hello" :: SerialT IO Char)
--   True
--   
isSubsequenceOf :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m Bool -- | Strip prefix if present and tell whether it was stripped or not. -- 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. -- -- 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 $ S.sequence $ S.fromList [putStr "a", putStr "b", putStrLn "c"]
--   abc
--   
--   drain $ S.replicateM 10 (return $ threadDelay 1000000 >> print 1)
--             & (serially . S.sequence)
--   
--   drain $ S.replicateM 10 (return $ threadDelay 1000000 >> print 1)
--             & (asyncly . S.sequence)
--   
-- -- Concurrent (do not use with parallely 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 $ S.mapM putStr $ S.fromList ["a", "b", "c"]
--   abc
--   
--   drain $ S.replicateM 10 (return 1)
--             & (serially . S.mapM (\x -> threadDelay 1000000 >> print x))
--   
--   drain $ S.replicateM 10 (return 1)
--             & (asyncly . S.mapM (\x -> threadDelay 1000000 >> print x))
--   
-- -- Concurrent (do not use with parallely on infinite -- streams) mapM :: (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m b -- |
--   mapM_ = drain . 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. -- --
--   > S.drain $ S.trace print (S.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-----
--   
-- --
--   > S.drain $ S.tap (FL.drainBy print) (S.enumerateFromTo 1 2)
--   1
--   2
--   
-- -- Compare with trace. tap :: (IsStream t, Monad m) => Fold m a b -> 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. -- --
--   > S.toList $ S.scanl' (+) 0 $ fromList [1,2,3,4]
--   [0,1,3,6,10]
--   
-- --
--   > S.toList $ S.scanl' (flip (:)) [] $ S.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': -- --
--   > S.foldl' (\(s, p) x -> (s + x, p * x)) (0,1) $ S.fromList [1,2,3,4]
--   (10,24)
--   
-- -- 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: -- --
--   >   S.foldl' (\(_, p) (s, x) -> (s, p * x)) (0,1)
--     $ S.scanl' (\(s, _) x -> (s + x, x)) (0,1)
--     $ S.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' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b -- | Like scanl' but with a monadic fold function. scanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> b -> t m a -> t m b -- | Like scanl' but does not stream the initial value of the -- accumulator. -- --
--   postscanl' f z xs = S.drop 1 $ S.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. postscanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> 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. -- --
--   > S.toList $ S.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. scan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | Postscan a stream using the given monadic fold. postscan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b -- | 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 -- | 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 = S.map fromJust . S.filter isJust . S.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 = S.map fromJust . S.filter isJust . S.mapM f
--   
-- -- Concurrent (do not use with parallely on infinite -- streams) mapMaybeM :: (IsStream t, MonadAsync m, Functor (t m)) => (a -> m (Maybe b)) -> t m a -> t m b -- | Deletes the first occurrence of the element in the stream that -- satisfies the given equality predicate. -- --
--   > S.toList $ S.deleteBy (==) 3 $ S.fromList [1,3,3,5]
--   [1,3,5]
--   
deleteBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> a -> 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 -- | 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 (yield x)
--   
-- --
--   > S.toList $ S.insertBy compare 2 $ S.fromList [1,3,5]
--   [1,2,3,5]
--   
insertBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> a -> t m a -> t m a -- | Generate a stream by inserting the result of a monadic action between -- consecutive elements of the given stream. Note that the monadic action -- is performed after the stream action before which its result is -- inserted. -- --
--   > S.toList $ S.intersperseM (return ',') $ S.fromList "hello"
--   "h,e,l,l,o"
--   
intersperseM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a -- | Generate a stream by inserting a given element between consecutive -- elements of the given stream. -- --
--   > S.toList $ S.intersperse ',' $ S.fromList "hello"
--   "h,e,l,l,o"
--   
intersperse :: (IsStream t, MonadAsync m) => a -> t m a -> t m a -- |
--   indexed = S.postscanl' (\(i, _) x -> (i + 1, x)) (-1,undefined)
--   indexed = S.zipWith (,) (S.enumerateFrom 0)
--   
-- -- Pair each element in a stream with its index, starting from index 0. -- --
--   > S.toList $ S.indexed $ S.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 = S.postscanl' (\(i, _) x -> (i - 1, x)) (n + 1,undefined)
--   indexedR n = S.zipWith (,) (S.enumerateFromThen n (n - 1))
--   
-- -- Pair each element in a stream with its index, starting from the given -- index n and counting down. -- --
--   > S.toList $ S.indexedR 10 $ S.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) -- | Returns the elements of the stream in reverse order. The stream must -- be finite. Note that this necessarily buffers the entire stream in -- memory. -- -- Since 0.7.0 (Monad m constraint) -- -- Since: 0.1.1 reverse :: (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 -- | Group the input stream into groups of n elements each and -- then fold each group using the provided fold function. -- --
--   > S.toList $ S.chunksOf 2 FL.sum (S.enumerateFromTo 1 10)
--    [3,7,11,15,19]
--   
-- -- This can be considered as an n-fold version of ltake where we -- apply ltake repeatedly on the leftover stream until the -- stream exhausts. 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. intervalsOf :: (IsStream t, MonadAsync m) => Double -> Fold m a b -> t m a -> t m b -- | Find all the indices where the element in the stream satisfies the -- given predicate. 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 :: (IsStream t, Eq a, Monad m) => a -> t m a -> t m Int -- | Split on an infixed separator element, dropping the separator. Splits -- the stream on separator elements determined by the supplied predicate, -- separator is considered as infixed between two segments, if one side -- of the separator is missing then it is parsed as an empty stream. The -- supplied Fold is applied on the split segments. With - -- representing non-separator elements and . as separator, -- splitOn splits as follows: -- --
--   "--.--" => "--" "--"
--   "--."   => "--" ""
--   ".--"   => ""   "--"
--   
-- -- splitOn (== x) is an inverse of intercalate (S.yield -- x) -- -- Let's use the following definition for illustration: -- --
--   splitOn' p xs = S.toList $ S.splitOn p (FL.toList) (S.fromList xs)
--   
-- --
--   >>> splitOn' (== '.') ""
--   [""]
--   
-- --
--   >>> splitOn' (== '.') "."
--   ["",""]
--   
-- --
--   >>> splitOn' (== '.') ".a"
--   > ["","a"]
--   
-- --
--   >>> splitOn' (== '.') "a."
--   > ["a",""]
--   
-- --
--   >>> splitOn' (== '.') "a.b"
--   > ["a","b"]
--   
-- --
--   >>> splitOn' (== '.') "a..b"
--   > ["a","","b"]
--   
splitOn :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b -- | Like splitOn but the separator is considered as suffixed to the -- segments in the stream. A missing suffix at the end is allowed. A -- separator at the beginning is parsed as empty segment. With - -- representing elements and . as separator, splitOnSuffix -- splits as follows: -- --
--   "--.--." => "--" "--"
--   "--.--"  => "--" "--"
--   ".--."   => "" "--"
--   
-- --
--   splitOnSuffix' p xs = S.toList $ S.splitSuffixBy p (FL.toList) (S.fromList xs)
--   
-- --
--   >>> splitOnSuffix' (== '.') ""
--   []
--   
-- --
--   >>> splitOnSuffix' (== '.') "."
--   [""]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a"
--   ["a"]
--   
-- --
--   >>> splitOnSuffix' (== '.') ".a"
--   > ["","a"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a."
--   > ["a"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a.b"
--   > ["a","b"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a.b."
--   > ["a","b"]
--   
-- --
--   >>> splitOnSuffix' (== '.') "a..b.."
--   > ["a","","b",""]
--   
-- --
--   lines = splitOnSuffix (== '\n')
--   
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 = S.toList $ S.splitWithSuffix p (FL.toList) (S.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 = S.toList $ S.wordsBy p (FL.toList) (S.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. -- --
--   >>> S.toList $ S.groups FL.toList $ S.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 a `cmp` b is True -- then 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 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. -- --
--   >>> S.toList $ S.groupsBy (>) FL.toList $ S.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. -- --
--   >>> S.toList $ S.groupsByRolling (\a b -> a + 1 == b) FL.toList $ S.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 -- | 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. -- --
--   > S.toList $ S.mergeBy compare (S.fromList [1,3,5]) (S.fromList [2,4,6,8])
--   [1,2,3,4,5,6,8]
--   
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
--   > S.toList $ S.mergeByM randomly (S.fromList [1,1,1,1]) (S.fromList [2,2,2,2])
--   [2,1,2,2,2,1,1,1]
--   
-- -- Merge two streams in a proportion of 2:1: -- --
--   proportionately m n = do
--    ref <- newIORef $ cycle $ concat [replicate m LT, replicate n GT]
--    return $ \_ _ -> do
--        r <- readIORef ref
--        writeIORef ref $ tail r
--        return $ head r
--   
--   main = do
--    f <- proportionately 2 1
--    xs <- S.toList $ S.mergeByM f (S.fromList [1,1,1,1,1,1]) (S.fromList [2,2,2])
--    print xs
--   
-- --
--   [1,1,2,1,1,2,1,1,2]
--   
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 -- | Zip two streams serially using a pure zipping function. -- --
--   > 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 generated concurrently. zipAsyncWith :: (IsStream t, MonadAsync m) => (a -> b -> c) -> t m a -> t m b -> t m c -- | Like zipWithM but zips concurrently i.e. both the streams being -- zipped are generated concurrently. zipAsyncWithM :: (IsStream t, MonadAsync m) => (a -> b -> m c) -> t m a -> t m b -> t m c -- | concatMapWith merge map stream is a two dimensional looping -- combinator. The first argument specifies a merge or concat function -- that is used to merge the streams generated by applying the second -- argument i.e. the map function to each element of the input -- stream. The concat function could be serial, -- parallel, async, ahead or any other zip or -- merge function and the second argument could be any stream generation -- function using a seed. -- -- Compare foldMapWith concatMapWith :: IsStream t => (forall c. t m c -> t m c -> t m c) -> (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 = concatMapWith serial
--   concatMap f = concatMapM (return . f)
--   
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 -- | 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. concatUnfold :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b -- | Run a side effect before the stream yields its first element. before :: (IsStream t, Monad m) => m b -> t m a -> t m a -- | Run a side effect whenever the stream stops normally. -- -- Prefer afterIO over this as the after action in this -- combinator is not executed if the unfold is partially evaluated lazily -- and then garbage collected. after :: (IsStream t, Monad m) => m b -> t m a -> t m a -- | Run the first action before the stream starts and remember its output, -- generate a stream using the output, run the second action using the -- remembered value as an argument whenever the stream ends normally or -- due to an exception. -- -- Prefer bracketIO over this as the after action in this -- combinator is not executed if the unfold is partially evaluated lazily -- and then garbage collected. bracket :: (IsStream t, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a -- | Run a side effect whenever the stream aborts due to an exception. onException :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a -- | Run a side effect whenever the stream stops normally or aborts due to -- an exception. -- -- Prefer finallyIO over this as the after action in this -- combinator is not executed if the unfold is partially evaluated lazily -- and then garbage collected. finally :: (IsStream t, 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. handle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a) -> t m a -> t m a -- | Same as yieldM -- | Deprecated: Please use yieldM instead. once :: (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.7.0 (Monad m constraint) -- -- Since 0.2.0 -- | 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 . -- asyncly. -- | 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 () -- | 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. 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. type MonadAsync m = (MonadIO m, MonadBaseControl IO m, MonadThrow m) -- | The Semigroup operation for SerialT behaves like a -- regular append operation. Therefore, when a <> b is -- evaluated, stream a is evaluated first until it exhausts and -- then stream b is evaluated. In other words, the elements of -- stream b are appended to the elements of stream a. -- This operation can be used to fold an infinite lazy container of -- streams. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   
--   main = (S.toList . serially $ (S.fromList [1,2]) <> (S.fromList [3,4])) >>= print
--   
-- --
--   [1,2,3,4]
--   
-- -- The Monad instance runs the monadic continuation for -- each element of the stream, serially. -- --
--   main = S.drain . serially $ do
--       x <- return 1 <> return 2
--       S.yieldM $ print x
--   
-- --
--   1
--   2
--   
-- -- SerialT nests streams serially in a depth first manner. -- --
--   main = S.drain . serially $ do
--       x <- return 1 <> return 2
--       y <- return 3 <> return 4
--       S.yieldM $ print (x, y)
--   
-- --
--   (1,3)
--   (1,4)
--   (2,3)
--   (2,4)
--   
-- -- We call the monadic code being run for each element of the stream a -- monadic continuation. In imperative paradigm we can think of this -- composition as nested for loops and the monadic continuation -- is the body of the loop. The loop iterates for all elements of the -- stream. -- -- Note that the behavior and semantics of SerialT, including -- Semigroup and Monad instances are exactly like Haskell -- lists except that SerialT can contain effectful actions while -- lists are pure. -- -- In the code above, the serially combinator can be omitted as -- the default stream type is SerialT. data SerialT m a -- | The Semigroup operation for WSerialT interleaves the -- elements from the two streams. Therefore, when a <> b -- is evaluated, stream a is evaluated first to produce the -- first element of the combined stream and then stream b is -- evaluated to produce the next element of the combined stream, and then -- we go back to evaluating stream a and so on. In other words, -- the elements of stream a are interleaved with the elements of -- stream b. -- -- Note that evaluation of a <> b <> c does not -- schedule a, b and c with equal priority. -- This expression is equivalent to a <> (b <> c), -- therefore, it fairly interleaves a with the result of b -- <> c. For example, S.fromList [1,2] <> S.fromList -- [3,4] <> S.fromList [5,6] :: WSerialT Identity Int would -- result in [1,3,2,5,4,6]. In other words, the leftmost stream gets the -- same scheduling priority as the rest of the streams taken together. -- The same is true for each subexpression on the right. -- -- Note that this operation cannot be used to fold a container of -- infinite streams as the state that it needs to maintain is -- proportional to the number of streams. -- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- SerialT. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   
--   main = (S.toList . wSerially $ (S.fromList [1,2]) <> (S.fromList [3,4])) >>= print
--   
-- --
--   [1,3,2,4]
--   
-- -- Similarly, the Monad instance interleaves the iterations of the -- inner and the outer loop, nesting loops in a breadth first manner. -- --
--   main = S.drain . wSerially $ do
--       x <- return 1 <> return 2
--       y <- return 3 <> return 4
--       S.yieldM $ print (x, y)
--   
-- --
--   (1,3)
--   (2,3)
--   (1,4)
--   (2,4)
--   
data WSerialT m a -- | The Semigroup operation for AheadT appends two streams. -- The combined stream behaves like a single stream with the actions from -- the second stream appended to the first stream. The combined stream is -- evaluated in the speculative style. This operation can be used to fold -- an infinite lazy container of streams. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   import Control.Concurrent
--   
--   main = do
--    xs <- S.toList . aheadly $ (p 1 |: p 2 |: nil) <> (p 3 |: p 4 |: nil)
--    print xs
--    where p n = threadDelay 1000000 >> return n
--   
-- --
--   [1,2,3,4]
--   
-- -- Any exceptions generated by a constituent stream are propagated to the -- output stream. -- -- The monad instance of AheadT may run each monadic continuation -- (bind) concurrently in a speculative manner, performing side effects -- in a partially ordered manner but producing the outputs in an ordered -- manner like SerialT. -- --
--   main = S.drain . aheadly $ do
--       n <- return 3 <> return 2 <> return 1
--       S.yieldM $ do
--            threadDelay (n * 1000000)
--            myThreadId >>= \tid -> putStrLn (show tid ++ ": Delay " ++ show n)
--   
-- --
--   ThreadId 40: Delay 1
--   ThreadId 39: Delay 2
--   ThreadId 38: Delay 3
--   
data AheadT m a -- | The Semigroup operation (<>) for AsyncT -- merges two streams concurrently with priority given to the first -- stream. In s1 <> s2 <> s3 ... the streams s1, s2 -- and s3 are scheduled for execution in that order. Multiple scheduled -- streams may be executed concurrently and the elements generated by -- them are served to the consumer as and when they become available. -- This behavior is similar to the scheduling and execution behavior of -- actions in a single async stream. -- -- Since only a finite number of streams are executed concurrently, this -- operation can be used to fold an infinite lazy container of streams. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   import Control.Concurrent
--   
--   main = (S.toList . asyncly $ (S.fromList [1,2]) <> (S.fromList [3,4])) >>= print
--   
-- --
--   [1,2,3,4]
--   
-- -- Any exceptions generated by a constituent stream are propagated to the -- output stream. The output and exceptions from a single stream are -- guaranteed to arrive in the same order in the resulting stream as they -- were generated in the input stream. However, the relative ordering of -- elements from different streams in the resulting stream can vary -- depending on scheduling and generation delays. -- -- Similarly, the monad instance of AsyncT may run each -- iteration concurrently based on demand. More concurrent iterations are -- started only if the previous iterations are not able to produce enough -- output for the consumer. -- --
--   main = drain . asyncly $ do
--       n <- return 3 <> return 2 <> return 1
--       S.yieldM $ do
--            threadDelay (n * 1000000)
--            myThreadId >>= \tid -> putStrLn (show tid ++ ": Delay " ++ show n)
--   
-- --
--   ThreadId 40: Delay 1
--   ThreadId 39: Delay 2
--   ThreadId 38: Delay 3
--   
data AsyncT m a -- | WAsyncT is similar to WSerialT but with concurrent -- execution. The Semigroup operation (<>) for -- WAsyncT merges two streams concurrently interleaving the -- actions from both the streams. In s1 <> s2 <> s3 -- ..., the individual actions from streams s1, s2 -- and s3 are scheduled for execution in a round-robin fashion. -- Multiple scheduled actions may be executed concurrently, the results -- from concurrent executions are consumed in the order in which they -- become available. -- -- The W in the name stands for wide or breadth wise -- scheduling in contrast to the depth wise scheduling behavior of -- AsyncT. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   import Control.Concurrent
--   
--   main = (S.toList . wAsyncly . maxThreads 1 $ (S.fromList [1,2]) <> (S.fromList [3,4])) >>= print
--   
-- --
--   [1,3,2,4]
--   
-- -- For this example, we are using maxThreads 1 so that -- concurrent thread scheduling does not affect the results and make them -- unpredictable. Let's now take a more general example: -- --
--   main = (S.toList . wAsyncly . maxThreads 1 $ (S.fromList [1,2,3]) <> (S.fromList [4,5,6]) <> (S.fromList [7,8,9])) >>= print
--   
-- --
--   [1,4,2,7,5,3,8,6,9]
--   
-- -- This is how the execution of the above stream proceeds: -- --
    --
  1. The scheduler queue is initialized with [S.fromList [1,2,3], -- (S.fromList [4,5,6]) <> (S.fromList [7,8,9])] assuming the -- head of the queue is represented by the rightmost item.
  2. --
  3. S.fromList [1,2,3] is executed, yielding the element -- 1 and putting [2,3] at the back of the scheduler -- queue. The scheduler queue now looks like [(S.fromList [4,5,6]) -- <> (S.fromList [7,8,9]), S.fromList [2,3]].
  4. --
  5. Now (S.fromList [4,5,6]) <> (S.fromList [7,8,9]) is -- picked up for execution, S.fromList [7,8,9] is added at the -- back of the queue and S.fromList [4,5,6] is executed, -- yielding the element 4 and adding S.fromList [5,6] -- at the back of the queue. The queue now looks like [S.fromList -- [2,3], S.fromList [7,8,9], S.fromList [5,6]].
  6. --
  7. Note that the scheduler queue expands by one more stream component -- in every pass because one more <> is broken down into -- two components. At this point there are no more <> -- operations to be broken down further and the queue has reached its -- maximum size. Now these streams are scheduled in round-robin fashion -- yielding [2,7,5,3,8,8,9].
  8. --
-- -- As we see above, in a right associated expression composed with -- <>, only one <> operation is broken down -- into two components in one execution, therefore, if we have n -- streams composed using <> it will take n -- scheduler passes to expand the whole expression. By the time -- n-th component is added to the scheduler queue, the first -- component would have received n scheduler passes. -- -- Since all streams get interleaved, this operation is not suitable for -- folding an infinite lazy container of infinite size streams. However, -- if the streams are small, the streams on the left may get finished -- before more streams are added to the scheduler queue from the right -- side of the expression, so it may be possible to fold an infinite lazy -- container of streams. For example, if the streams are of size -- n then at most n streams would be in the scheduler -- queue at a time. -- -- Note that WSerialT and WAsyncT differ in their -- scheduling behavior, therefore the output of WAsyncT even with -- a single thread of execution is not the same as that of -- WSerialT See notes in WSerialT for details about its -- scheduling behavior. -- -- Any exceptions generated by a constituent stream are propagated to the -- output stream. The output and exceptions from a single stream are -- guaranteed to arrive in the same order in the resulting stream as they -- were generated in the input stream. However, the relative ordering of -- elements from different streams in the resulting stream can vary -- depending on scheduling and generation delays. -- -- Similarly, the Monad instance of WAsyncT runs all -- iterations fairly concurrently using a round robin scheduling. -- --
--   main = drain . wAsyncly $ do
--       n <- return 3 <> return 2 <> return 1
--       S.yieldM $ do
--            threadDelay (n * 1000000)
--            myThreadId >>= \tid -> putStrLn (show tid ++ ": Delay " ++ show n)
--   
-- --
--   ThreadId 40: Delay 1
--   ThreadId 39: Delay 2
--   ThreadId 38: Delay 3
--   
data WAsyncT m a -- | Async composition with strict concurrent execution of all streams. -- -- The Semigroup instance of ParallelT executes both the -- streams concurrently without any delay or without waiting for the -- consumer demand and merges the results as they arrive. If the -- consumer does not consume the results, they are buffered upto a -- configured maximum, controlled by the maxBuffer primitive. If -- the buffer becomes full the concurrent tasks will block until there is -- space in the buffer. -- -- Both WAsyncT and ParallelT, evaluate the constituent -- streams fairly in a round robin fashion. The key difference is that -- WAsyncT might wait for the consumer demand before it executes -- the tasks whereas ParallelT starts executing all the tasks -- immediately without waiting for the consumer demand. For -- WAsyncT the maxThreads limit applies whereas for -- ParallelT it does not apply. In other words, WAsyncT -- can be lazy whereas ParallelT is strict. -- -- ParallelT is useful for cases when the streams are required to -- be evaluated simultaneously irrespective of how the consumer consumes -- them e.g. when we want to race two tasks and want to start both -- strictly at the same time or if we have timers in the parallel tasks -- and our results depend on the timers being started at the same time. -- If we do not have such requirements then AsyncT or -- AheadT are recommended as they can be more efficient than -- ParallelT. -- --
--   main = (toList . parallely $ (fromFoldable [1,2]) <> (fromFoldable [3,4])) >>= print
--   
-- --
--   [1,3,2,4]
--   
-- -- When streams with more than one element are merged, it yields -- whichever stream yields first without any bias, unlike the -- Async style streams. -- -- Any exceptions generated by a constituent stream are propagated to the -- output stream. The output and exceptions from a single stream are -- guaranteed to arrive in the same order in the resulting stream as they -- were generated in the input stream. However, the relative ordering of -- elements from different streams in the resulting stream can vary -- depending on scheduling and generation delays. -- -- Similarly, the Monad instance of ParallelT runs -- all iterations of the loop concurrently. -- --
--   import Streamly
--   import qualified Streamly.Prelude as S
--   import Control.Concurrent
--   
--   main = drain . parallely $ do
--       n <- return 3 <> return 2 <> return 1
--       S.yieldM $ do
--            threadDelay (n * 1000000)
--            myThreadId >>= \tid -> putStrLn (show tid ++ ": Delay " ++ show n)
--   
-- --
--   ThreadId 40: Delay 1
--   ThreadId 39: Delay 2
--   ThreadId 38: Delay 3
--   
-- -- Note that parallel composition can only combine a finite number of -- streams as it needs to retain state for each unfinished stream. -- -- Since: 0.7.0 (maxBuffer applies to ParallelT streams) -- -- Since: 0.1.0 data ParallelT m a -- | The applicative instance of ZipSerialM zips a number of streams -- serially i.e. it produces one element from each stream serially and -- then zips all those elements. -- --
--   main = (toList . zipSerially $ (,,) <$> s1 <*> s2 <*> s3) >>= print
--       where s1 = fromFoldable [1, 2]
--             s2 = fromFoldable [3, 4]
--             s3 = fromFoldable [5, 6]
--   
-- --
--   [(1,3,5),(2,4,6)]
--   
-- -- The Semigroup instance of this type works the same way as that -- of SerialT. data ZipSerialM m a -- | Like ZipSerialM but zips in parallel, it generates all the -- elements to be zipped concurrently. -- --
--   main = (toList . zipAsyncly $ (,,) <$> s1 <*> s2 <*> s3) >>= print
--       where s1 = fromFoldable [1, 2]
--             s2 = fromFoldable [3, 4]
--             s3 = fromFoldable [5, 6]
--   
-- --
--   [(1,3,5),(2,4,6)]
--   
-- -- The Semigroup instance of this type works the same way as that -- of SerialT. 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. -- --
--   drain $
--      S.mapM (\x -> threadDelay 1000000 >> print x)
--        |$ S.repeatM (threadDelay 1000000 >> return 1)
--   
-- -- Concurrent (|$) :: (IsStream t, MonadAsync m) => (t m a -> t m b) -> t m a -> t m b infixr 0 |$ -- | Parallel reverse function application operator for streams; just like -- the regular reverse function application operator & -- except that it is concurrent. -- --
--   drain $
--         S.repeatM (threadDelay 1000000 >> return 1)
--      |& S.mapM (\x -> threadDelay 1000000 >> print x)
--   
-- -- Concurrent (|&) :: (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. -- --
--   S.foldlM' (\_ a -> threadDelay 1000000 >> print a) ()
--      |$. S.repeatM (threadDelay 1000000 >> return 1)
--   
-- -- Concurrent (|$.) :: (IsStream t, MonadAsync m) => (t m a -> m b) -> t m a -> m b infixr 0 |$. -- | Parallel reverse function application operator for applying a run or -- fold functions to a stream. Just like |$. except that the -- operands are reversed. -- --
--       S.repeatM (threadDelay 1000000 >> return 1)
--   |&. S.foldlM' (\_ a -> threadDelay 1000000 >> print a) ()
--   
-- -- Concurrent (|&.) :: (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) -- | Polymorphic version of the Semigroup operation <> -- of SerialT. Appends two streams sequentially, yielding all -- elements from the first stream, and then all elements from the second -- stream. serial :: IsStream t => t m a -> t m a -> t m a -- | Polymorphic version of the Semigroup operation <> -- of WSerialT. 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 :: IsStream t => t m a -> t m a -> t m a -- | Polymorphic version of the Semigroup operation <> -- of AheadT. Merges two streams sequentially but with concurrent -- lookahead. ahead :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | Polymorphic version of the Semigroup operation <> -- of AsyncT. Merges two streams possibly concurrently, preferring -- the elements from the left one when available. async :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | Polymorphic version of the Semigroup operation <> -- of WAsyncT. Merges two streams concurrently choosing elements -- from both fairly. wAsync :: (IsStream t, MonadAsync m) => t m a -> t m a -> t m a -- | Polymorphic version of the Semigroup operation <> -- of ParallelT Merges two streams concurrently. parallel :: (IsStream t, MonadAsync m) => t m a -> 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. 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. 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. 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: -- -- 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. 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. 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. 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. 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. 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. serially :: IsStream t => SerialT m a -> t m a -- | Fix the type of a polymorphic stream as WSerialT. wSerially :: IsStream t => WSerialT m a -> t m a -- | Fix the type of a polymorphic stream as AsyncT. asyncly :: IsStream t => AsyncT m a -> t m a -- | Fix the type of a polymorphic stream as AheadT. aheadly :: IsStream t => AheadT m a -> t m a -- | Fix the type of a polymorphic stream as WAsyncT. wAsyncly :: IsStream t => WAsyncT m a -> t m a -- | Fix the type of a polymorphic stream as ParallelT. parallely :: IsStream t => ParallelT m a -> t m a -- | Fix the type of a polymorphic stream as ZipSerialM. zipSerially :: IsStream t => ZipSerialM m a -> t m a -- | Fix the type of a polymorphic stream as ZipAsyncM. zipAsyncly :: IsStream t => ZipAsyncM m a -> t m a -- | Adapt any specific stream type to any other specific stream type. 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. type Serial = SerialT IO -- | An interleaving serial IO stream of elements of type a. See -- WSerialT documentation for more details. type WSerial = WSerialT IO -- | A serial IO stream of elements of type a with concurrent -- lookahead. See AheadT documentation for more details. type Ahead = AheadT IO -- | A demand driven left biased parallely composing IO stream of elements -- of type a. See AsyncT documentation for more details. type Async = AsyncT IO -- | A round robin parallely composing IO stream of elements of type -- a. See WAsyncT documentation for more details. type WAsync = WAsyncT IO -- | A parallely composing IO stream of elements of type a. See -- ParallelT documentation for more details. type Parallel = ParallelT IO -- | An IO stream whose applicative instance zips streams serially. type ZipSerial = ZipSerialM IO -- | An IO stream whose applicative instance zips streams wAsyncly. type ZipAsync = ZipAsyncM IO -- | A variant of fold that allows you to fold a Foldable -- container of streams using the specified stream sum operation. -- --
--   foldWith async $ map return [1..3]
--   
-- -- Equivalent to: -- --
--   foldWith f = S.foldMapWith f id
--   
-- -- Since: 0.1.0 (Streamly) foldWith :: (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. -- --
--   foldMapWith async return [1..3]
--   
-- -- Equivalent to: -- --
--   foldMapWith f g xs = S.concatMapWith f g (S.fromFoldable xs)
--   
-- -- Since: 0.1.0 (Streamly) foldMapWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b -- | Like foldMapWith but with the last two arguments reversed i.e. -- the monadic streaming function is the last argument. -- -- Equivalent to: -- --
--   forEachWith = flip S.foldMapWith
--   
-- -- Since: 0.1.0 (Streamly) 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 (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". -- | Deprecated: Please use Streamly.Prelude.drain instead. runStream :: Monad m => SerialT m a -> m () -- | Same as runStream -- | Deprecated: Please use runStream instead. runStreaming :: (Monad m, IsStream t) => t m a -> m () -- | Same as runStream. -- | Deprecated: Please use runStream instead. runStreamT :: Monad m => SerialT m a -> m () -- | Same as runStream . wSerially. -- | Deprecated: Please use 'runStream . interleaving' instead. runInterleavedT :: Monad m => WSerialT m a -> m () -- | Same as runStream . asyncly. -- | Deprecated: Please use 'runStream . asyncly' instead. runAsyncT :: Monad m => AsyncT m a -> m () -- | Same as runStream . parallely. -- | Deprecated: Please use 'runStream . parallely' instead. runParallelT :: Monad m => ParallelT m a -> m () -- | Same as runStream . zipping. -- | Deprecated: Please use 'runStream . zipSerially instead. runZipStream :: Monad m => ZipSerialM m a -> m () -- | Same as runStream . zippingAsync. -- | Deprecated: Please use 'runStream . zipAsyncly instead. 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 wSerially. -- | Deprecated: Please use wSerially instead. interleaving :: IsStream t => WSerialT m a -> t m a -- | Same as zipSerially. -- | Deprecated: Please use zipSerially instead. zipping :: IsStream t => ZipSerialM m a -> t m a -- | Same as zipAsyncly. -- | Deprecated: Please use zipAsyncly 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 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)] -- | handleWithM socket act runs the monadic computation -- act passing the socket handle to it. The handle will be -- closed on exit from handleWithM, whether by normal termination -- or by raising an exception. If closing the handle raises an exception, -- then this exception will be raised by handleWithM rather than -- any exception raised by act. handleWithM :: (MonadMask m, MonadIO m) => (Socket -> m ()) -> Socket -> m () -- | Like handleWithM but runs a streaming computation instead of a -- monadic computation. handleWith :: (IsStream t, MonadCatch m, MonadIO 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. -- -- Internal connections :: MonadAsync m => Int -> SockSpec -> SockAddr -> SerialT m 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 -- | 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) -- | 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) -- | 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 arrays to a handle. fromChunks :: (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. fromBytesWithBufferOf :: 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. fromBytes :: 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. 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 -> Socket -> Fold m (Array a) () -- | Write a stream of strings to a socket in Latin1 encoding. Output is -- flushed to the socket for each string. -- -- Internal writeStrings :: MonadIO m => (SerialT m Char -> SerialT m Word8) -> Socket -> Fold m String () -- | 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 more succinctly by using higher level -- operations from Streamly.Network.Inet.TCP module. -- --
--   {-# LANGUAGE FlexibleContexts #-}
--   
--   import Data.Function ((&))
--   import Network.Socket
--   import Streamly.Internal.Network.Socket (handleWithM)
--   import Streamly.Network.Socket (SockSpec(..))
--   
--   import Streamly
--   import qualified Streamly.Prelude as S
--   import qualified Streamly.Network.Socket as SK
--   
--   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 =
--             S.unfold SK.accept (maxListenQueue, spec, addr) -- SerialT IO Socket
--           & parallely . S.mapM (handleWithM echo)           -- SerialT IO ()
--           & S.drain                                         -- IO ()
--   
--       echo sk =
--             S.unfold SK.readChunks sk  -- SerialT IO (Array Word8)
--           & S.fold (SK.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 SK
--   
-- --

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) -- | 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) () -- | 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. -- -- Internal 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)
--   
-- -- Internal 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)
--   
-- -- Internal connectionsOnLocalHost :: MonadAsync m => PortNumber -> SerialT m Socket -- | Connect to the specified IP address and port number. 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. -- -- Internal 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. -- -- Internal usingConnection :: (MonadCatch m, MonadIO 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, MonadIO 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. -- -- Internal withConnection :: (IsStream t, MonadCatch m, MonadIO 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, MonadIO 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. fromBytes :: (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. fromBytesWithBufferOf :: (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. fromChunks :: (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. -- -- Internal transformBytesWith :: (IsStream t, MonadAsync m, MonadCatch m) => (Word8, Word8, Word8, Word8) -> PortNumber -> SerialT m Word8 -> t m Word8 -- | 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. connect :: (Word8, Word8, Word8, Word8) -> PortNumber -> IO Socket module Streamly.Internal.FileSystem.Handle -- | Unfolds a file handle into a byte stream. IO requests to the device -- are performed in sizes of defaultChunkSize. 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 :: MonadIO m => Unfold m (Int, Handle) Word8 -- | Generate a byte stream from a file Handle. -- -- Internal 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. -- -- Internal toBytesWithBufferOf :: (IsStream t, MonadIO m) => Int -> Handle -> t m Word8 -- | Read a stream of bytes from standard input. -- --
--   getBytes = toBytes stdin
--   
-- -- Internal getBytes :: (IsStream t, MonadIO m) => 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 :: 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 :: (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 = toChunksWithBufferOf defaultChunkSize
--   
toChunks :: (IsStream t, MonadIO m) => Handle -> t 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 = toChunks stdin
--   
-- -- Internal getChunks :: (IsStream t, MonadIO m) => 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 :: MonadIO m => Handle -> Fold m Word8 () write2 :: MonadIO m => Fold2 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 :: MonadIO m => Int -> Handle -> Fold m 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. fromBytes :: MonadIO m => Handle -> SerialT m Word8 -> m () -- | fromBytesWithBufferOf 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. fromBytesWithBufferOf :: MonadIO m => Int -> Handle -> SerialT m Word8 -> m () -- | Write an Array to a file handle. writeArray :: Storable a => Handle -> Array a -> IO () -- | Write a stream of arrays to a handle. Each array in the stream is -- written to the device as a separate IO request. 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) () -- | fromChunksWithBufferOf 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. fromChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Handle -> SerialT m (Array a) -> m () -- | Write a stream of arrays to a handle. fromChunks :: (MonadIO m, Storable a) => Handle -> SerialT m (Array a) -> m () -- | Write a stream of chunks to standard output. -- -- Internal putChunks :: (MonadIO m, Storable a) => SerialT m (Array a) -> m () -- | Write a stream of strings to standard output using the supplied -- encoding. Output is flushed to the device for each string. -- -- Internal putStrings :: MonadAsync m => (SerialT m Char -> SerialT m Word8) -> SerialT m String -> m () -- | Write a stream of bytes from standard output. -- --
--   putBytes = fromBytes stdout
--   
-- -- Internal putBytes :: MonadIO m => SerialT m Word8 -> m () -- | Write a stream of strings as separate lines to standard output using -- the supplied encoding. Output is line buffered i.e. the output is -- written to the device as soon as a newline is encountered. -- -- Internal putLines :: MonadAsync m => (SerialT m Char -> SerialT m Word8) -> SerialT m String -> m () -- | 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. -- -- Internal withFile :: (IsStream t, MonadCatch m, MonadIO m) => FilePath -> IOMode -> (Handle -> t m a) -> t m a -- | Unfolds a file path into a byte stream. IO requests to the device are -- performed in sizes of defaultChunkSize. read :: (MonadCatch m, MonadIO 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. -- -- Internal toBytes :: (IsStream t, MonadCatch m, MonadIO m) => FilePath -> t m 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, MonadIO 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, MonadIO 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. -- -- Internal 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. -- -- Internal 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. -- -- Internal 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. writeArray :: 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. -- -- Internal 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 () -- | Read and write streams and arrays to and from file handles. File -- handle IO APIs are quite similar to Streamly.Memory.Array read -- write APIs. In that regard, arrays can be considered as in-memory -- files or files can be considered as on-disk arrays. -- -- Control over file reading and writing behavior in terms of buffering, -- encoding, decoding is in the hands of the programmer, the -- TextEncoding, NewLineMode, and Buffering -- options of the underlying handle provided by GHC are not needed and -- ignored. -- --

Programmer Notes

-- --
--   import qualified Streamly.FileSystem.Handle as FH
--   
-- -- For additional, experimental APIs take a look at -- Streamly.Internal.FileSystem.Handle module. -- --

Performance Notes

-- -- In some cases the stream type based APIs in the -- Streamly.Internal.FileSystem.Handle module may be more -- efficient compared to the unfold/fold based APIs exposed from this -- module because of better fusion by GHC. However, with the streamly -- fusion GHC plugin (upcoming) these APIs would perform as well as the -- stream based APIs in all cases. module Streamly.FileSystem.Handle -- | Unfolds a file handle into a byte stream. IO requests to the device -- are performed in sizes of defaultChunkSize. 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 :: 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 :: 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 :: 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 :: 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 :: (MonadIO m, Storable a) => Handle -> Fold m (Array a) () module Streamly.Internal.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 decodeLatin1 :: (IsStream t, Monad m) => t m Word8 -> t m Char -- | Decode a UTF-8 encoded bytestream to a stream of Unicode characters. -- The incoming stream is truncated if an invalid codepoint is -- encountered. -- -- Since: 0.7.0 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 replaced with the unicode -- replacement character. -- -- Since: 0.7.0 decodeUtf8Lax :: (Monad m, IsStream t) => t m Word8 -> t m Char data DecodeError DecodeError :: !DecodeState -> !CodePoint -> DecodeError type DecodeState = Word8 type CodePoint = Int -- | Internal decodeUtf8Either :: (Monad m, IsStream t) => t m Word8 -> t m (Either DecodeError Char) -- | Internal resumeDecodeUtf8Either :: (Monad m, IsStream t) => DecodeState -> CodePoint -> t m Word8 -> t m (Either DecodeError Char) -- | Internal decodeUtf8Arrays :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char -- | Internal decodeUtf8ArraysLenient :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char -- | 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. -- -- Since: 0.7.0 encodeLatin1 :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Like encodeLatin1 but silently truncates and maps input -- characters beyond 255 to (incorrect) chars in 0-255 range. No error or -- exception is thrown when such truncation occurs. -- -- Since: 0.7.0 encodeLatin1Lax :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Encode a stream of Unicode characters to a UTF-8 encoded bytestream. -- -- Since: 0.7.0 encodeUtf8 :: (Monad m, IsStream t) => t m Char -> t m Word8 decodeUtf8D :: Monad m => Stream m Word8 -> Stream m Char encodeUtf8D :: Monad m => Stream m Char -> Stream m Word8 decodeUtf8LenientD :: Monad m => Stream m Word8 -> Stream m Char 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 decodeUtf8ArraysLenientD :: MonadIO m => Stream m (Array Word8) -> Stream m Char -- | Remove leading whitespace from a string. -- --
--   stripStart = S.dropWhile isSpace
--   
-- -- Internal stripStart :: (Monad m, IsStream t) => t m Char -> t m Char -- | Fold each line of the stream using the supplied Fold and stream -- the result. -- --
--   >>> S.toList $ lines FL.toList (S.fromList "lines\nthis\nstring\n\n\n")
--   ["lines", "this", "string", "", ""]
--   
-- --
--   lines = S.splitOnSuffix (== '\n')
--   
-- -- Internal 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. -- --
--   >>> S.toList $ words FL.toList (S.fromList "fold these     words")
--   ["fold", "these", "words"]
--   
-- --
--   words = S.wordsBy isSpace
--   
-- -- Internal 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. -- -- Internal 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. -- -- Internal unwords :: (MonadIO m, IsStream t) => Unfold m a Char -> t m a -> t m Char instance GHC.Show.Show Streamly.Internal.Data.Unicode.Stream.CodingFailureMode instance GHC.Show.Show Streamly.Internal.Data.Unicode.Stream.DecodeError module Streamly.Internal.Memory.Unicode.Array -- | Break a string up into a stream of strings at newline characters. The -- resulting strings do not contain newlines. -- --
--   lines = S.lines A.write
--   
-- --
--   >>> S.toList $ lines $ S.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
--   
-- --
--   >>> S.toList $ words $ S.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. -- --
--   >>> S.toList $ unlines $ S.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. -- --
--   >>> S.toList $ unwords $ S.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 -- |

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. 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 decodeLatin1 :: (IsStream t, Monad m) => t m Word8 -> t m Char -- | Decode a UTF-8 encoded bytestream to a stream of Unicode characters. -- The incoming stream is truncated if an invalid codepoint is -- encountered. -- -- Since: 0.7.0 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 replaced with the unicode -- replacement character. -- -- Since: 0.7.0 decodeUtf8Lax :: (Monad m, IsStream t) => t m Word8 -> t m Char -- | 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. -- -- Since: 0.7.0 encodeLatin1 :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Like encodeLatin1 but silently truncates and maps input -- characters beyond 255 to (incorrect) chars in 0-255 range. No error or -- exception is thrown when such truncation occurs. -- -- Since: 0.7.0 encodeLatin1Lax :: (IsStream t, Monad m) => t m Char -> t m Word8 -- | Encode a stream of Unicode characters to a UTF-8 encoded bytestream. -- -- Since: 0.7.0 encodeUtf8 :: (Monad m, IsStream t) => t m Char -> t m Word8 -- | Streamly is a general computing framework based on concurrent data -- flow programming. The IO monad and pure lists are a special case of -- streamly. On one hand, streamly extends the lists of pure values to -- lists of monadic actions, on the other hand it extends the IO monad -- with concurrent non-determinism. In simple imperative terms we can say -- that streamly extends the IO monad with for loops and nested -- for loops with concurrency support. Hopefully, this analogy -- becomes clearer once you go through this tutorial. -- -- Streaming in general enables writing modular, composable and scalable -- applications with ease, and concurrency allows you to make them scale -- and perform well. Streamly enables writing scalable concurrent -- applications without being aware of threads or synchronization. No -- explicit thread control is needed. Where applicable, concurrency rate -- is automatically controlled based on the demand by the consumer. -- However, combinators can be used to fine tune the concurrency control. -- -- Streaming and concurrency together enable expressing reactive -- applications conveniently. See the CirclingSquare example in -- the examples directory for a simple SDL based FRP example. To -- summarize, streamly provides a unified computing framework for -- streaming, non-determinism and functional reactive programming in an -- elegant and simple API that is a natural extension of pure lists to -- monadic streams. -- -- In this tutorial we will go over the basic concepts and how to use the -- library. Before you go through this tutorial we recommend that you -- take a look at: -- -- -- -- Once you finish this tutorial, see the last section for further -- reading resources. module Streamly.Tutorial