conduit-combinators-1.1.2/src/0000755000000000000000000000000013211200065014441 5ustar0000000000000000conduit-combinators-1.1.2/src/Data/0000755000000000000000000000000013211200065015312 5ustar0000000000000000conduit-combinators-1.1.2/src/Data/Conduit/0000755000000000000000000000000013211222300016713 5ustar0000000000000000conduit-combinators-1.1.2/src/Data/Conduit/Combinators/0000755000000000000000000000000013211222300021173 5ustar0000000000000000conduit-combinators-1.1.2/test/0000755000000000000000000000000013211222300014625 5ustar0000000000000000conduit-combinators-1.1.2/test/subdir/0000755000000000000000000000000012736421710016136 5ustar0000000000000000conduit-combinators-1.1.2/src/Conduit.hs0000644000000000000000000000376213211200065016412 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} -- | Your intended one-stop-shop for conduit functionality. -- This re-exports functions from many commonly used modules. -- When there is a conflict with standard functions, functions -- in this module are disambiguated by adding a trailing C -- (or for chunked functions, replacing a trailing E with CE). -- This means that the Conduit module can be imported unqualified -- without causing naming conflicts. -- -- For more information on the naming scheme and intended usages of the -- combinators, please see the "Data.Conduit.Combinators" documentation. module Conduit ( -- * Core conduit library module Data.Conduit #if !MIN_VERSION_conduit(1,1,0) , module Data.Conduit.Util #endif #if MIN_VERSION_conduit(1, 0, 11) , module Data.Conduit.Lift #endif -- * Commonly used combinators , module Data.Conduit.Combinators.Unqualified -- * Monadic lifting , MonadIO (..) , MonadTrans (..) , MonadBase (..) , MonadThrow (..) , MonadBaseControl -- * ResourceT , MonadResource , ResourceT , runResourceT -- * Acquire #if MIN_VERSION_resourcet(1,1,0) , module Data.Acquire , withAcquire #endif -- * Pure pipelines , Identity (..) ) where import Data.Conduit #if !MIN_VERSION_conduit(1,1,0) import Data.Conduit.Util hiding (zip) #endif import Control.Monad.IO.Class (MonadIO (..)) import Control.Monad.Trans.Class (MonadTrans (..)) import Control.Monad.Trans.Control (MonadBaseControl) import Control.Monad.Base (MonadBase (..)) #if MIN_VERSION_conduit(1, 0, 11) import Data.Conduit.Lift #endif import Data.Conduit.Combinators.Unqualified import Data.Functor.Identity (Identity (..)) import Control.Monad.Trans.Resource (MonadResource, MonadThrow (..), runResourceT, ResourceT) #if MIN_VERSION_resourcet(1,1,0) import Data.Acquire hiding (with) import qualified Data.Acquire withAcquire :: MonadBaseControl IO m => Acquire a -> (a -> m b) -> m b withAcquire = Data.Acquire.with #endif conduit-combinators-1.1.2/src/Data/Conduit/Combinators.hs0000644000000000000000000017221713211222300021541 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE BangPatterns #-} -- | This module is meant as a replacement for Data.Conduit.List. -- That module follows a naming scheme which was originally inspired -- by its enumerator roots. This module is meant to introduce a naming -- scheme which encourages conduit best practices. -- -- There are two versions of functions in this module. Those with a trailing -- E work in the individual elements of a chunk of data, e.g., the bytes of -- a ByteString, the Chars of a Text, or the Ints of a Vector Int. Those -- without a trailing E work on unchunked streams. -- -- FIXME: discuss overall naming, usage of mono-traversable, etc -- -- Mention take (Conduit) vs drop (Consumer) module Data.Conduit.Combinators ( -- * Producers -- ** Pure yieldMany , unfold , enumFromTo , iterate , repeat , replicate , sourceLazy -- ** Monadic , repeatM , repeatWhileM , replicateM -- ** I\/O , sourceFile , sourceFileBS , sourceHandle , sourceIOHandle , stdin -- ** Random numbers , sourceRandom , sourceRandomN , sourceRandomGen , sourceRandomNGen , sourceRandomWith , sourceRandomNWith , sourceRandomGenWith , sourceRandomNGenWith -- ** Filesystem , sourceDirectory , sourceDirectoryDeep -- * Consumers -- ** Pure , drop , dropE , dropWhile , dropWhileE , fold , foldE , foldl , foldl1 , foldlE , foldMap , foldMapE , all , allE , any , anyE , and , andE , or , orE , asum , elem , elemE , notElem , notElemE , sinkLazy , sinkList , sinkVector , sinkVectorN , sinkBuilder , sinkLazyBuilder , sinkNull , awaitNonNull , head , headDef , headE , peek , peekE , last , lastDef , lastE , length , lengthE , lengthIf , lengthIfE , maximum , maximumE , minimum , minimumE , null , nullE , sum , sumE , product , productE , find -- ** Monadic , mapM_ , mapM_E , foldM , foldME , foldMapM , foldMapME -- ** I\/O , sinkFile , sinkFileBS , sinkHandle , sinkIOHandle , print , stdout , stderr -- * Transformers -- ** Pure , map , mapE , omapE , concatMap , concatMapE , take , takeE , takeWhile , takeWhileE , takeExactly , takeExactlyE , concat , filter , filterE , mapWhile , conduitVector , scanl , mapAccumWhile , concatMapAccum , intersperse , slidingWindow , chunksOfE , chunksOfExactlyE -- *** Binary base encoding , encodeBase64 , decodeBase64 , encodeBase64URL , decodeBase64URL , encodeBase16 , decodeBase16 -- ** Monadic , mapM , mapME , omapME , concatMapM , filterM , filterME , iterM , scanlM , mapAccumWhileM , concatMapAccumM -- ** Textual , encodeUtf8 , decodeUtf8 , decodeUtf8Lenient , line , lineAscii , unlines , unlinesAscii , takeExactlyUntilE , linesUnbounded , linesUnboundedAscii , splitOnUnboundedE -- * Special , vectorBuilder , mapAccumS , peekForever , peekForeverE ) where -- BEGIN IMPORTS import Data.Builder import qualified Data.NonNull as NonNull import qualified Data.Traversable import qualified Data.ByteString as S import qualified Data.ByteString.Base16 as B16 import qualified Data.ByteString.Base64 as B64 import qualified Data.ByteString.Base64.URL as B64U import Control.Applicative (Alternative(..), (<$>)) import Control.Exception (assert) import Control.Category (Category (..)) import Control.Monad (unless, when, (>=>), liftM, forever) import Control.Monad.Base (MonadBase (liftBase)) import Control.Monad.IO.Class (MonadIO (..)) import Control.Monad.Primitive (PrimMonad, PrimState) import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Resource (MonadResource, MonadThrow) import Data.Conduit import Data.Conduit.Binary (sourceFile, sourceHandle, sourceIOHandle, sinkFile, sinkHandle, sinkIOHandle) import qualified Data.Conduit.Filesystem as CF import Data.Conduit.Internal (ConduitM (..), Pipe (..)) import qualified Data.Conduit.List as CL import Data.Maybe (fromMaybe, isNothing, isJust) import Data.Monoid (Monoid (..)) import Data.MonoTraversable import qualified Data.Sequences as Seq import qualified Data.Vector.Generic as V import qualified Data.Vector.Generic.Mutable as VM import Data.Void (absurd) import Prelude (Bool (..), Eq (..), Int, Maybe (..), Either (..), Monad (..), Num (..), Ord (..), fromIntegral, maybe, either, ($), Functor (..), Enum, seq, Show, Char, mod, otherwise, Either (..), ($!), succ, FilePath) import Data.Word (Word8) import qualified Prelude import System.IO (Handle) import qualified System.IO as SIO import qualified Data.Conduit.Text as CT import Data.ByteString (ByteString) import Data.Text (Text) import qualified System.Random.MWC as MWC import Data.Conduit.Combinators.Internal import Data.Conduit.Combinators.Stream import Data.Conduit.Internal.Fusion import Data.Primitive.MutVar (MutVar, newMutVar, readMutVar, writeMutVar) #if MIN_VERSION_mono_traversable(1,0,0) import qualified Data.Sequences as DTE import Data.Sequences (LazySequence (..)) #else import Data.Sequences.Lazy import qualified Data.Textual.Encoding as DTE #endif -- Defines INLINE_RULE0, INLINE_RULE, STREAMING0, and STREAMING. #include "fusion-macros.h" -- END IMPORTS -- TODO: -- -- * The functions sourceRandom* are based on, initReplicate and -- initRepeat have specialized versions for when they're used with -- ($$). How does this interact with stream fusion? -- -- * Is it possible to implement fusion for vectorBuilder? Since it -- takes a Sink yielding function as an input, the rewrite rule -- would need to trigger when that parameter looks something like -- (\x -> unstream (...)). I don't see anything preventing doing -- this, but it would be quite a bit of code. -- NOTE: Fusion isn't possible for the following operations: -- -- * Due to a lack of leftovers: -- - dropE, dropWhile, dropWhileE -- - headE -- - peek, peekE -- - null, nullE -- - takeE, takeWhile, takeWhileE -- - mapWhile -- - codeWith -- - line -- - lineAscii -- -- * Due to a use of leftover in a dependency: -- - Due to "codeWith": encodeBase64, decodeBase64, encodeBase64URL, decodeBase64URL, decodeBase16 -- - due to "CT.decode": decodeUtf8, decodeUtf8Lenient -- -- * Due to lack of resource cleanup (e.g. bracketP): -- - sourceDirectory -- - sourceDirectoryDeep -- - sourceFile -- -- * takeExactly / takeExactlyE - no monadic bind. Another way to -- look at this is that subsequent streams drive stream evaluation, -- so there's no way for the conduit to guarantee a certain amount -- of demand from the upstream. -- | Yield each of the values contained by the given @MonoFoldable@. -- -- This will work on many data structures, including lists, @ByteString@s, and @Vector@s. -- -- Subject to fusion -- -- Since 1.0.0 yieldMany, yieldManyC :: (Monad m, MonoFoldable mono) => mono -> Producer m (Element mono) yieldManyC = ofoldMap yield {-# INLINE yieldManyC #-} STREAMING(yieldMany, yieldManyC, yieldManyS, x) -- | Generate a producer from a seed value. -- -- Subject to fusion -- -- Since 1.0.0 unfold :: Monad m => (b -> Maybe (a, b)) -> b -> Producer m a INLINE_RULE(unfold, f x, CL.unfold f x) -- | Enumerate from a value to a final value, inclusive, via 'succ'. -- -- This is generally more efficient than using @Prelude@\'s @enumFromTo@ and -- combining with @sourceList@ since this avoids any intermediate data -- structures. -- -- Subject to fusion -- -- Since 1.0.0 enumFromTo :: (Monad m, Enum a, Ord a) => a -> a -> Producer m a INLINE_RULE(enumFromTo, f t, CL.enumFromTo f t) -- | Produces an infinite stream of repeated applications of f to x. -- -- Subject to fusion -- -- Since 1.0.0 iterate :: Monad m => (a -> a) -> a -> Producer m a INLINE_RULE(iterate, f t, CL.iterate f t) -- | Produce an infinite stream consisting entirely of the given value. -- -- Subject to fusion -- -- Since 1.0.0 repeat :: Monad m => a -> Producer m a INLINE_RULE(repeat, x, iterate id x) -- | Produce a finite stream consisting of n copies of the given value. -- -- Subject to fusion -- -- Since 1.0.0 replicate :: Monad m => Int -> a -> Producer m a INLINE_RULE(replicate, n x, CL.replicate n x) -- | Generate a producer by yielding each of the strict chunks in a @LazySequence@. -- -- For more information, see 'toChunks'. -- -- Subject to fusion -- -- Since 1.0.0 sourceLazy :: (Monad m, LazySequence lazy strict) => lazy -> Producer m strict INLINE_RULE(sourceLazy, x, yieldMany (toChunks x)) -- | Repeatedly run the given action and yield all values it produces. -- -- Subject to fusion -- -- Since 1.0.0 repeatM, repeatMC :: Monad m => m a -> Producer m a repeatMC m = forever $ lift m >>= yield {-# INLINE repeatMC #-} STREAMING(repeatM, repeatMC, repeatMS, m) -- | Repeatedly run the given action and yield all values it produces, until -- the provided predicate returns @False@. -- -- Subject to fusion -- -- Since 1.0.0 repeatWhileM, repeatWhileMC :: Monad m => m a -> (a -> Bool) -> Producer m a repeatWhileMC m f = loop where loop = do x <- lift m when (f x) $ yield x >> loop STREAMING(repeatWhileM, repeatWhileMC, repeatWhileMS, m f) -- | Perform the given action n times, yielding each result. -- -- Subject to fusion -- -- Since 1.0.0 replicateM :: Monad m => Int -> m a -> Producer m a INLINE_RULE(replicateM, n m, CL.replicateM n m) -- | 'sourceFile' specialized to 'ByteString' to help with type -- inference. -- -- @since 1.0.7 sourceFileBS :: MonadResource m => FilePath -> Producer m ByteString sourceFileBS = sourceFile {-# INLINE sourceFileBS #-} -- | @sourceHandle@ applied to @stdin@. -- -- Subject to fusion -- -- Since 1.0.0 stdin :: MonadIO m => Producer m ByteString INLINE_RULE0(stdin, sourceHandle SIO.stdin) -- | Create an infinite stream of random values, seeding from the system random -- number. -- -- Subject to fusion -- -- Since 1.0.0 sourceRandom :: (MWC.Variate a, MonadIO m) => Producer m a sourceRandom = sourceRandomWith MWC.uniform {-# INLINE sourceRandom #-} -- | Create a stream of random values of length n, seeding from the system -- random number. -- -- Subject to fusion -- -- Since 1.0.0 sourceRandomN :: (MWC.Variate a, MonadIO m) => Int -- ^ count -> Producer m a sourceRandomN cnt = sourceRandomNWith cnt MWC.uniform {-# INLINE sourceRandomN #-} -- | Create an infinite stream of random values, using the given random number -- generator. -- -- Subject to fusion -- -- Since 1.0.0 sourceRandomGen :: (MWC.Variate a, MonadBase base m, PrimMonad base) => MWC.Gen (PrimState base) -> Producer m a sourceRandomGen gen = sourceRandomGenWith gen MWC.uniform {-# INLINE sourceRandomGen #-} -- | Create a stream of random values of length n, seeding from the system -- random number. -- -- Subject to fusion -- -- Since 1.0.0 sourceRandomNGen :: (MWC.Variate a, MonadBase base m, PrimMonad base) => MWC.Gen (PrimState base) -> Int -- ^ count -> Producer m a sourceRandomNGen gen cnt = sourceRandomNGenWith gen cnt MWC.uniform {-# INLINE sourceRandomNGen #-} -- | Create an infinite stream of random values from an arbitrary distribution, -- seeding from the system random number. -- -- Subject to fusion -- -- Since 1.0.3 sourceRandomWith :: (MWC.Variate a, MonadIO m) => (MWC.GenIO -> SIO.IO a) -> Producer m a INLINE_RULE(sourceRandomWith, f, initRepeat (liftIO MWC.createSystemRandom) (liftIO . f)) -- | Create a stream of random values of length n from an arbitrary -- distribution, seeding from the system random number. -- -- Subject to fusion -- -- Since 1.0.3 sourceRandomNWith :: (MWC.Variate a, MonadIO m) => Int -- ^ count -> (MWC.GenIO -> SIO.IO a) -> Producer m a INLINE_RULE(sourceRandomNWith, cnt f, initReplicate (liftIO MWC.createSystemRandom) (liftIO . f) cnt) -- | Create an infinite stream of random values from an arbitrary distribution, -- using the given random number generator. -- -- Subject to fusion -- -- Since 1.0.3 sourceRandomGenWith :: (MWC.Variate a, MonadBase base m, PrimMonad base) => MWC.Gen (PrimState base) -> (MWC.Gen (PrimState base) -> base a) -> Producer m a INLINE_RULE(sourceRandomGenWith, gen f, initRepeat (return gen) (liftBase . f)) -- | Create a stream of random values of length n from an arbitrary -- distribution, seeding from the system random number. -- -- Subject to fusion -- -- Since 1.0.3 sourceRandomNGenWith :: (MWC.Variate a, MonadBase base m, PrimMonad base) => MWC.Gen (PrimState base) -> Int -- ^ count -> (MWC.Gen (PrimState base) -> base a) -> Producer m a INLINE_RULE(sourceRandomNGenWith, gen cnt f, initReplicate (return gen) (liftBase . f) cnt) -- | Stream the contents of the given directory, without traversing deeply. -- -- This function will return /all/ of the contents of the directory, whether -- they be files, directories, etc. -- -- Note that the generated filepaths will be the complete path, not just the -- filename. In other words, if you have a directory @foo@ containing files -- @bar@ and @baz@, and you use @sourceDirectory@ on @foo@, the results will be -- @foo/bar@ and @foo/baz@. -- -- Since 1.0.0 sourceDirectory :: MonadResource m => FilePath -> Producer m FilePath sourceDirectory = CF.sourceDirectory -- | Deeply stream the contents of the given directory. -- -- This works the same as @sourceDirectory@, but will not return directories at -- all. This function also takes an extra parameter to indicate whether -- symlinks will be followed. -- -- Since 1.0.0 sourceDirectoryDeep :: MonadResource m => Bool -- ^ Follow directory symlinks -> FilePath -- ^ Root directory -> Producer m FilePath sourceDirectoryDeep = CF.sourceDirectoryDeep -- | Ignore a certain number of values in the stream. -- -- Since 1.0.0 drop :: Monad m => Int -> Consumer a m () INLINE_RULE(drop, n, CL.drop n) -- | Drop a certain number of elements from a chunked stream. -- -- Since 1.0.0 dropE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> Consumer seq m () dropE = loop where loop i = if i <= 0 then return () else await >>= maybe (return ()) (go i) go i sq = do unless (onull y) $ leftover y loop i' where (x, y) = Seq.splitAt i sq i' = i - fromIntegral (olength x) {-# INLINEABLE dropE #-} -- | Drop all values which match the given predicate. -- -- Since 1.0.0 dropWhile :: Monad m => (a -> Bool) -> Consumer a m () dropWhile f = loop where loop = await >>= maybe (return ()) go go x = if f x then loop else leftover x {-# INLINE dropWhile #-} -- | Drop all elements in the chunked stream which match the given predicate. -- -- Since 1.0.0 dropWhileE :: (Monad m, Seq.IsSequence seq) => (Element seq -> Bool) -> Consumer seq m () dropWhileE f = loop where loop = await >>= maybe (return ()) go go sq = if onull x then loop else leftover x where x = Seq.dropWhile f sq {-# INLINE dropWhileE #-} -- | Monoidally combine all values in the stream. -- -- Subject to fusion -- -- Since 1.0.0 fold :: (Monad m, Monoid a) => Consumer a m a INLINE_RULE0(fold, CL.foldMap id) -- | Monoidally combine all elements in the chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 foldE :: (Monad m, MonoFoldable mono, Monoid (Element mono)) => Consumer mono m (Element mono) INLINE_RULE0(foldE, CL.fold (\accum mono -> accum `mappend` ofoldMap id mono) mempty) -- | A strict left fold. -- -- Subject to fusion -- -- Since 1.0.0 foldl :: Monad m => (a -> b -> a) -> a -> Consumer b m a INLINE_RULE(foldl, f x, CL.fold f x) -- | A strict left fold on a chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 foldlE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> a) -> a -> Consumer mono m a INLINE_RULE(foldlE, f x, CL.fold (ofoldlPrime f) x) -- Work around CPP not supporting identifiers with primes... ofoldlPrime :: MonoFoldable mono => (a -> Element mono -> a) -> a -> mono -> a ofoldlPrime = ofoldl' -- | Apply the provided mapping function and monoidal combine all values. -- -- Subject to fusion -- -- Since 1.0.0 foldMap :: (Monad m, Monoid b) => (a -> b) -> Consumer a m b INLINE_RULE(foldMap, f, CL.foldMap f) -- | Apply the provided mapping function and monoidal combine all elements of the chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 foldMapE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Consumer mono m w INLINE_RULE(foldMapE, f, CL.foldMap (ofoldMap f)) -- | A strict left fold with no starting value. Returns 'Nothing' -- when the stream is empty. -- -- Subject to fusion foldl1, foldl1C :: Monad m => (a -> a -> a) -> Consumer a m (Maybe a) foldl1C f = await >>= maybe (return Nothing) loop where loop !prev = await >>= maybe (return $ Just prev) (loop . f prev) STREAMING(foldl1, foldl1C, foldl1S, f) -- | A strict left fold on a chunked stream, with no starting value. -- Returns 'Nothing' when the stream is empty. -- -- Subject to fusion -- -- Since 1.0.0 foldl1E :: (Monad m, MonoFoldable mono, a ~ Element mono) => (a -> a -> a) -> Consumer mono m (Maybe a) INLINE_RULE(foldl1E, f, foldl (foldMaybeNull f) Nothing) -- Helper for foldl1E foldMaybeNull :: (MonoFoldable mono, e ~ Element mono) => (e -> e -> e) -> Maybe e -> mono -> Maybe e foldMaybeNull f macc mono = case (macc, NonNull.fromNullable mono) of (Just acc, Just nn) -> Just $ ofoldl' f acc nn (Nothing, Just nn) -> Just $ NonNull.ofoldl1' f nn _ -> macc {-# INLINE foldMaybeNull #-} -- | Check that all values in the stream return True. -- -- Subject to shortcut logic: at the first False, consumption of the stream -- will stop. -- -- Subject to fusion -- -- Since 1.0.0 all, allC :: Monad m => (a -> Bool) -> Consumer a m Bool allC f = fmap isNothing $ find (Prelude.not . f) {-# INLINE allC #-} STREAMING(all, allC, allS, f) -- | Check that all elements in the chunked stream return True. -- -- Subject to shortcut logic: at the first False, consumption of the stream -- will stop. -- -- Subject to fusion -- -- Since 1.0.0 allE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m Bool INLINE_RULE(allE, f, all (oall f)) -- | Check that at least one value in the stream returns True. -- -- Subject to shortcut logic: at the first True, consumption of the stream -- will stop. -- -- Subject to fusion -- -- Since 1.0.0 any, anyC :: Monad m => (a -> Bool) -> Consumer a m Bool anyC = fmap isJust . find {-# INLINE anyC #-} STREAMING(any, anyC, anyS, f) -- | Check that at least one element in the chunked stream returns True. -- -- Subject to shortcut logic: at the first True, consumption of the stream -- will stop. -- -- Subject to fusion -- -- Since 1.0.0 anyE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m Bool INLINE_RULE(anyE, f, any (oany f)) -- | Are all values in the stream True? -- -- Consumption stops once the first False is encountered. -- -- Subject to fusion -- -- Since 1.0.0 and :: Monad m => Consumer Bool m Bool INLINE_RULE0(and, all id) -- | Are all elements in the chunked stream True? -- -- Consumption stops once the first False is encountered. -- -- Subject to fusion -- -- Since 1.0.0 andE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Consumer mono m Bool #if __GLASGOW_HASKELL__ >= 706 INLINE_RULE0(andE, allE id) #else andE = allE id {-# INLINE andE #-} #endif -- | Are any values in the stream True? -- -- Consumption stops once the first True is encountered. -- -- Subject to fusion -- -- Since 1.0.0 or :: Monad m => Consumer Bool m Bool INLINE_RULE0(or, any id) -- | Are any elements in the chunked stream True? -- -- Consumption stops once the first True is encountered. -- -- Subject to fusion -- -- Since 1.0.0 orE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Consumer mono m Bool #if __GLASGOW_HASKELL__ >= 706 INLINE_RULE0(orE, anyE id) #else orE = anyE id {-# INLINE orE #-} #endif -- | 'Alternative'ly combine all values in the stream. -- -- Since 1.1.1 asum :: (Monad m, Alternative f) => Consumer (f a) m (f a) INLINE_RULE0(asum, foldl (<|>) empty) -- | Are any values in the stream equal to the given value? -- -- Stops consuming as soon as a match is found. -- -- Subject to fusion -- -- Since 1.0.0 elem :: (Monad m, Eq a) => a -> Consumer a m Bool INLINE_RULE(elem, x, any (== x)) -- | Are any elements in the chunked stream equal to the given element? -- -- Stops consuming as soon as a match is found. -- -- Subject to fusion -- -- Since 1.0.0 #if MIN_VERSION_mono_traversable(1,0,0) elemE :: (Monad m, Seq.IsSequence seq, Eq (Element seq)) #else elemE :: (Monad m, Seq.EqSequence seq) #endif => Element seq -> Consumer seq m Bool #if MIN_VERSION_mono_traversable(0,8,0) INLINE_RULE(elemE, f, any (oelem f)) #else INLINE_RULE(elemE, f, any (Seq.elem f)) #endif -- | Are no values in the stream equal to the given value? -- -- Stops consuming as soon as a match is found. -- -- Subject to fusion -- -- Since 1.0.0 notElem :: (Monad m, Eq a) => a -> Consumer a m Bool INLINE_RULE(notElem, x, all (/= x)) -- | Are no elements in the chunked stream equal to the given element? -- -- Stops consuming as soon as a match is found. -- -- Subject to fusion -- -- Since 1.0.0 #if MIN_VERSION_mono_traversable(1,0,0) notElemE :: (Monad m, Seq.IsSequence seq, Eq (Element seq)) #else notElemE :: (Monad m, Seq.EqSequence seq) #endif => Element seq -> Consumer seq m Bool #if MIN_VERSION_mono_traversable(0,8,0) INLINE_RULE(notElemE, x, all (onotElem x)) #else INLINE_RULE(notElemE, x, all (Seq.notElem x)) #endif -- | Consume all incoming strict chunks into a lazy sequence. -- Note that the entirety of the sequence will be resident at memory. -- -- This can be used to consume a stream of strict ByteStrings into a lazy -- ByteString, for example. -- -- Subject to fusion -- -- Since 1.0.0 sinkLazy, sinkLazyC :: (Monad m, LazySequence lazy strict) => Consumer strict m lazy sinkLazyC = (fromChunks . ($ [])) <$> CL.fold (\front next -> front . (next:)) id {-# INLINE sinkLazyC #-} STREAMING0(sinkLazy, sinkLazyC, sinkLazyS) -- | Consume all values from the stream and return as a list. Note that this -- will pull all values into memory. -- -- Subject to fusion -- -- Since 1.0.0 sinkList :: Monad m => Consumer a m [a] INLINE_RULE0(sinkList, CL.consume) -- | Sink incoming values into a vector, growing the vector as necessary to fit -- more elements. -- -- Note that using this function is more memory efficient than @sinkList@ and -- then converting to a @Vector@, as it avoids intermediate list constructors. -- -- Subject to fusion -- -- Since 1.0.0 sinkVector, sinkVectorC :: (MonadBase base m, V.Vector v a, PrimMonad base) => Consumer a m (v a) sinkVectorC = do let initSize = 10 mv0 <- liftBase $ VM.new initSize let go maxSize i mv | i >= maxSize = do let newMax = maxSize * 2 mv' <- liftBase $ VM.grow mv maxSize go newMax i mv' go maxSize i mv = do mx <- await case mx of Nothing -> V.slice 0 i <$> liftBase (V.unsafeFreeze mv) Just x -> do liftBase $ VM.write mv i x go maxSize (i + 1) mv go initSize 0 mv0 {-# INLINEABLE sinkVectorC #-} STREAMING0(sinkVector, sinkVectorC, sinkVectorS) -- | Sink incoming values into a vector, up until size @maxSize@. Subsequent -- values will be left in the stream. If there are less than @maxSize@ values -- present, returns a @Vector@ of smaller size. -- -- Note that using this function is more memory efficient than @sinkList@ and -- then converting to a @Vector@, as it avoids intermediate list constructors. -- -- Subject to fusion -- -- Since 1.0.0 sinkVectorN, sinkVectorNC :: (MonadBase base m, V.Vector v a, PrimMonad base) => Int -- ^ maximum allowed size -> Consumer a m (v a) sinkVectorNC maxSize = do mv <- liftBase $ VM.new maxSize let go i | i >= maxSize = liftBase $ V.unsafeFreeze mv go i = do mx <- await case mx of Nothing -> V.slice 0 i <$> liftBase (V.unsafeFreeze mv) Just x -> do liftBase $ VM.write mv i x go (i + 1) go 0 {-# INLINEABLE sinkVectorNC #-} STREAMING(sinkVectorN, sinkVectorNC, sinkVectorNS, maxSize) -- | Convert incoming values to a builder and fold together all builder values. -- -- Defined as: @foldMap toBuilder@. -- -- Subject to fusion -- -- Since 1.0.0 sinkBuilder :: (Monad m, Monoid builder, ToBuilder a builder) => Consumer a m builder INLINE_RULE0(sinkBuilder, foldMap toBuilder) -- | Same as @sinkBuilder@, but afterwards convert the builder to its lazy -- representation. -- -- Alternatively, this could be considered an alternative to @sinkLazy@, with -- the following differences: -- -- * This function will allow multiple input types, not just the strict version -- of the lazy structure. -- -- * Some buffer copying may occur in this version. -- -- Subject to fusion -- -- Since 1.0.0 sinkLazyBuilder, sinkLazyBuilderC :: (Monad m, Monoid builder, ToBuilder a builder, Builder builder lazy) => Consumer a m lazy sinkLazyBuilderC = fmap builderToLazy sinkBuilder {-# INLINE sinkLazyBuilderC #-} STREAMING0(sinkLazyBuilder, sinkLazyBuilderC, sinkLazyBuilderS) -- | Consume and discard all remaining values in the stream. -- -- Subject to fusion -- -- Since 1.0.0 sinkNull :: Monad m => Consumer a m () INLINE_RULE0(sinkNull, CL.sinkNull) -- | Same as @await@, but discards any leading 'onull' values. -- -- Since 1.0.0 awaitNonNull :: (Monad m, MonoFoldable a) => Consumer a m (Maybe (NonNull.NonNull a)) awaitNonNull = go where go = await >>= maybe (return Nothing) go' go' = maybe go (return . Just) . NonNull.fromNullable {-# INLINE awaitNonNull #-} -- | Take a single value from the stream, if available. -- -- Since 1.0.5 head :: Monad m => Consumer a m (Maybe a) head = CL.head -- | Same as 'head', but returns a default value if none are available from the stream. -- -- Since 1.0.5 headDef :: Monad m => a -> Consumer a m a headDef a = fromMaybe a <$> head -- | Get the next element in the chunked stream. -- -- Since 1.0.0 headE :: (Monad m, Seq.IsSequence seq) => Consumer seq m (Maybe (Element seq)) headE = loop where loop = await >>= maybe (return Nothing) go go x = case Seq.uncons x of Nothing -> loop Just (y, z) -> do unless (onull z) $ leftover z return $ Just y {-# INLINE headE #-} -- | View the next value in the stream without consuming it. -- -- Since 1.0.0 peek :: Monad m => Consumer a m (Maybe a) peek = CL.peek {-# INLINE peek #-} -- | View the next element in the chunked stream without consuming it. -- -- Since 1.0.0 peekE :: (Monad m, MonoFoldable mono) => Consumer mono m (Maybe (Element mono)) peekE = loop where loop = await >>= maybe (return Nothing) go go x = case headMay x of Nothing -> loop Just y -> do leftover x return $ Just y {-# INLINE peekE #-} -- | Retrieve the last value in the stream, if present. -- -- Subject to fusion -- -- Since 1.0.0 last, lastC :: Monad m => Consumer a m (Maybe a) lastC = await >>= maybe (return Nothing) loop where loop prev = await >>= maybe (return $ Just prev) loop STREAMING0(last, lastC, lastS) -- | Same as 'last', but returns a default value if none are available from the stream. -- -- Since 1.0.5 lastDef :: Monad m => a -> Consumer a m a lastDef a = fromMaybe a <$> last -- | Retrieve the last element in the chunked stream, if present. -- -- Subject to fusion -- -- Since 1.0.0 lastE, lastEC :: (Monad m, Seq.IsSequence seq) => Consumer seq m (Maybe (Element seq)) lastEC = awaitNonNull >>= maybe (return Nothing) (loop . NonNull.last) where loop prev = awaitNonNull >>= maybe (return $ Just prev) (loop . NonNull.last) STREAMING0(lastE, lastEC, lastES) -- | Count how many values are in the stream. -- -- Subject to fusion -- -- Since 1.0.0 length :: (Monad m, Num len) => Consumer a m len INLINE_RULE0(length, foldl (\x _ -> x + 1) 0) -- | Count how many elements are in the chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 lengthE :: (Monad m, Num len, MonoFoldable mono) => Consumer mono m len INLINE_RULE0(lengthE, foldl (\x y -> x + fromIntegral (olength y)) 0) -- | Count how many values in the stream pass the given predicate. -- -- Subject to fusion -- -- Since 1.0.0 lengthIf :: (Monad m, Num len) => (a -> Bool) -> Consumer a m len INLINE_RULE(lengthIf, f, foldl (\cnt a -> if f a then (cnt + 1) else cnt) 0) -- | Count how many elements in the chunked stream pass the given predicate. -- -- Subject to fusion -- -- Since 1.0.0 lengthIfE :: (Monad m, Num len, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m len INLINE_RULE(lengthIfE, f, foldlE (\cnt a -> if f a then (cnt + 1) else cnt) 0) -- | Get the largest value in the stream, if present. -- -- Subject to fusion -- -- Since 1.0.0 maximum :: (Monad m, Ord a) => Consumer a m (Maybe a) INLINE_RULE0(maximum, foldl1 max) -- | Get the largest element in the chunked stream, if present. -- -- Subject to fusion -- -- Since 1.0.0 #if MIN_VERSION_mono_traversable(1,0,0) maximumE :: (Monad m, Seq.IsSequence seq, Ord (Element seq)) => Consumer seq m (Maybe (Element seq)) #else maximumE :: (Monad m, Seq.OrdSequence seq) => Consumer seq m (Maybe (Element seq)) #endif INLINE_RULE0(maximumE, foldl1E max) -- | Get the smallest value in the stream, if present. -- -- Subject to fusion -- -- Since 1.0.0 minimum :: (Monad m, Ord a) => Consumer a m (Maybe a) INLINE_RULE0(minimum, foldl1 min) -- | Get the smallest element in the chunked stream, if present. -- -- Subject to fusion -- -- Since 1.0.0 #if MIN_VERSION_mono_traversable(1,0,0) minimumE :: (Monad m, Seq.IsSequence seq, Ord (Element seq)) => Consumer seq m (Maybe (Element seq)) #else minimumE :: (Monad m, Seq.OrdSequence seq) => Consumer seq m (Maybe (Element seq)) #endif INLINE_RULE0(minimumE, foldl1E min) -- | True if there are no values in the stream. -- -- This function does not modify the stream. -- -- Since 1.0.0 null :: Monad m => Consumer a m Bool null = (maybe True (\_ -> False)) `fmap` peek {-# INLINE null #-} -- | True if there are no elements in the chunked stream. -- -- This function may remove empty leading chunks from the stream, but otherwise -- will not modify it. -- -- Since 1.0.0 nullE :: (Monad m, MonoFoldable mono) => Consumer mono m Bool nullE = go where go = await >>= maybe (return True) go' go' x = if onull x then go else leftover x >> return False {-# INLINE nullE #-} -- | Get the sum of all values in the stream. -- -- Subject to fusion -- -- Since 1.0.0 sum :: (Monad m, Num a) => Consumer a m a INLINE_RULE0(sum, foldl (+) 0) -- | Get the sum of all elements in the chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 sumE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono) INLINE_RULE0(sumE, foldlE (+) 0) -- | Get the product of all values in the stream. -- -- Subject to fusion -- -- Since 1.0.0 product :: (Monad m, Num a) => Consumer a m a INLINE_RULE0(product, foldl (*) 1) -- | Get the product of all elements in the chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 productE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono) INLINE_RULE0(productE, foldlE (*) 1) -- | Find the first matching value. -- -- Subject to fusion -- -- Since 1.0.0 find, findC :: Monad m => (a -> Bool) -> Consumer a m (Maybe a) findC f = loop where loop = await >>= maybe (return Nothing) go go x = if f x then return (Just x) else loop {-# INLINE findC #-} STREAMING(find, findC, findS, f) -- | Apply the action to all values in the stream. -- -- Subject to fusion -- -- Since 1.0.0 mapM_ :: Monad m => (a -> m ()) -> Consumer a m () INLINE_RULE(mapM_, f, CL.mapM_ f) -- | Apply the action to all elements in the chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 mapM_E :: (Monad m, MonoFoldable mono) => (Element mono -> m ()) -> Consumer mono m () INLINE_RULE(mapM_E, f, CL.mapM_ (omapM_ f)) -- | A monadic strict left fold. -- -- Subject to fusion -- -- Since 1.0.0 foldM :: Monad m => (a -> b -> m a) -> a -> Consumer b m a INLINE_RULE(foldM, f x, CL.foldM f x) -- | A monadic strict left fold on a chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 foldME :: (Monad m, MonoFoldable mono) => (a -> Element mono -> m a) -> a -> Consumer mono m a INLINE_RULE(foldME, f x, foldM (ofoldlM f) x) -- | Apply the provided monadic mapping function and monoidal combine all values. -- -- Subject to fusion -- -- Since 1.0.0 foldMapM :: (Monad m, Monoid w) => (a -> m w) -> Consumer a m w INLINE_RULE(foldMapM, f, CL.foldMapM f) -- | Apply the provided monadic mapping function and monoidal combine all -- elements in the chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 foldMapME :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> m w) -> Consumer mono m w INLINE_RULE(foldMapME, f, CL.foldM (ofoldlM (\accum e -> mappend accum `liftM` f e)) mempty) -- | 'sinkFile' specialized to 'ByteString' to help with type -- inference. -- -- @since 1.0.7 sinkFileBS :: MonadResource m => FilePath -> Consumer ByteString m () sinkFileBS = sinkFile {-# INLINE sinkFileBS #-} -- | Print all incoming values to stdout. -- -- Subject to fusion -- -- Since 1.0.0 print :: (Show a, MonadIO m) => Consumer a m () INLINE_RULE0(print, mapM_ (liftIO . Prelude.print)) -- | @sinkHandle@ applied to @stdout@. -- -- Subject to fusion -- -- Since 1.0.0 stdout :: MonadIO m => Consumer ByteString m () INLINE_RULE0(stdout, sinkHandle SIO.stdout) -- | @sinkHandle@ applied to @stderr@. -- -- Subject to fusion -- -- Since 1.0.0 stderr :: MonadIO m => Consumer ByteString m () INLINE_RULE0(stderr, sinkHandle SIO.stderr) -- | Apply a transformation to all values in a stream. -- -- Subject to fusion -- -- Since 1.0.0 map :: Monad m => (a -> b) -> Conduit a m b INLINE_RULE(map, f, CL.map f) -- | Apply a transformation to all elements in a chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 mapE :: (Monad m, Functor f) => (a -> b) -> Conduit (f a) m (f b) INLINE_RULE(mapE, f, CL.map (fmap f)) -- | Apply a monomorphic transformation to all elements in a chunked stream. -- -- Unlike @mapE@, this will work on types like @ByteString@ and @Text@ which -- are @MonoFunctor@ but not @Functor@. -- -- Subject to fusion -- -- Since 1.0.0 omapE :: (Monad m, MonoFunctor mono) => (Element mono -> Element mono) -> Conduit mono m mono INLINE_RULE(omapE, f, CL.map (omap f)) -- | Apply the function to each value in the stream, resulting in a foldable -- value (e.g., a list). Then yield each of the individual values in that -- foldable value separately. -- -- Generalizes concatMap, mapMaybe, and mapFoldable. -- -- Subject to fusion -- -- Since 1.0.0 concatMap, concatMapC :: (Monad m, MonoFoldable mono) => (a -> mono) -> Conduit a m (Element mono) concatMapC f = awaitForever (yieldMany . f) {-# INLINE concatMapC #-} STREAMING(concatMap, concatMapC, concatMapS, f) -- | Apply the function to each element in the chunked stream, resulting in a -- foldable value (e.g., a list). Then yield each of the individual values in -- that foldable value separately. -- -- Generalizes concatMap, mapMaybe, and mapFoldable. -- -- Subject to fusion -- -- Since 1.0.0 concatMapE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Conduit mono m w INLINE_RULE(concatMapE, f, CL.map (ofoldMap f)) -- | Stream up to n number of values downstream. -- -- Note that, if downstream terminates early, not all values will be consumed. -- If you want to force /exactly/ the given number of values to be consumed, -- see 'takeExactly'. -- -- Subject to fusion -- -- Since 1.0.0 take :: Monad m => Int -> Conduit a m a INLINE_RULE(take, n, CL.isolate n) -- | Stream up to n number of elements downstream in a chunked stream. -- -- Note that, if downstream terminates early, not all values will be consumed. -- If you want to force /exactly/ the given number of values to be consumed, -- see 'takeExactlyE'. -- -- Since 1.0.0 takeE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> Conduit seq m seq takeE = loop where loop i = if i <= 0 then return () else await >>= maybe (return ()) (go i) go i sq = do unless (onull x) $ yield x unless (onull y) $ leftover y loop i' where (x, y) = Seq.splitAt i sq i' = i - fromIntegral (olength x) {-# INLINEABLE takeE #-} -- | Stream all values downstream that match the given predicate. -- -- Same caveats regarding downstream termination apply as with 'take'. -- -- Since 1.0.0 takeWhile :: Monad m => (a -> Bool) -> Conduit a m a takeWhile f = loop where loop = await >>= maybe (return ()) go go x = if f x then yield x >> loop else leftover x {-# INLINE takeWhile #-} -- | Stream all elements downstream that match the given predicate in a chunked stream. -- -- Same caveats regarding downstream termination apply as with 'takeE'. -- -- Since 1.0.0 takeWhileE :: (Monad m, Seq.IsSequence seq) => (Element seq -> Bool) -> Conduit seq m seq takeWhileE f = loop where loop = await >>= maybe (return ()) go go sq = do unless (onull x) $ yield x if onull y then loop else leftover y where (x, y) = Seq.span f sq {-# INLINE takeWhileE #-} -- | Consume precisely the given number of values and feed them downstream. -- -- This function is in contrast to 'take', which will only consume up to the -- given number of values, and will terminate early if downstream terminates -- early. This function will discard any additional values in the stream if -- they are unconsumed. -- -- Note that this function takes a downstream @ConduitM@ as a parameter, as -- opposed to working with normal fusion. For more information, see -- , the section -- titled \"pipes and conduit: isolate\". -- -- Since 1.0.0 takeExactly :: Monad m => Int -> ConduitM a b m r -> ConduitM a b m r takeExactly count inner = take count =$= do r <- inner CL.sinkNull return r -- | Same as 'takeExactly', but for chunked streams. -- -- Since 1.0.0 takeExactlyE :: (Monad m, Seq.IsSequence a) => Seq.Index a -> ConduitM a b m r -> ConduitM a b m r takeExactlyE count inner = takeE count =$= do r <- inner CL.sinkNull return r {-# INLINE takeExactlyE #-} -- | Flatten out a stream by yielding the values contained in an incoming -- @MonoFoldable@ as individually yielded values. -- -- Subject to fusion -- -- Since 1.0.0 concat, concatC :: (Monad m, MonoFoldable mono) => Conduit mono m (Element mono) concatC = awaitForever yieldMany STREAMING0(concat, concatC, concatS) -- | Keep only values in the stream passing a given predicate. -- -- Subject to fusion -- -- Since 1.0.0 filter :: Monad m => (a -> Bool) -> Conduit a m a INLINE_RULE(filter, f, CL.filter f) -- | Keep only elements in the chunked stream passing a given predicate. -- -- Subject to fusion -- -- Since 1.0.0 filterE :: (Seq.IsSequence seq, Monad m) => (Element seq -> Bool) -> Conduit seq m seq INLINE_RULE(filterE, f, CL.map (Seq.filter f)) -- | Map values as long as the result is @Just@. -- -- Since 1.0.0 mapWhile :: Monad m => (a -> Maybe b) -> Conduit a m b mapWhile f = loop where loop = await >>= maybe (return ()) go go x = case f x of Just y -> yield y >> loop Nothing -> leftover x {-# INLINE mapWhile #-} -- | Break up a stream of values into vectors of size n. The final vector may -- be smaller than n if the total number of values is not a strict multiple of -- n. No empty vectors will be yielded. -- -- Since 1.0.0 conduitVector :: (MonadBase base m, V.Vector v a, PrimMonad base) => Int -- ^ maximum allowed size -> Conduit a m (v a) conduitVector size = loop where loop = do v <- sinkVectorN size unless (V.null v) $ do yield v loop {-# INLINE conduitVector #-} -- | Analog of 'Prelude.scanl' for lists. -- -- Subject to fusion -- -- Since 1.0.6 scanl, scanlC :: Monad m => (a -> b -> a) -> a -> Conduit b m a scanlC f = loop where loop seed = await >>= maybe (yield seed) go where go b = do let seed' = f seed b seed' `seq` yield seed loop seed' STREAMING(scanl, scanlC, scanlS, f x) -- | 'mapWhile' with a break condition dependent on a strict accumulator. -- Equivalently, 'CL.mapAccum' as long as the result is @Right@. Instead of -- producing a leftover, the breaking input determines the resulting -- accumulator via @Left@. -- -- Subject to fusion mapAccumWhile, mapAccumWhileC :: Monad m => (a -> s -> Either s (s, b)) -> s -> ConduitM a b m s mapAccumWhileC f = loop where loop !s = await >>= maybe (return s) go where go a = either (return $!) (\(s', b) -> yield b >> loop s') $ f a s {-# INLINE mapAccumWhileC #-} STREAMING(mapAccumWhile, mapAccumWhileC, mapAccumWhileS, f s) -- | 'concatMap' with an accumulator. -- -- Subject to fusion -- -- Since 1.0.0 concatMapAccum :: Monad m => (a -> accum -> (accum, [b])) -> accum -> Conduit a m b INLINE_RULE0(concatMapAccum, CL.concatMapAccum) -- | Insert the given value between each two values in the stream. -- -- Subject to fusion -- -- Since 1.0.0 intersperse, intersperseC :: Monad m => a -> Conduit a m a intersperseC x = await >>= omapM_ go where go y = yield y >> concatMap (\z -> [x, z]) STREAMING(intersperse, intersperseC, intersperseS, x) -- | Sliding window of values -- 1,2,3,4,5 with window size 2 gives -- [1,2],[2,3],[3,4],[4,5] -- -- Best used with structures that support O(1) snoc. -- -- Subject to fusion -- -- Since 1.0.0 slidingWindow, slidingWindowC :: (Monad m, Seq.IsSequence seq, Element seq ~ a) => Int -> Conduit a m seq slidingWindowC sz = go (max 1 sz) mempty where goContinue st = await >>= maybe (return ()) (\x -> do let st' = Seq.snoc st x yield st' >> goContinue (Seq.unsafeTail st') ) go 0 st = yield st >> goContinue (Seq.unsafeTail st) go !n st = CL.head >>= \m -> case m of Nothing -> yield st Just x -> go (n-1) (Seq.snoc st x) STREAMING(slidingWindow, slidingWindowC, slidingWindowS, sz) -- | Split input into chunk of size 'chunkSize' -- -- The last element may be smaller than the 'chunkSize' (see also -- 'chunksOfExactlyE' which will not yield this last element) -- -- @since 1.1.2 chunksOfE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> Conduit seq m seq chunksOfE chunkSize = chunksOfExactlyE chunkSize >> (await >>= maybe (return ()) yield) -- | Split input into chunk of size 'chunkSize' -- -- If the input does not split into chunks exactly, the remainder will be -- leftover (see also 'chunksOfE') -- -- @since 1.1.2 chunksOfExactlyE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> Conduit seq m seq chunksOfExactlyE chunkSize = await >>= maybe (return ()) start where start b | onull b = chunksOfE chunkSize | Seq.lengthIndex b < chunkSize = continue (Seq.lengthIndex b) [b] | otherwise = let (first,rest) = Seq.splitAt chunkSize b in yield first >> start rest continue !sofar bs = do next <- await case next of Nothing -> leftover (mconcat $ Prelude.reverse bs) Just next' -> let !sofar' = Seq.lengthIndex next' + sofar bs' = next':bs in if sofar' < chunkSize then continue sofar' bs' else start (mconcat (Prelude.reverse bs')) codeWith :: Monad m => Int -> (ByteString -> Either e ByteString) -> Conduit ByteString m ByteString codeWith size f = loop where loop = await >>= maybe (return ()) push loopWith bs | S.null bs = loop | otherwise = await >>= maybe (finish bs) (pushWith bs) finish bs = case f bs of Left _ -> leftover bs Right x -> yield x push bs = do let (x, y) = S.splitAt (len - (len `mod` size)) bs if S.null x then loopWith y else do case f x of Left _ -> leftover bs Right x' -> yield x' >> loopWith y where len = olength bs pushWith bs1 bs2 | S.length bs1 + S.length bs2 < size = loopWith (S.append bs1 bs2) pushWith bs1 bs2 = assertion1 $ assertion2 $ assertion3 $ case f bs1' of Left _ -> leftover bs2 >> leftover bs1 Right toYield -> yield toYield >> push y where m = S.length bs1 `mod` size (x, y) = S.splitAt (size - m) bs2 bs1' = mappend bs1 x assertion1 = assert $ olength bs1 < size assertion2 = assert $ olength bs1' `mod` size == 0 assertion3 = assert $ olength bs1' > 0 -- | Apply base64-encoding to the stream. -- -- Since 1.0.0 encodeBase64 :: Monad m => Conduit ByteString m ByteString encodeBase64 = codeWith 3 (Right . B64.encode) {-# INLINE encodeBase64 #-} -- | Apply base64-decoding to the stream. Will stop decoding on the first -- invalid chunk. -- -- Since 1.0.0 decodeBase64 :: Monad m => Conduit ByteString m ByteString decodeBase64 = codeWith 4 B64.decode {-# INLINE decodeBase64 #-} -- | Apply URL-encoding to the stream. -- -- Since 1.0.0 encodeBase64URL :: Monad m => Conduit ByteString m ByteString encodeBase64URL = codeWith 3 (Right . B64U.encode) {-# INLINE encodeBase64URL #-} -- | Apply lenient base64URL-decoding to the stream. Will stop decoding on the -- first invalid chunk. -- -- Since 1.0.0 decodeBase64URL :: Monad m => Conduit ByteString m ByteString decodeBase64URL = codeWith 4 B64U.decode {-# INLINE decodeBase64URL #-} -- | Apply base16-encoding to the stream. -- -- Subject to fusion -- -- Since 1.0.0 encodeBase16 :: Monad m => Conduit ByteString m ByteString INLINE_RULE0(encodeBase16, map B16.encode) -- | Apply base16-decoding to the stream. Will stop decoding on the first -- invalid chunk. -- -- Since 1.0.0 decodeBase16 :: Monad m => Conduit ByteString m ByteString decodeBase16 = codeWith 2 decode' where decode' x | onull z = Right y | otherwise = Left () where (y, z) = B16.decode x {-# INLINE decodeBase16 #-} -- | Apply a monadic transformation to all values in a stream. -- -- If you do not need the transformed values, and instead just want the monadic -- side-effects of running the action, see 'mapM_'. -- -- Subject to fusion -- -- Since 1.0.0 mapM :: Monad m => (a -> m b) -> Conduit a m b INLINE_RULE(mapM, f, CL.mapM f) -- | Apply a monadic transformation to all elements in a chunked stream. -- -- Subject to fusion -- -- Since 1.0.0 mapME :: (Monad m, Data.Traversable.Traversable f) => (a -> m b) -> Conduit (f a) m (f b) INLINE_RULE(mapME, f, CL.mapM (Data.Traversable.mapM f)) -- | Apply a monadic monomorphic transformation to all elements in a chunked stream. -- -- Unlike @mapME@, this will work on types like @ByteString@ and @Text@ which -- are @MonoFunctor@ but not @Functor@. -- -- Subject to fusion -- -- Since 1.0.0 omapME :: (Monad m, MonoTraversable mono) => (Element mono -> m (Element mono)) -> Conduit mono m mono INLINE_RULE(omapME, f, CL.mapM (omapM f)) -- | Apply the monadic function to each value in the stream, resulting in a -- foldable value (e.g., a list). Then yield each of the individual values in -- that foldable value separately. -- -- Generalizes concatMapM, mapMaybeM, and mapFoldableM. -- -- Subject to fusion -- -- Since 1.0.0 concatMapM, concatMapMC :: (Monad m, MonoFoldable mono) => (a -> m mono) -> Conduit a m (Element mono) concatMapMC f = awaitForever (lift . f >=> yieldMany) STREAMING(concatMapM, concatMapMC, concatMapMS, f) -- | Keep only values in the stream passing a given monadic predicate. -- -- Subject to fusion -- -- Since 1.0.0 filterM, filterMC :: Monad m => (a -> m Bool) -> Conduit a m a filterMC f = awaitForever go where go x = do b <- lift $ f x when b $ yield x STREAMING(filterM, filterMC, filterMS, f) -- | Keep only elements in the chunked stream passing a given monadic predicate. -- -- Subject to fusion -- -- Since 1.0.0 filterME :: (Monad m, Seq.IsSequence seq) => (Element seq -> m Bool) -> Conduit seq m seq INLINE_RULE(filterME, f, CL.mapM (Seq.filterM f)) -- | Apply a monadic action on all values in a stream. -- -- This @Conduit@ can be used to perform a monadic side-effect for every -- value, whilst passing the value through the @Conduit@ as-is. -- -- > iterM f = mapM (\a -> f a >>= \() -> return a) -- -- Subject to fusion -- -- Since 1.0.0 iterM :: Monad m => (a -> m ()) -> Conduit a m a INLINE_RULE(iterM, f, CL.iterM f) -- | Analog of 'Prelude.scanl' for lists, monadic. -- -- Subject to fusion -- -- Since 1.0.6 scanlM, scanlMC :: Monad m => (a -> b -> m a) -> a -> Conduit b m a scanlMC f = loop where loop seed = await >>= maybe (yield seed) go where go b = do seed' <- lift $ f seed b seed' `seq` yield seed loop seed' STREAMING(scanlM, scanlMC, scanlMS, f x) -- | Monadic `mapAccumWhile`. -- -- Subject to fusion mapAccumWhileM, mapAccumWhileMC :: Monad m => (a -> s -> m (Either s (s, b))) -> s -> ConduitM a b m s mapAccumWhileMC f = loop where loop !s = await >>= maybe (return s) go where go a = lift (f a s) >>= either (return $!) (\(s', b) -> yield b >> loop s') {-# INLINE mapAccumWhileMC #-} STREAMING(mapAccumWhileM, mapAccumWhileMC, mapAccumWhileMS, f s) -- | 'concatMapM' with an accumulator. -- -- Subject to fusion -- -- Since 1.0.0 concatMapAccumM :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> Conduit a m b INLINE_RULE(concatMapAccumM, f x, CL.concatMapAccumM f x) -- | Encode a stream of text as UTF8. -- -- Subject to fusion -- -- Since 1.0.0 encodeUtf8 :: (Monad m, DTE.Utf8 text binary) => Conduit text m binary INLINE_RULE0(encodeUtf8, map DTE.encodeUtf8) -- | Decode a stream of binary data as UTF8. -- -- Since 1.0.0 decodeUtf8 :: MonadThrow m => Conduit ByteString m Text decodeUtf8 = CT.decode CT.utf8 -- | Decode a stream of binary data as UTF8, replacing any invalid bytes with -- the Unicode replacement character. -- -- Since 1.0.0 decodeUtf8Lenient :: MonadThrow m => Conduit ByteString m Text decodeUtf8Lenient = CT.decodeUtf8Lenient -- | Stream in the entirety of a single line. -- -- Like @takeExactly@, this will consume the entirety of the line regardless of -- the behavior of the inner Conduit. -- -- Since 1.0.0 line :: (Monad m, Seq.IsSequence seq, Element seq ~ Char) => ConduitM seq o m r -> ConduitM seq o m r line = takeExactlyUntilE (== '\n') {-# INLINE line #-} -- | Same as 'line', but operates on ASCII/binary data. -- -- Since 1.0.0 lineAscii :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8) => ConduitM seq o m r -> ConduitM seq o m r lineAscii = takeExactlyUntilE (== 10) {-# INLINE lineAscii #-} -- | Stream in the chunked input until an element matches a predicate. -- -- Like @takeExactly@, this will consume the entirety of the prefix -- regardless of the behavior of the inner Conduit. takeExactlyUntilE :: (Monad m, Seq.IsSequence seq) => (Element seq -> Bool) -> ConduitM seq o m r -> ConduitM seq o m r takeExactlyUntilE f inner = loop =$= do x <- inner sinkNull return x where loop = await >>= omapM_ go go t = if onull y then yield x >> loop else do unless (onull x) $ yield x let y' = Seq.drop 1 y unless (onull y') $ leftover y' where (x, y) = Seq.break f t {-# INLINE takeExactlyUntilE #-} -- | Insert a newline character after each incoming chunk of data. -- -- Subject to fusion -- -- Since 1.0.0 unlines :: (Monad m, Seq.IsSequence seq, Element seq ~ Char) => Conduit seq m seq #if __GLASGOW_HASKELL__ >= 706 INLINE_RULE0(unlines, concatMap (:[Seq.singleton '\n'])) #else unlines = concatMap (:[Seq.singleton '\n']) {-# INLINE unlines #-} #endif -- | Same as 'unlines', but operates on ASCII/binary data. -- -- Subject to fusion -- -- Since 1.0.0 unlinesAscii :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8) => Conduit seq m seq #if __GLASGOW_HASKELL__ >= 706 INLINE_RULE0(unlinesAscii, concatMap (:[Seq.singleton 10])) #else unlinesAscii = concatMap (:[Seq.singleton 10]) #endif -- | Split a stream of arbitrarily-chunked data, based on a predicate -- on elements. Elements that satisfy the predicate will cause chunks -- to be split, and aren't included in these output chunks. Note -- that, if you have unknown or untrusted input, this function is -- /unsafe/, since it would allow an attacker to form chunks of -- massive length and exhaust memory. splitOnUnboundedE, splitOnUnboundedEC :: (Monad m, Seq.IsSequence seq) => (Element seq -> Bool) -> Conduit seq m seq splitOnUnboundedEC f = start where start = await >>= maybe (return ()) (loop id) loop bldr t = if onull y then do mt <- await case mt of Nothing -> let finalChunk = mconcat $ bldr [t] in unless (onull finalChunk) $ yield finalChunk Just t' -> loop (bldr . (t:)) t' else yield (mconcat $ bldr [x]) >> loop id (Seq.drop 1 y) where (x, y) = Seq.break f t STREAMING(splitOnUnboundedE, splitOnUnboundedEC, splitOnUnboundedES, f) -- | Convert a stream of arbitrarily-chunked textual data into a stream of data -- where each chunk represents a single line. Note that, if you have -- unknown or untrusted input, this function is /unsafe/, since it would allow an -- attacker to form lines of massive length and exhaust memory. -- -- Subject to fusion -- -- Since 1.0.0 linesUnbounded :: (Monad m, Seq.IsSequence seq, Element seq ~ Char) => Conduit seq m seq #if __GLASGOW_HASKELL__ >= 706 INLINE_RULE0(linesUnbounded, splitOnUnboundedE (== '\n')) #else linesUnbounded = splitOnUnboundedE (== '\n') #endif -- | Same as 'linesUnbounded', but for ASCII/binary data. -- -- Subject to fusion -- -- Since 1.0.0 linesUnboundedAscii :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8) => Conduit seq m seq #if __GLASGOW_HASKELL__ >= 706 INLINE_RULE0(linesUnboundedAscii, splitOnUnboundedE (== 10)) #else linesUnboundedAscii = splitOnUnboundedE (== 10) #endif -- | Generally speaking, yielding values from inside a Conduit requires -- some allocation for constructors. This can introduce an overhead, -- similar to the overhead needed to represent a list of values instead of -- a vector. This overhead is even more severe when talking about unboxed -- values. -- -- This combinator allows you to overcome this overhead, and efficiently -- fill up vectors. It takes two parameters. The first is the size of each -- mutable vector to be allocated. The second is a function. The function -- takes an argument which will yield the next value into a mutable -- vector. -- -- Under the surface, this function uses a number of tricks to get high -- performance. For more information on both usage and implementation, -- please see: -- -- -- Since 1.0.0 vectorBuilder :: (PrimMonad base, MonadBase base m, V.Vector v e, MonadBase base n) => Int -- ^ size -> ((e -> n ()) -> Sink i m r) -> ConduitM i (v e) m r vectorBuilder size inner = do ref <- liftBase $ do mv <- VM.new size newMutVar $! S 0 mv id res <- onAwait (yieldS ref) (inner (liftBase . addE ref)) vs <- liftBase $ do S idx mv front <- readMutVar ref end <- if idx == 0 then return [] else do v <- V.unsafeFreeze mv return [V.unsafeTake idx v] return $ front end Prelude.mapM_ yield vs return res {-# INLINE vectorBuilder #-} data S s v e = S {-# UNPACK #-} !Int -- index !(V.Mutable v s e) ([v e] -> [v e]) onAwait :: Monad m => ConduitM i o m () -> Sink i m r -> ConduitM i o m r onAwait (ConduitM callback) (ConduitM sink0) = ConduitM $ \rest -> let go (Done r) = rest r go (HaveOutput _ _ o) = absurd o go (NeedInput f g) = callback $ \() -> NeedInput (go . f) (go . g) go (PipeM mp) = PipeM (liftM go mp) go (Leftover f i) = Leftover (go f) i in go (sink0 Done) {-# INLINE onAwait #-} yieldS :: (PrimMonad base, MonadBase base m) => MutVar (PrimState base) (S (PrimState base) v e) -> Producer m (v e) yieldS ref = do S idx mv front <- liftBase $ readMutVar ref Prelude.mapM_ yield (front []) liftBase $ writeMutVar ref $! S idx mv id {-# INLINE yieldS #-} addE :: (PrimMonad m, V.Vector v e) => MutVar (PrimState m) (S (PrimState m) v e) -> e -> m () addE ref e = do S idx mv front <- readMutVar ref VM.write mv idx e let idx' = succ idx size = VM.length mv if idx' >= size then do v <- V.unsafeFreeze mv let front' = front . (v:) mv' <- VM.new size writeMutVar ref $! S 0 mv' front' else writeMutVar ref $! S idx' mv front {-# INLINE addE #-} -- | Consume a source with a strict accumulator, in a way piecewise defined by -- a controlling stream. The latter will be evaluated until it terminates. -- -- >>> let f a s = liftM (:s) $ mapC (*a) =$ CL.take a -- >>> reverse $ runIdentity $ yieldMany [0..3] $$ mapAccumS f [] (yieldMany [1..]) -- [[],[1],[4,6],[12,15,18]] :: [[Int]] mapAccumS :: Monad m => (a -> s -> Sink b m s) -> s -> Source m b -> Sink a m s mapAccumS f s xs = do (zs, u) <- loop (newResumableSource xs, s) lift (closeResumableSource zs) >> return u where loop r@(ys, !t) = await >>= maybe (return r) go where go a = lift (ys $$++ f a t) >>= loop {-# INLINE mapAccumS #-} -- | Run a consuming conduit repeatedly, only stopping when there is no more -- data available from upstream. -- -- Since 1.0.0 peekForever :: Monad m => ConduitM i o m () -> ConduitM i o m () peekForever inner = loop where loop = do mx <- peek case mx of Nothing -> return () Just _ -> inner >> loop -- | Run a consuming conduit repeatedly, only stopping when there is no more -- data available from upstream. -- -- In contrast to 'peekForever', this function will ignore empty -- chunks of data. So for example, if a stream of data contains an -- empty @ByteString@, it is still treated as empty, and the consuming -- function is not called. -- -- @since 1.0.6 peekForeverE :: (Monad m, MonoFoldable i) => ConduitM i o m () -> ConduitM i o m () peekForeverE inner = loop where loop = do mx <- peekE case mx of Nothing -> return () Just _ -> inner >> loop conduit-combinators-1.1.2/src/Data/Conduit/Combinators/Internal.hs0000644000000000000000000000617613211200065023321 0ustar0000000000000000{-# LANGUAGE RankNTypes #-} {-# LANGUAGE CPP #-} -- | Internal helper functions, usually used for rewrite rules. module Data.Conduit.Combinators.Internal ( initReplicate , initReplicateConnect , initRepeat , initRepeatConnect ) where import Data.Conduit import Data.Conduit.Internal (ConduitM (..), Pipe (..), injectLeftovers) import Data.Void (absurd) import Control.Monad.Trans.Class (lift) import Control.Monad (replicateM_, forever) import Data.Conduit.Combinators.Stream import Data.Conduit.Internal.Fusion -- Defines INLINE_RULE0, INLINE_RULE, STREAMING0, and STREAMING. #include "fusion-macros.h" -- | Acquire the seed value and perform the given action with it n times, -- yielding each result. -- -- Subject to fusion -- -- Since 0.2.1 initReplicate, initReplicateC :: Monad m => m seed -> (seed -> m a) -> Int -> Producer m a initReplicateC mseed f cnt = do seed <- lift mseed replicateM_ cnt (lift (f seed) >>= yield) {-# INLINE [1] initReplicateC #-} STREAMING(initReplicate, initReplicateC, initReplicateS, mseed f cnt) -- | Optimized version of initReplicate for the special case of connecting with -- a @Sink@. -- -- Since 0.2.1 initReplicateConnect :: Monad m => m seed -> (seed -> m a) -> Int -> Sink a m b -> m b initReplicateConnect mseed f cnt0 (ConduitM sink0) = do seed <- mseed let loop cnt sink | cnt <= 0 = finish sink loop _ (Done r) = return r loop cnt (NeedInput p _) = f seed >>= loop (pred cnt) . p loop _ (HaveOutput _ _ o) = absurd o loop cnt (PipeM mp) = mp >>= loop cnt loop _ (Leftover _ i) = absurd i loop cnt0 (injectLeftovers $ sink0 Done) where finish (Done r) = return r finish (HaveOutput _ _ o) = absurd o finish (NeedInput _ p) = finish (p ()) finish (PipeM mp) = mp >>= finish finish (Leftover _ i) = absurd i {-# RULES "initReplicateConnect" forall mseed f cnt sink. initReplicate mseed f cnt $$ sink = initReplicateConnect mseed f cnt sink #-} -- | Acquire the seed value and perform the given action with it forever, -- yielding each result. -- -- Subject to fusion -- -- Since 0.2.1 initRepeat, initRepeatC :: Monad m => m seed -> (seed -> m a) -> Producer m a initRepeatC mseed f = do seed <- lift mseed forever $ lift (f seed) >>= yield {-# INLINE [1] initRepeatC #-} STREAMING(initRepeat, initRepeatC, initRepeatS, mseed f) -- | Optimized version of initRepeat for the special case of connecting with -- a @Sink@. -- -- Since 0.2.1 initRepeatConnect :: Monad m => m seed -> (seed -> m a) -> Sink a m b -> m b initRepeatConnect mseed f (ConduitM sink0) = do seed <- mseed let loop (Done r) = return r loop (NeedInput p _) = f seed >>= loop . p loop (HaveOutput _ _ o) = absurd o loop (PipeM mp) = mp >>= loop loop (Leftover _ i) = absurd i loop (injectLeftovers (sink0 Done)) {-# RULES "initRepeatConnect" forall mseed f sink. initRepeat mseed f $$ sink = initRepeatConnect mseed f sink #-} conduit-combinators-1.1.2/src/Data/Conduit/Combinators/Stream.hs0000644000000000000000000003463113211200065022775 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE TypeFamilies #-} -- | These are stream fusion versions of some of the functions in -- "Data.Conduit.Combinators". Many functions don't have stream -- versions here because instead they have @RULES@ which inline a -- definition that fuses. module Data.Conduit.Combinators.Stream ( yieldManyS , repeatMS , repeatWhileMS , foldl1S , allS , anyS , sinkLazyS , sinkVectorS , sinkVectorNS , sinkLazyBuilderS , lastS , lastES , findS , concatMapS , concatMapMS , concatS , scanlS , scanlMS , mapAccumWhileS , mapAccumWhileMS , intersperseS , slidingWindowS , filterMS , splitOnUnboundedES , initReplicateS , initRepeatS ) where -- BEGIN IMPORTS import Control.Monad (liftM) import Control.Monad.Base (MonadBase (liftBase)) import Control.Monad.Primitive (PrimMonad) import Data.Builder import Data.Conduit.Internal.Fusion import Data.Conduit.Internal.List.Stream (foldS) import Data.Maybe (isNothing, isJust) import Data.MonoTraversable #if ! MIN_VERSION_base(4,8,0) import Data.Monoid (Monoid (..)) #endif import qualified Data.NonNull as NonNull import qualified Data.Sequences as Seq import qualified Data.Vector.Generic as V import qualified Data.Vector.Generic.Mutable as VM import Prelude #if MIN_VERSION_mono_traversable(1,0,0) import Data.Sequences (LazySequence (..)) #else import Data.Sequences.Lazy #endif -- END IMPORTS yieldManyS :: (Monad m, MonoFoldable mono) => mono -> StreamProducer m (Element mono) yieldManyS mono _ = Stream (return . step) (return (otoList mono)) where step [] = Stop () step (x:xs) = Emit xs x {-# INLINE yieldManyS #-} repeatMS :: Monad m => m a -> StreamProducer m a repeatMS m _ = Stream step (return ()) where step _ = liftM (Emit ()) m {-# INLINE repeatMS #-} repeatWhileMS :: Monad m => m a -> (a -> Bool) -> StreamProducer m a repeatWhileMS m f _ = Stream step (return ()) where step _ = do x <- m return $ if f x then Emit () x else Stop () {-# INLINE repeatWhileMS #-} foldl1S :: Monad m => (a -> a -> a) -> StreamConsumer a m (Maybe a) foldl1S f (Stream step ms0) = Stream step' (liftM (Nothing, ) ms0) where step' (mprev, s) = do res <- step s return $ case res of Stop () -> Stop mprev Skip s' -> Skip (mprev, s') Emit s' a -> Skip (Just $ maybe a (`f` a) mprev, s') {-# INLINE foldl1S #-} allS :: Monad m => (a -> Bool) -> StreamConsumer a m Bool allS f = fmapS isNothing (findS (Prelude.not . f)) {-# INLINE allS #-} anyS :: Monad m => (a -> Bool) -> StreamConsumer a m Bool anyS f = fmapS isJust (findS f) {-# INLINE anyS #-} --TODO: use a definition like -- fmapS (fromChunks . ($ [])) <$> CL.fold (\front next -> front . (next:)) id sinkLazyS :: (Monad m, LazySequence lazy strict) => StreamConsumer strict m lazy sinkLazyS = fmapS (fromChunks . ($ [])) $ foldS (\front next -> front . (next:)) id {-# INLINE sinkLazyS #-} sinkVectorS :: (MonadBase base m, V.Vector v a, PrimMonad base) => StreamConsumer a m (v a) sinkVectorS (Stream step ms0) = do Stream step' $ do s0 <- ms0 mv0 <- liftBase $ VM.new initSize return (initSize, 0, mv0, s0) where initSize = 10 step' (maxSize, i, mv, s) = do res <- step s case res of Stop () -> liftM (Stop . V.slice 0 i) $ liftBase (V.unsafeFreeze mv) Skip s' -> return $ Skip (maxSize, i, mv, s') Emit s' x -> do liftBase $ VM.write mv i x let i' = i + 1 if i' >= maxSize then do let newMax = maxSize * 2 mv' <- liftBase $ VM.grow mv maxSize return $ Skip (newMax, i', mv', s') else return $ Skip (maxSize, i', mv, s') {-# INLINE sinkVectorS #-} sinkVectorNS :: (MonadBase base m, V.Vector v a, PrimMonad base) => Int -- ^ maximum allowed size -> StreamConsumer a m (v a) sinkVectorNS maxSize (Stream step ms0) = do Stream step' $ do s0 <- ms0 mv0 <- liftBase $ VM.new maxSize return (0, mv0, s0) where step' (i, mv, _) | i >= maxSize = liftM Stop $ liftBase $ V.unsafeFreeze mv step' (i, mv, s) = do res <- step s case res of Stop () -> liftM (Stop . V.slice 0 i) $ liftBase (V.unsafeFreeze mv) Skip s' -> return $ Skip (i, mv, s') Emit s' x -> do liftBase $ VM.write mv i x let i' = i + 1 return $ Skip (i', mv, s') {-# INLINE sinkVectorNS #-} sinkLazyBuilderS :: (Monad m, Monoid builder, ToBuilder a builder, Builder builder lazy) => StreamConsumer a m lazy sinkLazyBuilderS = fmapS builderToLazy (foldS combiner mempty) where combiner accum = mappend accum . toBuilder {-# INLINE sinkLazyBuilderS #-} lastS :: Monad m => StreamConsumer a m (Maybe a) lastS (Stream step ms0) = Stream step' (liftM (Nothing,) ms0) where step' (mlast, s) = do res <- step s return $ case res of Stop () -> Stop mlast Skip s' -> Skip (mlast, s') Emit s' x -> Skip (Just x, s') {-# INLINE lastS #-} lastES :: (Monad m, Seq.IsSequence seq) => StreamConsumer seq m (Maybe (Element seq)) lastES (Stream step ms0) = Stream step' (liftM (Nothing, ) ms0) where step' (mlast, s) = do res <- step s return $ case res of Stop () -> Stop (fmap NonNull.last mlast) Skip s' -> Skip (mlast, s') Emit s' (NonNull.fromNullable -> mlast'@(Just _)) -> Skip (mlast', s') Emit s' _ -> Skip (mlast, s') {-# INLINE lastES #-} findS :: Monad m => (a -> Bool) -> StreamConsumer a m (Maybe a) findS f (Stream step ms0) = Stream step' ms0 where step' s = do res <- step s return $ case res of Stop () -> Stop Nothing Skip s' -> Skip s' Emit s' x -> if f x then Stop (Just x) else Skip s' {-# INLINE findS #-} concatMapS :: (Monad m, MonoFoldable mono) => (a -> mono) -> StreamConduit a m (Element mono) concatMapS f (Stream step ms0) = Stream step' (liftM ([], ) ms0) where step' ([], s) = do res <- step s return $ case res of Stop () -> Stop () Skip s' -> Skip ([], s') Emit s' x -> Skip (otoList (f x), s') step' ((x:xs), s) = return (Emit (xs, s) x) {-# INLINE concatMapS #-} concatMapMS :: (Monad m, MonoFoldable mono) => (a -> m mono) -> StreamConduit a m (Element mono) concatMapMS f (Stream step ms0) = Stream step' (liftM ([], ) ms0) where step' ([], s) = do res <- step s case res of Stop () -> return $ Stop () Skip s' -> return $ Skip ([], s') Emit s' x -> do o <- f x return $ Skip (otoList o, s') step' ((x:xs), s) = return (Emit (xs, s) x) {-# INLINE concatMapMS #-} concatS :: (Monad m, MonoFoldable mono) => StreamConduit mono m (Element mono) concatS = concatMapS id {-# INLINE concatS #-} data ScanState a s = ScanEnded | ScanContinues a s scanlS :: Monad m => (a -> b -> a) -> a -> StreamConduit b m a scanlS f seed0 (Stream step ms0) = Stream step' (liftM (ScanContinues seed0) ms0) where step' ScanEnded = return $ Stop () step' (ScanContinues seed s) = do res <- step s return $ case res of Stop () -> Emit ScanEnded seed Skip s' -> Skip (ScanContinues seed s') Emit s' x -> Emit (ScanContinues seed' s') seed where !seed' = f seed x {-# INLINE scanlS #-} scanlMS :: Monad m => (a -> b -> m a) -> a -> StreamConduit b m a scanlMS f seed0 (Stream step ms0) = Stream step' (liftM (ScanContinues seed0) ms0) where step' ScanEnded = return $ Stop () step' (ScanContinues seed s) = do res <- step s case res of Stop () -> return $ Emit ScanEnded seed Skip s' -> return $ Skip (ScanContinues seed s') Emit s' x -> do !seed' <- f seed x return $ Emit (ScanContinues seed' s') seed {-# INLINE scanlMS #-} mapAccumWhileS :: Monad m => (a -> s -> Either s (s, b)) -> s -> StreamConduitM a b m s mapAccumWhileS f initial (Stream step ms0) = Stream step' (liftM (initial, ) ms0) where step' (!accum, s) = do res <- step s return $ case res of Stop () -> Stop accum Skip s' -> Skip (accum, s') Emit s' x -> case f x accum of Right (!accum', r) -> Emit (accum', s') r Left !accum' -> Stop accum' {-# INLINE mapAccumWhileS #-} mapAccumWhileMS :: Monad m => (a -> s -> m (Either s (s, b))) -> s -> StreamConduitM a b m s mapAccumWhileMS f initial (Stream step ms0) = Stream step' (liftM (initial, ) ms0) where step' (!accum, s) = do res <- step s case res of Stop () -> return $ Stop accum Skip s' -> return $ Skip (accum, s') Emit s' x -> do lr <- f x accum return $ case lr of Right (!accum', r) -> Emit (accum', s') r Left !accum' -> Stop accum' {-# INLINE mapAccumWhileMS #-} data IntersperseState a s = IFirstValue s | IGotValue s a | IEmitValue s a intersperseS :: Monad m => a -> StreamConduit a m a intersperseS sep (Stream step ms0) = Stream step' (liftM IFirstValue ms0) where step' (IFirstValue s) = do res <- step s return $ case res of Stop () -> Stop () Skip s' -> Skip (IFirstValue s') Emit s' x -> Emit (IGotValue s' x) x -- Emit the separator once we know it's not the end of the list. step' (IGotValue s x) = do res <- step s return $ case res of Stop () -> Stop () Skip s' -> Skip (IGotValue s' x) Emit s' x' -> Emit (IEmitValue s' x') sep -- We emitted a separator, now emit the value that comes after. step' (IEmitValue s x) = return $ Emit (IGotValue s x) x {-# INLINE intersperseS #-} data SlidingWindowState seq s = SWInitial Int seq s | SWSliding seq s | SWEarlyExit slidingWindowS :: (Monad m, Seq.IsSequence seq, Element seq ~ a) => Int -> StreamConduit a m seq slidingWindowS sz (Stream step ms0) = Stream step' (liftM (SWInitial (max 1 sz) mempty) ms0) where step' (SWInitial n st s) = do res <- step s return $ case res of Stop () -> Emit SWEarlyExit st Skip s' -> Skip (SWInitial n st s') Emit s' x -> if n == 1 then Emit (SWSliding (Seq.unsafeTail st') s') st' else Skip (SWInitial (n - 1) st' s') where st' = Seq.snoc st x -- After collecting the initial window, each upstream element -- causes an additional window to be yielded. step' (SWSliding st s) = do res <- step s return $ case res of Stop () -> Stop () Skip s' -> Skip (SWSliding st s') Emit s' x -> Emit (SWSliding (Seq.unsafeTail st') s') st' where st' = Seq.snoc st x step' SWEarlyExit = return $ Stop () {-# INLINE slidingWindowS #-} filterMS :: Monad m => (a -> m Bool) -> StreamConduit a m a filterMS f (Stream step ms0) = do Stream step' ms0 where step' s = do res <- step s case res of Stop () -> return $ Stop () Skip s' -> return $ Skip s' Emit s' x -> do r <- f x return $ if r then Emit s' x else Skip s' {-# INLINE filterMS #-} data SplitState seq s = SplitDone -- When no element of seq passes the predicate. This allows -- 'splitOnUnboundedES' to not run 'Seq.break' multiple times due -- to 'Skip's being sent by the upstream. | SplitNoSep seq s | SplitState seq s splitOnUnboundedES :: (Monad m, Seq.IsSequence seq) => (Element seq -> Bool) -> StreamConduit seq m seq splitOnUnboundedES f (Stream step ms0) = Stream step' (liftM (SplitState mempty) ms0) where step' SplitDone = return $ Stop () step' (SplitNoSep t s) = do res <- step s return $ case res of Stop () | not (onull t) -> Emit SplitDone t | otherwise -> Stop () Skip s' -> Skip (SplitNoSep t s') Emit s' t' -> Skip (SplitState (t `mappend` t') s') step' (SplitState t s) = do if onull y then do res <- step s return $ case res of Stop () | not (onull t) -> Emit SplitDone t | otherwise -> Stop () Skip s' -> Skip (SplitNoSep t s') Emit s' t' -> Skip (SplitState (t `mappend` t') s') else return $ Emit (SplitState (Seq.drop 1 y) s) x where (x, y) = Seq.break f t {-# INLINE splitOnUnboundedES #-} -- | Streaming versions of @Data.Conduit.Combinators.Internal.initReplicate@ initReplicateS :: Monad m => m seed -> (seed -> m a) -> Int -> StreamProducer m a initReplicateS mseed f cnt _ = Stream step (liftM (cnt, ) mseed) where step (ix, _) | ix <= 0 = return $ Stop () step (ix, seed) = do x <- f seed return $ Emit (ix - 1, seed) x {-# INLINE initReplicateS #-} -- | Streaming versions of @Data.Conduit.Combinators.Internal.initRepeat@ initRepeatS :: Monad m => m seed -> (seed -> m a) -> StreamProducer m a initRepeatS mseed f _ = Stream step mseed where step seed = do x <- f seed return $ Emit seed x {-# INLINE initRepeatS #-} -- | Utility function fmapS :: Monad m => (a -> b) -> StreamConduitM i o m a -> StreamConduitM i o m b fmapS f s inp = case s inp of Stream step ms0 -> Stream (fmap (liftM (fmap f)) step) ms0 {-# INLINE fmapS #-} conduit-combinators-1.1.2/src/Data/Conduit/Combinators/Unqualified.hs0000644000000000000000000011735313211222300024007 0ustar0000000000000000-- WARNING: This module is autogenerated {-# OPTIONS_HADDOCK not-home #-} {-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoMonomorphismRestriction #-} module Data.Conduit.Combinators.Unqualified ( -- ** Producers -- *** Pure yieldMany , unfoldC , enumFromToC , iterateC , repeatC , replicateC , sourceLazy -- *** Monadic , repeatMC , repeatWhileMC , replicateMC -- *** I\/O , CC.sourceFile , CC.sourceFileBS , CC.sourceHandle , CC.sourceIOHandle , stdinC -- *** Random numbers , sourceRandom , sourceRandomN , sourceRandomGen , sourceRandomNGen , sourceRandomWith , sourceRandomNWith , sourceRandomGenWith , sourceRandomNGenWith -- *** Filesystem , sourceDirectory , sourceDirectoryDeep -- ** Consumers -- *** Pure , dropC , dropCE , dropWhileC , dropWhileCE , foldC , foldCE , foldlC , foldlCE , foldMapC , foldMapCE , allC , allCE , anyC , anyCE , andC , andCE , orC , orCE , asumC , elemC , elemCE , notElemC , notElemCE , sinkLazy , sinkList , sinkVector , sinkVectorN , sinkBuilder , sinkLazyBuilder , sinkNull , awaitNonNull , headC , headDefC , headCE , peekC , peekCE , lastC , lastDefC , lastCE , lengthC , lengthCE , lengthIfC , lengthIfCE , maximumC , maximumCE , minimumC , minimumCE , nullC , nullCE , sumC , sumCE , productC , productCE , findC -- *** Monadic , mapM_C , mapM_CE , foldMC , foldMCE , foldMapMC , foldMapMCE -- *** I\/O , CC.sinkFile , CC.sinkFileBS , CC.sinkHandle , CC.sinkIOHandle , printC , stdoutC , stderrC -- ** Transformers -- *** Pure , mapC , mapCE , omapCE , concatMapC , concatMapCE , takeC , takeCE , takeWhileC , takeWhileCE , takeExactlyC , takeExactlyCE , concatC , filterC , filterCE , mapWhileC , conduitVector , scanlC , mapAccumWhileC , concatMapAccumC , intersperseC , slidingWindowC , chunksOfCE , chunksOfExactlyCE -- **** Binary base encoding , encodeBase64C , decodeBase64C , encodeBase64URLC , decodeBase64URLC , encodeBase16C , decodeBase16C -- *** Monadic , mapMC , mapMCE , omapMCE , concatMapMC , filterMC , filterMCE , iterMC , scanlMC , mapAccumWhileMC , concatMapAccumMC -- *** Textual , encodeUtf8C , decodeUtf8C , decodeUtf8LenientC , lineC , lineAsciiC , unlinesC , unlinesAsciiC , linesUnboundedC , linesUnboundedAsciiC -- ** Special , vectorBuilderC , CC.mapAccumS , CC.peekForever , CC.peekForeverE ) where -- BEGIN IMPORTS import qualified Data.Conduit.Combinators as CC -- BEGIN IMPORTS import Data.Builder import qualified Data.NonNull as NonNull import qualified Data.Traversable import Control.Monad.Base (MonadBase (..)) import Control.Monad.IO.Class (MonadIO (..)) import Control.Monad.Primitive (PrimMonad, PrimState) import Control.Monad.Trans.Resource (MonadResource, MonadThrow) import Data.Conduit import Data.Monoid (Monoid (..)) import Data.MonoTraversable import qualified Data.Sequences as Seq import qualified Data.Vector.Generic as V import Prelude (Bool (..), Eq (..), Int, Maybe (..), Monad (..), Num (..), Ord (..), Functor (..), Either (..), Enum, Show, Char, FilePath) import Data.Word (Word8) import qualified System.IO as SIO import Data.ByteString (ByteString) import Data.Text (Text) import qualified System.Random.MWC as MWC #if MIN_VERSION_mono_traversable(1,0,0) import qualified Data.Sequences as DTE import Data.Sequences (LazySequence (..)) #else import Data.Sequences.Lazy import qualified Data.Textual.Encoding as DTE #endif -- END IMPORTS -- | Yield each of the values contained by the given @MonoFoldable@. -- -- This will work on many data structures, including lists, @ByteString@s, and @Vector@s. -- -- Since 1.0.0 yieldMany :: (Monad m, MonoFoldable mono) => mono -> Producer m (Element mono) yieldMany = CC.yieldMany {-# INLINE yieldMany #-} -- | Generate a producer from a seed value. -- -- Since 1.0.0 unfoldC :: Monad m => (b -> Maybe (a, b)) -> b -> Producer m a unfoldC = CC.unfold {-# INLINE unfoldC #-} -- | Enumerate from a value to a final value, inclusive, via 'succ'. -- -- This is generally more efficient than using @Prelude@\'s @enumFromTo@ and -- combining with @sourceList@ since this avoids any intermediate data -- structures. -- -- Since 1.0.0 enumFromToC :: (Monad m, Enum a, Ord a) => a -> a -> Producer m a enumFromToC = CC.enumFromTo {-# INLINE enumFromToC #-} -- | Produces an infinite stream of repeated applications of f to x. -- -- Since 1.0.0 iterateC :: Monad m => (a -> a) -> a -> Producer m a iterateC = CC.iterate {-# INLINE iterateC #-} -- | Produce an infinite stream consisting entirely of the given value. -- -- Since 1.0.0 repeatC :: Monad m => a -> Producer m a repeatC = CC.repeat {-# INLINE repeatC #-} -- | Produce a finite stream consisting of n copies of the given value. -- -- Since 1.0.0 replicateC :: Monad m => Int -> a -> Producer m a replicateC = CC.replicate {-# INLINE replicateC #-} -- | Generate a producer by yielding each of the strict chunks in a @LazySequence@. -- -- For more information, see 'toChunks'. -- -- Since 1.0.0 sourceLazy :: (Monad m, LazySequence lazy strict) => lazy -> Producer m strict sourceLazy = CC.sourceLazy {-# INLINE sourceLazy #-} -- | Repeatedly run the given action and yield all values it produces. -- -- Since 1.0.0 repeatMC :: Monad m => m a -> Producer m a repeatMC = CC.repeatM {-# INLINE repeatMC #-} -- | Repeatedly run the given action and yield all values it produces, until -- the provided predicate returns @False@. -- -- Since 1.0.0 repeatWhileMC :: Monad m => m a -> (a -> Bool) -> Producer m a repeatWhileMC = CC.repeatWhileM {-# INLINE repeatWhileMC #-} -- | Perform the given action n times, yielding each result. -- -- Since 1.0.0 replicateMC :: Monad m => Int -> m a -> Producer m a replicateMC = CC.replicateM {-# INLINE replicateMC #-} -- | @sourceHandle@ applied to @stdin@. -- -- Since 1.0.0 stdinC :: MonadIO m => Producer m ByteString stdinC = CC.stdin {-# INLINE stdinC #-} -- | Create an infinite stream of random values, seeding from the system random -- number. -- -- Since 1.0.0 sourceRandom :: (MWC.Variate a, MonadIO m) => Producer m a sourceRandom = CC.sourceRandom {-# INLINE sourceRandom #-} -- | Create a stream of random values of length n, seeding from the system -- random number. -- -- Since 1.0.0 sourceRandomN :: (MWC.Variate a, MonadIO m) => Int -- ^ count -> Producer m a sourceRandomN = CC.sourceRandomN {-# INLINE sourceRandomN #-} -- | Create an infinite stream of random values, using the given random number -- generator. -- -- Since 1.0.0 sourceRandomGen :: (MWC.Variate a, MonadBase base m, PrimMonad base) => MWC.Gen (PrimState base) -> Producer m a sourceRandomGen = CC.sourceRandomGen {-# INLINE sourceRandomGen #-} -- | Create a stream of random values of length n, seeding from the system -- random number. -- -- Since 1.0.0 sourceRandomNGen :: (MWC.Variate a, MonadBase base m, PrimMonad base) => MWC.Gen (PrimState base) -> Int -- ^ count -> Producer m a sourceRandomNGen = CC.sourceRandomNGen {-# INLINE sourceRandomNGen #-} -- | Create an infinite stream of random values from an arbitrary distribution, -- seeding from the system random number. -- -- Subject to fusion -- -- Since 1.0.3 sourceRandomWith :: (MWC.Variate a, MonadIO m) => (MWC.GenIO -> SIO.IO a) -> Producer m a sourceRandomWith = CC.sourceRandomWith {-# INLINE sourceRandomWith #-} -- | Create a stream of random values of length n from an arbitrary -- distribution, seeding from the system random number. -- -- Subject to fusion -- -- Since 1.0.3 sourceRandomNWith :: (MWC.Variate a, MonadIO m) => Int -- ^ count -> (MWC.GenIO -> SIO.IO a) -> Producer m a sourceRandomNWith = CC.sourceRandomNWith {-# INLINE sourceRandomNWith #-} -- | Create an infinite stream of random values from an arbitrary distribution, -- using the given random number generator. -- -- Subject to fusion -- -- Since 1.0.3 sourceRandomGenWith :: (MWC.Variate a, MonadBase base m, PrimMonad base) => MWC.Gen (PrimState base) -> (MWC.Gen (PrimState base) -> base a) -> Producer m a sourceRandomGenWith = CC.sourceRandomGenWith {-# INLINE sourceRandomGenWith #-} -- | Create a stream of random values of length n from an arbitrary -- distribution, seeding from the system random number. -- -- Subject to fusion -- -- Since 1.0.3 sourceRandomNGenWith :: (MWC.Variate a, MonadBase base m, PrimMonad base) => MWC.Gen (PrimState base) -> Int -- ^ count -> (MWC.Gen (PrimState base) -> base a) -> Producer m a sourceRandomNGenWith= CC.sourceRandomNGenWith {-# INLINE sourceRandomNGenWith #-} -- | Stream the contents of the given directory, without traversing deeply. -- -- This function will return /all/ of the contents of the directory, whether -- they be files, directories, etc. -- -- Note that the generated filepaths will be the complete path, not just the -- filename. In other words, if you have a directory @foo@ containing files -- @bar@ and @baz@, and you use @sourceDirectory@ on @foo@, the results will be -- @foo/bar@ and @foo/baz@. -- -- Since 1.0.0 sourceDirectory :: MonadResource m => FilePath -> Producer m FilePath sourceDirectory = CC.sourceDirectory {-# INLINE sourceDirectory #-} -- | Deeply stream the contents of the given directory. -- -- This works the same as @sourceDirectory@, but will not return directories at -- all. This function also takes an extra parameter to indicate whether -- symlinks will be followed. -- -- Since 1.0.0 sourceDirectoryDeep :: MonadResource m => Bool -- ^ Follow directory symlinks -> FilePath -- ^ Root directory -> Producer m FilePath sourceDirectoryDeep = CC.sourceDirectoryDeep {-# INLINE sourceDirectoryDeep #-} -- | Ignore a certain number of values in the stream. -- -- Since 1.0.0 dropC :: Monad m => Int -> Consumer a m () dropC = CC.drop {-# INLINE dropC #-} -- | Drop a certain number of elements from a chunked stream. -- -- Since 1.0.0 dropCE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> Consumer seq m () dropCE = CC.dropE {-# INLINE dropCE #-} -- | Drop all values which match the given predicate. -- -- Since 1.0.0 dropWhileC :: Monad m => (a -> Bool) -> Consumer a m () dropWhileC = CC.dropWhile {-# INLINE dropWhileC #-} -- | Drop all elements in the chunked stream which match the given predicate. -- -- Since 1.0.0 dropWhileCE :: (Monad m, Seq.IsSequence seq) => (Element seq -> Bool) -> Consumer seq m () dropWhileCE = CC.dropWhileE {-# INLINE dropWhileCE #-} -- | Monoidally combine all values in the stream. -- -- Since 1.0.0 foldC :: (Monad m, Monoid a) => Consumer a m a foldC = CC.fold {-# INLINE foldC #-} -- | Monoidally combine all elements in the chunked stream. -- -- Since 1.0.0 foldCE :: (Monad m, MonoFoldable mono, Monoid (Element mono)) => Consumer mono m (Element mono) foldCE = CC.foldE {-# INLINE foldCE #-} -- | A strict left fold. -- -- Since 1.0.0 foldlC :: Monad m => (a -> b -> a) -> a -> Consumer b m a foldlC = CC.foldl {-# INLINE foldlC #-} -- | A strict left fold on a chunked stream. -- -- Since 1.0.0 foldlCE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> a) -> a -> Consumer mono m a foldlCE = CC.foldlE {-# INLINE foldlCE #-} -- | Apply the provided mapping function and monoidal combine all values. -- -- Since 1.0.0 foldMapC :: (Monad m, Monoid b) => (a -> b) -> Consumer a m b foldMapC = CC.foldMap {-# INLINE foldMapC #-} -- | Apply the provided mapping function and monoidal combine all elements of the chunked stream. -- -- Since 1.0.0 foldMapCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Consumer mono m w foldMapCE = CC.foldMapE {-# INLINE foldMapCE #-} -- | Check that all values in the stream return True. -- -- Subject to shortcut logic: at the first False, consumption of the stream -- will stop. -- -- Since 1.0.0 allC :: Monad m => (a -> Bool) -> Consumer a m Bool allC = CC.all {-# INLINE allC #-} -- | Check that all elements in the chunked stream return True. -- -- Subject to shortcut logic: at the first False, consumption of the stream -- will stop. -- -- Since 1.0.0 allCE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m Bool allCE = CC.allE {-# INLINE allCE #-} -- | Check that at least one value in the stream returns True. -- -- Subject to shortcut logic: at the first True, consumption of the stream -- will stop. -- -- Since 1.0.0 anyC :: Monad m => (a -> Bool) -> Consumer a m Bool anyC = CC.any {-# INLINE anyC #-} -- | Check that at least one element in the chunked stream returns True. -- -- Subject to shortcut logic: at the first True, consumption of the stream -- will stop. -- -- Since 1.0.0 anyCE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m Bool anyCE = CC.anyE {-# INLINE anyCE #-} -- | Are all values in the stream True? -- -- Consumption stops once the first False is encountered. -- -- Since 1.0.0 andC :: Monad m => Consumer Bool m Bool andC = CC.and {-# INLINE andC #-} -- | Are all elements in the chunked stream True? -- -- Consumption stops once the first False is encountered. -- -- Since 1.0.0 andCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Consumer mono m Bool andCE = CC.andE {-# INLINE andCE #-} -- | Are any values in the stream True? -- -- Consumption stops once the first True is encountered. -- -- Since 1.0.0 orC :: Monad m => Consumer Bool m Bool orC = CC.or {-# INLINE orC #-} -- | Are any elements in the chunked stream True? -- -- Consumption stops once the first True is encountered. -- -- Since 1.0.0 orCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Consumer mono m Bool orCE = CC.orE {-# INLINE orCE #-} -- | 'Alternative'ly combine all values in the stream. -- -- Since 1.1.1 asumC = CC.asum -- | Are any values in the stream equal to the given value? -- -- Stops consuming as soon as a match is found. -- -- Since 1.0.0 elemC :: (Monad m, Eq a) => a -> Consumer a m Bool elemC = CC.elem {-# INLINE elemC #-} -- | Are any elements in the chunked stream equal to the given element? -- -- Stops consuming as soon as a match is found. -- -- Since 1.0.0 #if MIN_VERSION_mono_traversable(1,0,0) elemCE :: (Monad m, Seq.IsSequence seq, Eq (Element seq)) #else elemCE :: (Monad m, Seq.EqSequence seq) #endif => Element seq -> Consumer seq m Bool elemCE = CC.elemE {-# INLINE elemCE #-} -- | Are no values in the stream equal to the given value? -- -- Stops consuming as soon as a match is found. -- -- Since 1.0.0 notElemC :: (Monad m, Eq a) => a -> Consumer a m Bool notElemC = CC.notElem {-# INLINE notElemC #-} -- | Are no elements in the chunked stream equal to the given element? -- -- Stops consuming as soon as a match is found. -- -- Since 1.0.0 #if MIN_VERSION_mono_traversable(1,0,0) notElemCE :: (Monad m, Seq.IsSequence seq, Eq (Element seq)) #else notElemCE :: (Monad m, Seq.EqSequence seq) #endif => Element seq -> Consumer seq m Bool notElemCE = CC.notElemE {-# INLINE notElemCE #-} -- | Consume all incoming strict chunks into a lazy sequence. -- Note that the entirety of the sequence will be resident at memory. -- -- This can be used to consume a stream of strict ByteStrings into a lazy -- ByteString, for example. -- -- Since 1.0.0 sinkLazy :: (Monad m, LazySequence lazy strict) => Consumer strict m lazy sinkLazy = CC.sinkLazy {-# INLINE sinkLazy #-} -- | Consume all values from the stream and return as a list. Note that this -- will pull all values into memory. -- -- Since 1.0.0 sinkList :: Monad m => Consumer a m [a] sinkList = CC.sinkList {-# INLINE sinkList #-} -- | Sink incoming values into a vector, growing the vector as necessary to fit -- more elements. -- -- Note that using this function is more memory efficient than @sinkList@ and -- then converting to a @Vector@, as it avoids intermediate list constructors. -- -- Since 1.0.0 sinkVector :: (MonadBase base m, V.Vector v a, PrimMonad base) => Consumer a m (v a) sinkVector = CC.sinkVector {-# INLINE sinkVector #-} -- | Sink incoming values into a vector, up until size @maxSize@. Subsequent -- values will be left in the stream. If there are less than @maxSize@ values -- present, returns a @Vector@ of smaller size. -- -- Note that using this function is more memory efficient than @sinkList@ and -- then converting to a @Vector@, as it avoids intermediate list constructors. -- -- Since 1.0.0 sinkVectorN :: (MonadBase base m, V.Vector v a, PrimMonad base) => Int -- ^ maximum allowed size -> Consumer a m (v a) sinkVectorN = CC.sinkVectorN {-# INLINE sinkVectorN #-} -- | Convert incoming values to a builder and fold together all builder values. -- -- Defined as: @foldMap toBuilder@. -- -- Since 1.0.0 sinkBuilder :: (Monad m, Monoid builder, ToBuilder a builder) => Consumer a m builder sinkBuilder = CC.sinkBuilder {-# INLINE sinkBuilder #-} -- | Same as @sinkBuilder@, but afterwards convert the builder to its lazy -- representation. -- -- Alternatively, this could be considered an alternative to @sinkLazy@, with -- the following differences: -- -- * This function will allow multiple input types, not just the strict version -- of the lazy structure. -- -- * Some buffer copying may occur in this version. -- -- Since 1.0.0 sinkLazyBuilder :: (Monad m, Monoid builder, ToBuilder a builder, Builder builder lazy) => Consumer a m lazy sinkLazyBuilder = CC.sinkLazyBuilder {-# INLINE sinkLazyBuilder #-} -- | Consume and discard all remaining values in the stream. -- -- Since 1.0.0 sinkNull :: Monad m => Consumer a m () sinkNull = CC.sinkNull {-# INLINE sinkNull #-} -- | Same as @await@, but discards any leading 'onull' values. -- -- Since 1.0.0 awaitNonNull :: (Monad m, MonoFoldable a) => Consumer a m (Maybe (NonNull.NonNull a)) awaitNonNull = CC.awaitNonNull {-# INLINE awaitNonNull #-} -- | Take a single value from the stream, if available. -- -- Since 1.0.5 headC :: Monad m => Consumer a m (Maybe a) headC = CC.head -- | Same as 'headC', but returns a default value if none are available from the stream. -- -- Since 1.0.5 headDefC :: Monad m => a -> Consumer a m a headDefC = CC.headDef -- | Get the next element in the chunked stream. -- -- Since 1.0.0 headCE :: (Monad m, Seq.IsSequence seq) => Consumer seq m (Maybe (Element seq)) headCE = CC.headE {-# INLINE headCE #-} -- | View the next value in the stream without consuming it. -- -- Since 1.0.0 peekC :: Monad m => Consumer a m (Maybe a) peekC = CC.peek {-# INLINE peekC #-} -- | View the next element in the chunked stream without consuming it. -- -- Since 1.0.0 peekCE :: (Monad m, MonoFoldable mono) => Consumer mono m (Maybe (Element mono)) peekCE = CC.peekE {-# INLINE peekCE #-} -- | Retrieve the last value in the stream, if present. -- -- Since 1.0.0 lastC :: Monad m => Consumer a m (Maybe a) lastC = CC.last {-# INLINE lastC #-} -- | Same as 'lastC', but returns a default value if none are available from the stream. -- -- Since 1.0.5 lastDefC :: Monad m => a -> Consumer a m a lastDefC = CC.lastDef -- | Retrieve the last element in the chunked stream, if present. -- -- Since 1.0.0 lastCE :: (Monad m, Seq.IsSequence seq) => Consumer seq m (Maybe (Element seq)) lastCE = CC.lastE {-# INLINE lastCE #-} -- | Count how many values are in the stream. -- -- Since 1.0.0 lengthC :: (Monad m, Num len) => Consumer a m len lengthC = CC.length {-# INLINE lengthC #-} -- | Count how many elements are in the chunked stream. -- -- Since 1.0.0 lengthCE :: (Monad m, Num len, MonoFoldable mono) => Consumer mono m len lengthCE = CC.lengthE {-# INLINE lengthCE #-} -- | Count how many values in the stream pass the given predicate. -- -- Since 1.0.0 lengthIfC :: (Monad m, Num len) => (a -> Bool) -> Consumer a m len lengthIfC = CC.lengthIf {-# INLINE lengthIfC #-} -- | Count how many elements in the chunked stream pass the given predicate. -- -- Since 1.0.0 lengthIfCE :: (Monad m, Num len, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m len lengthIfCE = CC.lengthIfE {-# INLINE lengthIfCE #-} -- | Get the largest value in the stream, if present. -- -- Since 1.0.0 maximumC :: (Monad m, Ord a) => Consumer a m (Maybe a) maximumC = CC.maximum {-# INLINE maximumC #-} -- | Get the largest element in the chunked stream, if present. -- -- Since 1.0.0 #if MIN_VERSION_mono_traversable(1,0,0) maximumCE :: (Monad m, Seq.IsSequence seq, Ord (Element seq)) => Consumer seq m (Maybe (Element seq)) #else maximumCE :: (Monad m, Seq.OrdSequence seq) => Consumer seq m (Maybe (Element seq)) #endif maximumCE = CC.maximumE {-# INLINE maximumCE #-} -- | Get the smallest value in the stream, if present. -- -- Since 1.0.0 minimumC :: (Monad m, Ord a) => Consumer a m (Maybe a) minimumC = CC.minimum {-# INLINE minimumC #-} -- | Get the smallest element in the chunked stream, if present. -- -- Since 1.0.0 #if MIN_VERSION_mono_traversable(1,0,0) minimumCE :: (Monad m, Seq.IsSequence seq, Ord (Element seq)) => Consumer seq m (Maybe (Element seq)) #else minimumCE :: (Monad m, Seq.OrdSequence seq) => Consumer seq m (Maybe (Element seq)) #endif minimumCE = CC.minimumE {-# INLINE minimumCE #-} -- | True if there are no values in the stream. -- -- This function does not modify the stream. -- -- Since 1.0.0 nullC :: Monad m => Consumer a m Bool nullC = CC.null {-# INLINE nullC #-} -- | True if there are no elements in the chunked stream. -- -- This function may remove empty leading chunks from the stream, but otherwise -- will not modify it. -- -- Since 1.0.0 nullCE :: (Monad m, MonoFoldable mono) => Consumer mono m Bool nullCE = CC.nullE {-# INLINE nullCE #-} -- | Get the sum of all values in the stream. -- -- Since 1.0.0 sumC :: (Monad m, Num a) => Consumer a m a sumC = CC.sum {-# INLINE sumC #-} -- | Get the sum of all elements in the chunked stream. -- -- Since 1.0.0 sumCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono) sumCE = CC.sumE {-# INLINE sumCE #-} -- | Get the product of all values in the stream. -- -- Since 1.0.0 productC :: (Monad m, Num a) => Consumer a m a productC = CC.product {-# INLINE productC #-} -- | Get the product of all elements in the chunked stream. -- -- Since 1.0.0 productCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono) productCE = CC.productE {-# INLINE productCE #-} -- | Find the first matching value. -- -- Since 1.0.0 findC :: Monad m => (a -> Bool) -> Consumer a m (Maybe a) findC = CC.find {-# INLINE findC #-} -- | Apply the action to all values in the stream. -- -- Since 1.0.0 mapM_C :: Monad m => (a -> m ()) -> Consumer a m () mapM_C = CC.mapM_ {-# INLINE mapM_C #-} -- | Apply the action to all elements in the chunked stream. -- -- Since 1.0.0 mapM_CE :: (Monad m, MonoFoldable mono) => (Element mono -> m ()) -> Consumer mono m () mapM_CE = CC.mapM_E {-# INLINE mapM_CE #-} -- | A monadic strict left fold. -- -- Since 1.0.0 foldMC :: Monad m => (a -> b -> m a) -> a -> Consumer b m a foldMC = CC.foldM {-# INLINE foldMC #-} -- | A monadic strict left fold on a chunked stream. -- -- Since 1.0.0 foldMCE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> m a) -> a -> Consumer mono m a foldMCE = CC.foldME {-# INLINE foldMCE #-} -- | Apply the provided monadic mapping function and monoidal combine all values. -- -- Since 1.0.0 foldMapMC :: (Monad m, Monoid w) => (a -> m w) -> Consumer a m w foldMapMC = CC.foldMapM {-# INLINE foldMapMC #-} -- | Apply the provided monadic mapping function and monoidal combine all -- elements in the chunked stream. -- -- Since 1.0.0 foldMapMCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> m w) -> Consumer mono m w foldMapMCE = CC.foldMapME {-# INLINE foldMapMCE #-} -- | Print all incoming values to stdout. -- -- Since 1.0.0 printC :: (Show a, MonadIO m) => Consumer a m () printC = CC.print {-# INLINE printC #-} -- | @sinkHandle@ applied to @stdout@. -- -- Since 1.0.0 stdoutC :: MonadIO m => Consumer ByteString m () stdoutC = CC.stdout {-# INLINE stdoutC #-} -- | @sinkHandle@ applied to @stderr@. -- -- Since 1.0.0 stderrC :: MonadIO m => Consumer ByteString m () stderrC = CC.stderr {-# INLINE stderrC #-} -- | Apply a transformation to all values in a stream. -- -- Since 1.0.0 mapC :: Monad m => (a -> b) -> Conduit a m b mapC = CC.map {-# INLINE mapC #-} -- | Apply a transformation to all elements in a chunked stream. -- -- Since 1.0.0 mapCE :: (Monad m, Functor f) => (a -> b) -> Conduit (f a) m (f b) mapCE = CC.mapE {-# INLINE mapCE #-} -- | Apply a monomorphic transformation to all elements in a chunked stream. -- -- Unlike @mapE@, this will work on types like @ByteString@ and @Text@ which -- are @MonoFunctor@ but not @Functor@. -- -- Since 1.0.0 omapCE :: (Monad m, MonoFunctor mono) => (Element mono -> Element mono) -> Conduit mono m mono omapCE = CC.omapE {-# INLINE omapCE #-} -- | Apply the function to each value in the stream, resulting in a foldable -- value (e.g., a list). Then yield each of the individual values in that -- foldable value separately. -- -- Generalizes concatMap, mapMaybe, and mapFoldable. -- -- Since 1.0.0 concatMapC :: (Monad m, MonoFoldable mono) => (a -> mono) -> Conduit a m (Element mono) concatMapC = CC.concatMap {-# INLINE concatMapC #-} -- | Apply the function to each element in the chunked stream, resulting in a -- foldable value (e.g., a list). Then yield each of the individual values in -- that foldable value separately. -- -- Generalizes concatMap, mapMaybe, and mapFoldable. -- -- Since 1.0.0 concatMapCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Conduit mono m w concatMapCE = CC.concatMapE {-# INLINE concatMapCE #-} -- | Stream up to n number of values downstream. -- -- Note that, if downstream terminates early, not all values will be consumed. -- If you want to force /exactly/ the given number of values to be consumed, -- see 'takeExactly'. -- -- Since 1.0.0 takeC :: Monad m => Int -> Conduit a m a takeC = CC.take {-# INLINE takeC #-} -- | Stream up to n number of elements downstream in a chunked stream. -- -- Note that, if downstream terminates early, not all values will be consumed. -- If you want to force /exactly/ the given number of values to be consumed, -- see 'takeExactlyE'. -- -- Since 1.0.0 takeCE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> Conduit seq m seq takeCE = CC.takeE {-# INLINE takeCE #-} -- | Stream all values downstream that match the given predicate. -- -- Same caveats regarding downstream termination apply as with 'take'. -- -- Since 1.0.0 takeWhileC :: Monad m => (a -> Bool) -> Conduit a m a takeWhileC = CC.takeWhile {-# INLINE takeWhileC #-} -- | Stream all elements downstream that match the given predicate in a chunked stream. -- -- Same caveats regarding downstream termination apply as with 'takeE'. -- -- Since 1.0.0 takeWhileCE :: (Monad m, Seq.IsSequence seq) => (Element seq -> Bool) -> Conduit seq m seq takeWhileCE = CC.takeWhileE {-# INLINE takeWhileCE #-} -- | Consume precisely the given number of values and feed them downstream. -- -- This function is in contrast to 'take', which will only consume up to the -- given number of values, and will terminate early if downstream terminates -- early. This function will discard any additional values in the stream if -- they are unconsumed. -- -- Note that this function takes a downstream @ConduitM@ as a parameter, as -- opposed to working with normal fusion. For more information, see -- , the section -- titled \"pipes and conduit: isolate\". -- -- Since 1.0.0 takeExactlyC :: Monad m => Int -> ConduitM a b m r -> ConduitM a b m r takeExactlyC = CC.takeExactly {-# INLINE takeExactlyC #-} -- | Same as 'takeExactly', but for chunked streams. -- -- Since 1.0.0 takeExactlyCE :: (Monad m, Seq.IsSequence a) => Seq.Index a -> ConduitM a b m r -> ConduitM a b m r takeExactlyCE = CC.takeExactlyE {-# INLINE takeExactlyCE #-} -- | Flatten out a stream by yielding the values contained in an incoming -- @MonoFoldable@ as individually yielded values. -- -- Since 1.0.0 concatC :: (Monad m, MonoFoldable mono) => Conduit mono m (Element mono) concatC = CC.concat {-# INLINE concatC #-} -- | Keep only values in the stream passing a given predicate. -- -- Since 1.0.0 filterC :: Monad m => (a -> Bool) -> Conduit a m a filterC = CC.filter {-# INLINE filterC #-} -- | Keep only elements in the chunked stream passing a given predicate. -- -- Since 1.0.0 filterCE :: (Seq.IsSequence seq, Monad m) => (Element seq -> Bool) -> Conduit seq m seq filterCE = CC.filterE {-# INLINE filterCE #-} -- | Map values as long as the result is @Just@. -- -- Since 1.0.0 mapWhileC :: Monad m => (a -> Maybe b) -> Conduit a m b mapWhileC = CC.mapWhile {-# INLINE mapWhileC #-} -- | Break up a stream of values into vectors of size n. The final vector may -- be smaller than n if the total number of values is not a strict multiple of -- n. No empty vectors will be yielded. -- -- Since 1.0.0 conduitVector :: (MonadBase base m, V.Vector v a, PrimMonad base) => Int -- ^ maximum allowed size -> Conduit a m (v a) conduitVector = CC.conduitVector {-# INLINE conduitVector #-} -- | Analog of 'Prelude.scanl' for lists. -- -- Since 1.0.6 scanlC :: Monad m => (a -> b -> a) -> a -> Conduit b m a scanlC = CC.scanl {-# INLINE scanlC #-} -- | 'mapWhileC' with a break condition dependent on a strict accumulator. -- Equivalently, 'CL.mapAccum' as long as the result is @Right@. Instead of -- producing a leftover, the breaking input determines the resulting -- accumulator via @Left@. mapAccumWhileC :: Monad m => (a -> s -> Either s (s, b)) -> s -> ConduitM a b m s mapAccumWhileC = CC.mapAccumWhile {-# INLINE mapAccumWhileC #-} -- | 'concatMap' with an accumulator. -- -- Since 1.0.0 concatMapAccumC :: Monad m => (a -> accum -> (accum, [b])) -> accum -> Conduit a m b concatMapAccumC = CC.concatMapAccum {-# INLINE concatMapAccumC #-} -- | Insert the given value between each two values in the stream. -- -- Since 1.0.0 intersperseC :: Monad m => a -> Conduit a m a intersperseC = CC.intersperse {-# INLINE intersperseC #-} -- | Sliding window of values -- 1,2,3,4,5 with window size 2 gives -- [1,2],[2,3],[3,4],[4,5] -- -- Best used with structures that support O(1) snoc. -- -- Since 1.0.0 slidingWindowC :: (Monad m, Seq.IsSequence seq, Element seq ~ a) => Int -> Conduit a m seq slidingWindowC = CC.slidingWindow {-# INLINE slidingWindowC #-} -- | Split input into chunk of size 'chunkSize' -- -- The last element may be smaller than the 'chunkSize' (see also -- 'chunksOfExactlyE' which will not yield this last element) -- -- @since 1.1.2 chunksOfCE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> Conduit seq m seq chunksOfCE = CC.chunksOfE {-# INLINE chunksOfCE #-} -- | Split input into chunk of size 'chunkSize' -- -- If the input does not split into chunks exactly, the remainder will be -- leftover (see also 'chunksOfE') -- -- @since 1.1.2 chunksOfExactlyCE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> Conduit seq m seq chunksOfExactlyCE = CC.chunksOfExactlyE {-# INLINE chunksOfExactlyCE #-} -- | Apply base64-encoding to the stream. -- -- Since 1.0.0 encodeBase64C :: Monad m => Conduit ByteString m ByteString encodeBase64C = CC.encodeBase64 {-# INLINE encodeBase64C #-} -- | Apply base64-decoding to the stream. Will stop decoding on the first -- invalid chunk. -- -- Since 1.0.0 decodeBase64C :: Monad m => Conduit ByteString m ByteString decodeBase64C = CC.decodeBase64 {-# INLINE decodeBase64C #-} -- | Apply URL-encoding to the stream. -- -- Since 1.0.0 encodeBase64URLC :: Monad m => Conduit ByteString m ByteString encodeBase64URLC = CC.encodeBase64URL {-# INLINE encodeBase64URLC #-} -- | Apply lenient base64URL-decoding to the stream. Will stop decoding on the -- first invalid chunk. -- -- Since 1.0.0 decodeBase64URLC :: Monad m => Conduit ByteString m ByteString decodeBase64URLC = CC.decodeBase64URL {-# INLINE decodeBase64URLC #-} -- | Apply base16-encoding to the stream. -- -- Since 1.0.0 encodeBase16C :: Monad m => Conduit ByteString m ByteString encodeBase16C = CC.encodeBase16 {-# INLINE encodeBase16C #-} -- | Apply base16-decoding to the stream. Will stop decoding on the first -- invalid chunk. -- -- Since 1.0.0 decodeBase16C :: Monad m => Conduit ByteString m ByteString decodeBase16C = CC.decodeBase16 {-# INLINE decodeBase16C #-} -- | Apply a monadic transformation to all values in a stream. -- -- If you do not need the transformed values, and instead just want the monadic -- side-effects of running the action, see 'mapM_'. -- -- Since 1.0.0 mapMC :: Monad m => (a -> m b) -> Conduit a m b mapMC = CC.mapM {-# INLINE mapMC #-} -- | Apply a monadic transformation to all elements in a chunked stream. -- -- Since 1.0.0 mapMCE :: (Monad m, Data.Traversable.Traversable f) => (a -> m b) -> Conduit (f a) m (f b) mapMCE = CC.mapME {-# INLINE mapMCE #-} -- | Apply a monadic monomorphic transformation to all elements in a chunked stream. -- -- Unlike @mapME@, this will work on types like @ByteString@ and @Text@ which -- are @MonoFunctor@ but not @Functor@. -- -- Since 1.0.0 omapMCE :: (Monad m, MonoTraversable mono) => (Element mono -> m (Element mono)) -> Conduit mono m mono omapMCE = CC.omapME {-# INLINE omapMCE #-} -- | Apply the monadic function to each value in the stream, resulting in a -- foldable value (e.g., a list). Then yield each of the individual values in -- that foldable value separately. -- -- Generalizes concatMapM, mapMaybeM, and mapFoldableM. -- -- Since 1.0.0 concatMapMC :: (Monad m, MonoFoldable mono) => (a -> m mono) -> Conduit a m (Element mono) concatMapMC = CC.concatMapM {-# INLINE concatMapMC #-} -- | Keep only values in the stream passing a given monadic predicate. -- -- Since 1.0.0 filterMC :: Monad m => (a -> m Bool) -> Conduit a m a filterMC = CC.filterM {-# INLINE filterMC #-} -- | Keep only elements in the chunked stream passing a given monadic predicate. -- -- Since 1.0.0 filterMCE :: (Monad m, Seq.IsSequence seq) => (Element seq -> m Bool) -> Conduit seq m seq filterMCE = CC.filterME {-# INLINE filterMCE #-} -- | Apply a monadic action on all values in a stream. -- -- This @Conduit@ can be used to perform a monadic side-effect for every -- value, whilst passing the value through the @Conduit@ as-is. -- -- > iterM f = mapM (\a -> f a >>= \() -> return a) -- -- Since 1.0.0 iterMC :: Monad m => (a -> m ()) -> Conduit a m a iterMC = CC.iterM {-# INLINE iterMC #-} -- | Analog of 'Prelude.scanl' for lists, monadic. -- -- Since 1.0.6 scanlMC :: Monad m => (a -> b -> m a) -> a -> Conduit b m a scanlMC = CC.scanlM {-# INLINE scanlMC #-} -- | Monadic `mapAccumWhileC`. mapAccumWhileMC :: Monad m => (a -> s -> m (Either s (s, b))) -> s -> ConduitM a b m s mapAccumWhileMC = CC.mapAccumWhileM {-# INLINE mapAccumWhileMC #-} -- | 'concatMapM' with an accumulator. -- -- Since 1.0.0 concatMapAccumMC :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> Conduit a m b concatMapAccumMC = CC.concatMapAccumM {-# INLINE concatMapAccumMC #-} -- | Encode a stream of text as UTF8. -- -- Since 1.0.0 encodeUtf8C :: (Monad m, DTE.Utf8 text binary) => Conduit text m binary encodeUtf8C = CC.encodeUtf8 {-# INLINE encodeUtf8C #-} -- | Decode a stream of binary data as UTF8. -- -- Since 1.0.0 decodeUtf8C :: MonadThrow m => Conduit ByteString m Text decodeUtf8C = CC.decodeUtf8 {-# INLINE decodeUtf8C #-} -- | Decode a stream of binary data as UTF8, replacing any invalid bytes with -- the Unicode replacement character. -- -- Since 1.0.0 decodeUtf8LenientC :: MonadThrow m => Conduit ByteString m Text decodeUtf8LenientC = CC.decodeUtf8Lenient {-# INLINE decodeUtf8LenientC #-} -- | Stream in the entirety of a single line. -- -- Like @takeExactly@, this will consume the entirety of the line regardless of -- the behavior of the inner Conduit. -- -- Since 1.0.0 lineC :: (Monad m, Seq.IsSequence seq, Element seq ~ Char) => ConduitM seq o m r -> ConduitM seq o m r lineC = CC.line {-# INLINE lineC #-} -- | Same as 'line', but operates on ASCII/binary data. -- -- Since 1.0.0 lineAsciiC :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8) => ConduitM seq o m r -> ConduitM seq o m r lineAsciiC = CC.lineAscii {-# INLINE lineAsciiC #-} -- | Insert a newline character after each incoming chunk of data. -- -- Since 1.0.0 unlinesC :: (Monad m, Seq.IsSequence seq, Element seq ~ Char) => Conduit seq m seq unlinesC = CC.unlines {-# INLINE unlinesC #-} -- | Same as 'unlines', but operates on ASCII/binary data. -- -- Since 1.0.0 unlinesAsciiC :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8) => Conduit seq m seq unlinesAsciiC = CC.unlinesAscii {-# INLINE unlinesAsciiC #-} -- | Convert a stream of arbitrarily-chunked textual data into a stream of data -- where each chunk represents a single line. Note that, if you have -- unknown/untrusted input, this function is /unsafe/, since it would allow an -- attacker to form lines of massive length and exhaust memory. -- -- Since 1.0.0 linesUnboundedC :: (Monad m, Seq.IsSequence seq, Element seq ~ Char) => Conduit seq m seq linesUnboundedC = CC.linesUnbounded {-# INLINE linesUnboundedC #-} -- | Same as 'linesUnbounded', but for ASCII/binary data. -- -- Since 1.0.0 linesUnboundedAsciiC :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8) => Conduit seq m seq linesUnboundedAsciiC = CC.linesUnboundedAscii {-# INLINE linesUnboundedAsciiC #-} -- | Generally speaking, yielding values from inside a Conduit requires -- some allocation for constructors. This can introduce an overhead, -- similar to the overhead needed to represent a list of values instead of -- a vector. This overhead is even more severe when talking about unboxed -- values. -- -- This combinator allows you to overcome this overhead, and efficiently -- fill up vectors. It takes two parameters. The first is the size of each -- mutable vector to be allocated. The second is a function. The function -- takes an argument which will yield the next value into a mutable -- vector. -- -- Under the surface, this function uses a number of tricks to get high -- performance. For more information on both usage and implementation, -- please see: -- -- -- Since 1.0.0 vectorBuilderC :: (PrimMonad base, MonadBase base m, V.Vector v e, MonadBase base n) => Int -- ^ size -> ((e -> n ()) -> Sink i m r) -> ConduitM i (v e) m r vectorBuilderC = CC.vectorBuilder {-# INLINE vectorBuilderC #-} conduit-combinators-1.1.2/test/Spec.hs0000644000000000000000000010024713211222300016057 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} import Conduit import Prelude hiding (FilePath) import Data.Maybe (listToMaybe) import Data.Conduit.Combinators.Internal import Data.Conduit.Combinators (slidingWindow, chunksOfE, chunksOfExactlyE) import Data.List (intersperse, sort, find, mapAccumL) import Safe (tailSafe) import System.FilePath (takeExtension) import Test.Hspec import Test.Hspec.QuickCheck import qualified Data.Text as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Encoding as TL import Data.IORef import qualified Data.Vector as V import qualified Data.Vector.Unboxed as VU import qualified Data.Vector.Storable as VS import Control.Monad (liftM) import Control.Monad.ST (runST) import Control.Monad.Trans.Writer import System.FilePath (()) import qualified System.IO as IO #if ! MIN_VERSION_base(4,8,0) import Data.Monoid (Monoid (..)) import Control.Applicative ((<$>), (<*>)) #endif import Data.Builder #if MIN_VERSION_mono_traversable(1,0,0) import Data.Sequences (LazySequence (..), Utf8 (..)) #else import Data.Sequences.Lazy import Data.Textual.Encoding #endif import qualified Data.NonNull as NN import System.IO.Silently (hCapture) import GHC.IO.Handle (hDuplicateTo) import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as S8 import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy.Char8 as L8 import System.Random.MWC (createSystemRandom) import qualified Data.ByteString.Base16 as B16 import qualified Data.ByteString.Base16.Lazy as B16L import qualified Data.ByteString.Base64 as B64 import qualified Data.ByteString.Base64.Lazy as B64L import qualified Data.ByteString.Base64.URL.Lazy as B64LU import qualified Data.ByteString.Base64.URL as B64U import qualified StreamSpec main :: IO () main = hspec $ do describe "yieldMany" $ do it "list" $ runIdentity (yieldMany [1..10] $$ sinkList) `shouldBe` [1..10] it "Text" $ runIdentity (yieldMany ("Hello World" :: T.Text) $$ sinkList) `shouldBe` "Hello World" it "unfold" $ let f 11 = Nothing f i = Just (show i, i + 1) in runIdentity (unfoldC f 1 $$ sinkList) `shouldBe` map show [1..10] it "enumFromTo" $ runIdentity (enumFromToC 1 10 $$ sinkList) `shouldBe` [1..10] it "iterate" $ let f i = i + 1 src = iterateC f seed seed = 1 count = 10 res = runIdentity $ src $$ takeC count =$ sinkList in res `shouldBe` take count (iterate f seed) it "repeat" $ let src = repeatC seed seed = 1 count = 10 res = runIdentity $ src $$ takeC count =$ sinkList in res `shouldBe` take count (repeat seed) it "replicate" $ let src = replicateC count seed seed = 1 count = 10 res = runIdentity $ src $$ sinkList in res `shouldBe` replicate count seed it "sourceLazy" $ let tss = ["foo", "bar", "baz"] tl = TL.fromChunks tss res = runIdentity $ sourceLazy tl $$ sinkList in res `shouldBe` tss it "repeatM" $ let src = repeatMC (return seed) seed = 1 count = 10 res = runIdentity $ src $$ takeC count =$ sinkList in res `shouldBe` take count (repeat seed) it "repeatWhileM" $ do ref <- newIORef 0 let f = atomicModifyIORef ref $ \i -> (succ i, succ i) src = repeatWhileMC f (< 11) res <- src $$ sinkList res `shouldBe` [1..10] it "replicateM" $ do ref <- newIORef 0 let f = atomicModifyIORef ref $ \i -> (succ i, succ i) src = replicateMC 10 f res <- src $$ sinkList res `shouldBe` [1..10] it "sourceFile" $ do let contents = concat $ replicate 10000 $ "this is some content\n" fp = "tmp" writeFile fp contents res <- runResourceT $ sourceFile fp $$ sinkLazy nocrBL res `shouldBe` TL.encodeUtf8 (TL.pack contents) it "sourceHandle" $ do let contents = concat $ replicate 10000 $ "this is some content\n" fp = "tmp" writeFile fp contents res <- IO.withBinaryFile "tmp" IO.ReadMode $ \h -> sourceHandle h $$ sinkLazy nocrBL res `shouldBe` TL.encodeUtf8 (TL.pack contents) it "sourceIOHandle" $ do let contents = concat $ replicate 10000 $ "this is some content\n" fp = "tmp" writeFile fp contents let open = IO.openBinaryFile "tmp" IO.ReadMode res <- runResourceT $ sourceIOHandle open $$ sinkLazy nocrBL res `shouldBe` TL.encodeUtf8 (TL.pack contents) prop "stdin" $ \(S.pack -> content) -> do S.writeFile "tmp" content IO.withBinaryFile "tmp" IO.ReadMode $ \h -> do hDuplicateTo h IO.stdin x <- stdinC $$ foldC x `shouldBe` content it "sourceRandom" $ do x <- sourceRandom $$ takeC 100 =$ sumC :: IO Double x `shouldSatisfy` (\y -> y > 10 && y < 90) it "sourceRandomN" $ do x <- sourceRandomN 100 $$ sumC :: IO Double x `shouldSatisfy` (\y -> y > 10 && y < 90) it "sourceRandomGen" $ do gen <- createSystemRandom x <- sourceRandomGen gen $$ takeC 100 =$ sumC :: IO Double x `shouldSatisfy` (\y -> y > 10 && y < 90) it "sourceRandomNGen" $ do gen <- createSystemRandom x <- sourceRandomNGen gen 100 $$ sumC :: IO Double x `shouldSatisfy` (\y -> y > 10 && y < 90) let hasExtension' ext fp = takeExtension fp == ext it "sourceDirectory" $ do res <- runResourceT $ sourceDirectory "test" $$ filterC (not . hasExtension' ".swp") =$ sinkList sort res `shouldBe` [ "test" "Spec.hs" , "test" "StreamSpec.hs" , "test" "subdir" ] it "sourceDirectoryDeep" $ do res1 <- runResourceT $ sourceDirectoryDeep False "test" $$ filterC (not . hasExtension' ".swp") =$ sinkList res2 <- runResourceT $ sourceDirectoryDeep True "test" $$ filterC (not . hasExtension' ".swp") =$ sinkList sort res1 `shouldBe` [ "test" "Spec.hs" , "test" "StreamSpec.hs" , "test" "subdir" "dummyfile.txt" ] sort res1 `shouldBe` sort res2 prop "drop" $ \(T.pack -> input) count -> runIdentity (yieldMany input $$ (dropC count >>= \() -> sinkList)) `shouldBe` T.unpack (T.drop count input) prop "dropE" $ \(T.pack -> input) -> runIdentity (yield input $$ (dropCE 5 >>= \() -> foldC)) `shouldBe` T.drop 5 input prop "dropWhile" $ \(T.pack -> input) sep -> runIdentity (yieldMany input $$ (dropWhileC (<= sep) >>= \() -> sinkList)) `shouldBe` T.unpack (T.dropWhile (<= sep) input) prop "dropWhileE" $ \(T.pack -> input) sep -> runIdentity (yield input $$ (dropWhileCE (<= sep) >>= \() -> foldC)) `shouldBe` T.dropWhile (<= sep) input it "fold" $ let list = [[1..10], [11..20]] src = yieldMany list res = runIdentity $ src $$ foldC in res `shouldBe` concat list it "foldE" $ let list = [[1..10], [11..20]] src = yieldMany $ Identity list res = runIdentity $ src $$ foldCE in res `shouldBe` concat list it "foldl" $ let res = runIdentity $ yieldMany [1..10] $$ foldlC (+) 0 in res `shouldBe` sum [1..10] it "foldlE" $ let res = runIdentity $ yield [1..10] $$ foldlCE (+) 0 in res `shouldBe` sum [1..10] it "foldMap" $ let src = yieldMany [1..10] res = runIdentity $ src $$ foldMapC return in res `shouldBe` [1..10] it "foldMapE" $ let src = yield [1..10] res = runIdentity $ src $$ foldMapCE return in res `shouldBe` [1..10] prop "all" $ \ (input :: [Int]) -> runIdentity (yieldMany input $$ allC even) `shouldBe` all evenInt input prop "allE" $ \ (input :: [Int]) -> runIdentity (yield input $$ allCE even) `shouldBe` all evenInt input prop "any" $ \ (input :: [Int]) -> runIdentity (yieldMany input $$ anyC even) `shouldBe` any evenInt input prop "anyE" $ \ (input :: [Int]) -> runIdentity (yield input $$ anyCE even) `shouldBe` any evenInt input prop "and" $ \ (input :: [Bool]) -> runIdentity (yieldMany input $$ andC) `shouldBe` and input prop "andE" $ \ (input :: [Bool]) -> runIdentity (yield input $$ andCE) `shouldBe` and input prop "or" $ \ (input :: [Bool]) -> runIdentity (yieldMany input $$ orC) `shouldBe` or input prop "orE" $ \ (input :: [Bool]) -> runIdentity (yield input $$ orCE) `shouldBe` or input prop "elem" $ \x xs -> runIdentity (yieldMany xs $$ elemC x) `shouldBe` elemInt x xs prop "elemE" $ \x xs -> runIdentity (yield xs $$ elemCE x) `shouldBe` elemInt x xs prop "notElem" $ \x xs -> runIdentity (yieldMany xs $$ notElemC x) `shouldBe` notElemInt x xs prop "notElemE" $ \x xs -> runIdentity (yield xs $$ notElemCE x) `shouldBe` notElemInt x xs prop "sinkVector regular" $ \xs -> do res <- yieldMany xs $$ sinkVector res `shouldBe` V.fromList (xs :: [Int]) prop "sinkVector unboxed" $ \xs -> do res <- yieldMany xs $$ sinkVector res `shouldBe` VU.fromList (xs :: [Int]) prop "sinkVector storable" $ \xs -> do res <- yieldMany xs $$ sinkVector res `shouldBe` VS.fromList (xs :: [Int]) prop "sinkVectorN regular" $ \xs' -> do let maxSize = 20 xs = take maxSize xs' res <- yieldMany xs' $$ sinkVectorN maxSize res `shouldBe` V.fromList (xs :: [Int]) prop "sinkVectorN unboxed" $ \xs' -> do let maxSize = 20 xs = take maxSize xs' res <- yieldMany xs' $$ sinkVectorN maxSize res `shouldBe` VU.fromList (xs :: [Int]) prop "sinkVectorN storable" $ \xs' -> do let maxSize = 20 xs = take maxSize xs' res <- yieldMany xs' $$ sinkVectorN maxSize res `shouldBe` VS.fromList (xs :: [Int]) prop "sinkBuilder" $ \(map T.pack -> inputs) -> let builder = runIdentity (yieldMany inputs $$ sinkBuilder) :: TextBuilder ltext = builderToLazy builder in ltext `shouldBe` fromChunks inputs prop "sinkLazyBuilder" $ \(map T.pack -> inputs) -> let lbs = runIdentity (yieldMany inputs $$ sinkLazyBuilder) in lbs `shouldBe` encodeUtf8 (fromChunks inputs) prop "sinkNull" $ \xs toSkip -> do res <- yieldMany xs $$ do takeC toSkip =$ sinkNull sinkList res `shouldBe` drop toSkip (xs :: [Int]) prop "awaitNonNull" $ \xs -> fmap NN.toNullable (runIdentity $ yieldMany xs $$ awaitNonNull) `shouldBe` listToMaybe (filter (not . null) (xs :: [[Int]])) prop "headE" $ \ (xs :: [[Int]]) -> runIdentity (yieldMany xs $$ ((,) <$> headCE <*> foldC)) `shouldBe` (listToMaybe $ concat xs, drop 1 $ concat xs) prop "peek" $ \xs -> runIdentity (yieldMany xs $$ ((,) <$> peekC <*> sinkList)) `shouldBe` (listToMaybe xs, xs :: [Int]) prop "peekE" $ \ (xs :: [[Int]]) -> runIdentity (yieldMany xs $$ ((,) <$> peekCE <*> foldC)) `shouldBe` (listToMaybe $ concat xs, concat xs) prop "last" $ \xs -> runIdentity (yieldMany xs $$ lastC) `shouldBe` listToMaybe (reverse (xs :: [Int])) prop "lastE" $ \ (xs :: [[Int]]) -> runIdentity (yieldMany xs $$ lastCE) `shouldBe` listToMaybe (reverse (concat xs)) prop "length" $ \xs -> runIdentity (yieldMany xs $$ lengthC) `shouldBe` length (xs :: [Int]) prop "lengthE" $ \ (xs :: [[Int]]) -> runIdentity (yieldMany xs $$ lengthCE) `shouldBe` length (concat xs) prop "lengthIf" $ \x xs -> runIdentity (yieldMany xs $$ lengthIfC (< x)) `shouldBe` length (filter (< x) xs :: [Int]) prop "lengthIfE" $ \x (xs :: [[Int]]) -> runIdentity (yieldMany xs $$ lengthIfCE (< x)) `shouldBe` length (filter (< x) (concat xs)) prop "maximum" $ \xs -> runIdentity (yieldMany xs $$ maximumC) `shouldBe` (if null (xs :: [Int]) then Nothing else Just (maximum xs)) prop "maximumE" $ \ (xs :: [[Int]]) -> runIdentity (yieldMany xs $$ maximumCE) `shouldBe` (if null (concat xs) then Nothing else Just (maximum $ concat xs)) prop "minimum" $ \xs -> runIdentity (yieldMany xs $$ minimumC) `shouldBe` (if null (xs :: [Int]) then Nothing else Just (minimum xs)) prop "minimumE" $ \ (xs :: [[Int]]) -> runIdentity (yieldMany xs $$ minimumCE) `shouldBe` (if null (concat xs) then Nothing else Just (minimum $ concat xs)) prop "null" $ \xs -> runIdentity (yieldMany xs $$ nullC) `shouldBe` null (xs :: [Int]) prop "nullE" $ \ (xs :: [[Int]]) -> runIdentity (yieldMany xs $$ ((,) <$> nullCE <*> foldC)) `shouldBe` (null (concat xs), concat xs) prop "sum" $ \xs -> runIdentity (yieldMany xs $$ sumC) `shouldBe` sum (xs :: [Int]) prop "sumE" $ \ (xs :: [[Int]]) -> runIdentity (yieldMany xs $$ sumCE) `shouldBe` sum (concat xs) prop "product" $ \xs -> runIdentity (yieldMany xs $$ productC) `shouldBe` product (xs :: [Int]) prop "productE" $ \ (xs :: [[Int]]) -> runIdentity (yieldMany xs $$ productCE) `shouldBe` product (concat xs) prop "find" $ \x xs -> runIdentity (yieldMany xs $$ findC (< x)) `shouldBe` find (< x) (xs :: [Int]) prop "mapM_" $ \xs -> let res = execWriter $ yieldMany xs $$ mapM_C (tell . return) in res `shouldBe` (xs :: [Int]) prop "mapM_E" $ \xs -> let res = execWriter $ yield xs $$ mapM_CE (tell . return) in res `shouldBe` (xs :: [Int]) prop "foldM" $ \ (xs :: [Int]) -> do res <- yieldMany xs $$ foldMC addM 0 res `shouldBe` sum xs prop "foldME" $ \ (xs :: [Int]) -> do res <- yield xs $$ foldMCE addM 0 res `shouldBe` sum xs it "foldMapM" $ let src = yieldMany [1..10] res = runIdentity $ src $$ foldMapMC (return . return) in res `shouldBe` [1..10] it "foldMapME" $ let src = yield [1..10] res = runIdentity $ src $$ foldMapMCE (return . return) in res `shouldBe` [1..10] it "sinkFile" $ do let contents = mconcat $ replicate 1000 $ "this is some content\n" fp = "tmp" runResourceT $ yield contents $$ sinkFile fp res <- S.readFile fp res `shouldBe` contents it "sinkHandle" $ do let contents = mconcat $ replicate 1000 $ "this is some content\n" fp = "tmp" IO.withBinaryFile "tmp" IO.WriteMode $ \h -> yield contents $$ sinkHandle h res <- S.readFile fp res `shouldBe` contents it "sinkIOHandle" $ do let contents = mconcat $ replicate 1000 $ "this is some content\n" fp = "tmp" open = IO.openBinaryFile "tmp" IO.WriteMode runResourceT $ yield contents $$ sinkIOHandle open res <- S.readFile fp res `shouldBe` contents prop "print" $ \vals -> do let expected = Prelude.unlines $ map showInt vals (actual, ()) <- hCapture [IO.stdout] $ yieldMany vals $$ printC actual `shouldBe` expected #ifndef WINDOWS prop "stdout" $ \ (vals :: [String]) -> do let expected = concat vals (actual, ()) <- hCapture [IO.stdout] $ yieldMany (map T.pack vals) $$ encodeUtf8C =$ stdoutC actual `shouldBe` expected prop "stderr" $ \ (vals :: [String]) -> do let expected = concat vals (actual, ()) <- hCapture [IO.stderr] $ yieldMany (map T.pack vals) $$ encodeUtf8C =$ stderrC actual `shouldBe` expected #endif prop "map" $ \input -> runIdentity (yieldMany input $$ mapC succChar =$ sinkList) `shouldBe` map succChar input prop "mapE" $ \(map V.fromList -> inputs) -> runIdentity (yieldMany inputs $$ mapCE succChar =$ foldC) `shouldBe` V.map succChar (V.concat inputs) prop "omapE" $ \(map T.pack -> inputs) -> runIdentity (yieldMany inputs $$ omapCE succChar =$ foldC) `shouldBe` T.map succChar (T.concat inputs) prop "concatMap" $ \ (input :: [Int]) -> runIdentity (yieldMany input $$ concatMapC showInt =$ sinkList) `shouldBe` concatMap showInt input prop "concatMapE" $ \ (input :: [Int]) -> runIdentity (yield input $$ concatMapCE showInt =$ foldC) `shouldBe` concatMap showInt input prop "take" $ \(T.pack -> input) count -> runIdentity (yieldMany input $$ (takeC count >>= \() -> mempty) =$ sinkList) `shouldBe` T.unpack (T.take count input) prop "takeE" $ \(T.pack -> input) count -> runIdentity (yield input $$ (takeCE count >>= \() -> mempty) =$ foldC) `shouldBe` T.take count input prop "takeWhile" $ \(T.pack -> input) sep -> runIdentity (yieldMany input $$ do x <- (takeWhileC (<= sep) >>= \() -> mempty) =$ sinkList y <- sinkList return (x, y)) `shouldBe` span (<= sep) (T.unpack input) prop "takeWhileE" $ \(T.pack -> input) sep -> runIdentity (yield input $$ do x <- (takeWhileCE (<= sep) >>= \() -> mempty) =$ foldC y <- foldC return (x, y)) `shouldBe` T.span (<= sep) input it "takeExactly" $ let src = yieldMany [1..10] sink = do x <- takeExactlyC 5 $ return 1 y <- sinkList return (x, y) res = runIdentity $ src $$ sink in res `shouldBe` (1, [6..10]) it "takeExactlyE" $ let src = yield ("Hello World" :: T.Text) sink = do takeExactlyCE 5 (mempty :: Sink T.Text Identity ()) y <- sinkLazy return y res = runIdentity $ src $$ sink in res `shouldBe` " World" it "takeExactlyE Vector" $ do let src = yield (V.fromList $ T.unpack "Hello World") sink = do x <- takeExactlyCE 5 $ return 1 y <- foldC return (x, y) res <- src $$ sink res `shouldBe` (1, V.fromList $ T.unpack " World") it "takeExactlyE 2" $ let src = yield ("Hello World" :: T.Text) sink = do x <- takeExactlyCE 5 $ return 1 y <- sinkLazy return (x, y) res = runIdentity $ src $$ sink -- FIXME type signature on next line is necessary in GHC 7.6.3 to -- avoid a crash: -- -- test: internal error: ARR_WORDS object entered! -- (GHC version 7.6.3 for x86_64_unknown_linux) -- Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug -- Aborted (core dumped) -- -- Report upstream when packages are released in res `shouldBe` (1, " World" :: TL.Text) prop "concat" $ \input -> runIdentity (yield (T.pack input) $$ concatC =$ sinkList) `shouldBe` input prop "filter" $ \input -> runIdentity (yieldMany input $$ filterC evenInt =$ sinkList) `shouldBe` filter evenInt input prop "filterE" $ \input -> runIdentity (yield input $$ filterCE evenInt =$ foldC) `shouldBe` filter evenInt input prop "mapWhile" $ \input (min 20 -> highest) -> let f i | i < highest = Just (i + 2 :: Int) | otherwise = Nothing res = runIdentity $ yieldMany input $$ do x <- (mapWhileC f >>= \() -> mempty) =$ sinkList y <- sinkList return (x, y) (taken, dropped) = span (< highest) input in res `shouldBe` (map (+ 2) taken, dropped) prop "conduitVector" $ \(take 200 -> input) size' -> do let size = min 30 $ succ $ abs size' res <- yieldMany input $$ conduitVector size =$ sinkList res `shouldSatisfy` all (\v -> V.length v <= size) drop 1 (reverse res) `shouldSatisfy` all (\v -> V.length v == size) V.concat res `shouldBe` V.fromList (input :: [Int]) prop "scanl" $ \input seed -> let f a b = a + b :: Int res = runIdentity $ yieldMany input $$ scanlC f seed =$ sinkList in res `shouldBe` scanl f seed input prop "mapAccumWhile" $ \input (min 20 -> highest) -> let f i accum | i < highest = Right (i + accum, 2 * i :: Int) | otherwise = Left accum res = runIdentity $ yieldMany input $$ do (s, x) <- fuseBoth (mapAccumWhileC f 0) sinkList y <- sinkList return (s, x, y) (taken, dropped) = span (< highest) input in res `shouldBe` (sum taken, map (* 2) taken, tailSafe dropped) prop "concatMapAccum" $ \(input :: [Int]) -> let f a accum = (a + accum, [a, accum]) res = runIdentity $ yieldMany input $$ concatMapAccumC f 0 =$ sinkList expected = concat $ snd $ mapAccumL (flip f) 0 input in res `shouldBe` expected prop "intersperse" $ \xs x -> runIdentity (yieldMany xs $$ intersperseC x =$ sinkList) `shouldBe` intersperse (x :: Int) xs describe "binary base encoding" $ do describe "encode/decode is idempotent" $ do prop "64 non-url" $ \(map S.pack -> bss) -> mconcat bss == runIdentity (yieldMany bss $$ encodeBase64C =$ decodeBase64C =$ foldC) prop "64 url" $ \(map S.pack -> bss) -> mconcat bss == runIdentity (yieldMany bss $$ encodeBase64URLC =$ decodeBase64URLC =$ foldC) prop "16" $ \(map S.pack -> bss) -> mconcat bss == runIdentity (yieldMany bss $$ encodeBase16C =$ decodeBase16C =$ foldC) describe "encode is identical" $ do prop "64 non-url" $ \(map S.pack -> bss) -> B64.encode (mconcat bss) == runIdentity (yieldMany bss $$ encodeBase64C =$ foldC) prop "64 url" $ \(map S.pack -> bss) -> B64U.encode (mconcat bss) == runIdentity (yieldMany bss $$ encodeBase64URLC =$ foldC) prop "16" $ \(map S.pack -> bss) -> B16.encode (mconcat bss) == runIdentity (yieldMany bss $$ encodeBase16C =$ foldC) describe "decode leftovers work" $ do let test name encL dec decC = prop name $ \(L.toChunks . encL . L.pack -> bss) -> do let invalid = "\0INVALID" src = yieldMany bss >> yield invalid sink = (,) <$> (decC =$ foldC) <*> foldC expected = (dec $ mconcat bss, invalid) actual <- src $$ sink actual `shouldBe` expected test "64 non-url" B64L.encode B64.decodeLenient decodeBase64C test "64 url" B64LU.encode B64U.decodeLenient decodeBase64URLC let b16Decode x = case B16.decode x of (y, "") -> y _ -> error "FIXME!" test "16" B16L.encode b16Decode decodeBase16C prop "mapM" $ \input -> runIdentity (yieldMany input $$ mapMC (return . succChar) =$ sinkList) `shouldBe` map succChar input prop "mapME" $ \(map V.fromList -> inputs) -> runIdentity (yieldMany inputs $$ mapMCE (return . succChar) =$ foldC) `shouldBe` V.map succChar (V.concat inputs) prop "omapME" $ \(map T.pack -> inputs) -> runIdentity (yieldMany inputs $$ omapMCE (return . succChar) =$ foldC) `shouldBe` T.map succChar (T.concat inputs) prop "concatMapM" $ \ (input :: [Int]) -> runIdentity (yieldMany input $$ concatMapMC (return . showInt) =$ sinkList) `shouldBe` concatMap showInt input prop "filterM" $ \input -> runIdentity (yieldMany input $$ filterMC (return . evenInt) =$ sinkList) `shouldBe` filter evenInt input prop "filterME" $ \input -> runIdentity (yield input $$ filterMCE (return . evenInt) =$ foldC) `shouldBe` filter evenInt input prop "iterM" $ \input -> do (x, y) <- runWriterT $ yieldMany input $$ iterMC (tell . return) =$ sinkList x `shouldBe` (input :: [Int]) y `shouldBe` input prop "scanlM" $ \input seed -> let f a b = a + b :: Int fm a b = return $ a + b res = runIdentity $ yieldMany input $$ scanlMC fm seed =$ sinkList in res `shouldBe` scanl f seed input prop "mapAccumWhileM" $ \input (min 20 -> highest) -> let f i accum | i < highest = Right (i + accum, 2 * i :: Int) | otherwise = Left accum res = runIdentity $ yieldMany input $$ do (s, x) <- fuseBoth (mapAccumWhileMC ((return.).f) 0) sinkList y <- sinkList return (s, x, y) (taken, dropped) = span (< highest) input in res `shouldBe` (sum taken, map (* 2) taken, tailSafe dropped) prop "concatMapAccumM" $ \(input :: [Int]) -> let f a accum = (a + accum, [a, accum]) res = runIdentity $ yieldMany input $$ concatMapAccumMC ((return.).f) 0 =$ sinkList expected = concat $ snd $ mapAccumL (flip f) 0 input in res `shouldBe` expected prop "encode UTF8" $ \(map T.pack -> inputs) -> do let expected = encodeUtf8 $ fromChunks inputs actual <- yieldMany inputs $$ encodeUtf8C =$ sinkLazy actual `shouldBe` expected prop "encode/decode UTF8" $ \(map T.pack -> inputs) (min 50 . max 1 . abs -> chunkSize) -> do let expected = fromChunks inputs actual <- yieldMany inputs $$ encodeUtf8C =$ concatC =$ conduitVector chunkSize =$ mapC (S.pack . V.toList) =$ decodeUtf8C =$ sinkLazy actual `shouldBe` expected prop "encode/decode UTF8 lenient" $ \(map T.pack -> inputs) (min 50 . max 1 . abs -> chunkSize) -> do let expected = fromChunks inputs actual <- yieldMany inputs $$ encodeUtf8C =$ concatC =$ conduitVector chunkSize =$ mapC (S.pack . V.toList) =$ decodeUtf8LenientC =$ sinkLazy actual `shouldBe` expected prop "line" $ \(map T.pack -> input) size -> let src = yieldMany input sink = do x <- lineC $ takeCE size =$ foldC y <- foldC return (x, y) res = runIdentity $ src $$ sink expected = let (x, y) = T.break (== '\n') (T.concat input) in (T.take size x, T.drop 1 y) in res `shouldBe` expected prop "lineAscii" $ \(map S.pack -> input) size -> let src = yieldMany input sink = do x <- lineAsciiC $ takeCE size =$ foldC y <- foldC return (x, y) res = runIdentity $ src $$ sink expected = let (x, y) = S.break (== 10) (S.concat input) in (S.take size x, S.drop 1 y) in res `shouldBe` expected prop "unlines" $ \(map T.pack -> input) -> runIdentity (yieldMany input $$ unlinesC =$ foldC) `shouldBe` T.unlines input prop "unlinesAscii" $ \(map S.pack -> input) -> runIdentity (yieldMany input $$ unlinesAsciiC =$ foldC) `shouldBe` S8.unlines input prop "linesUnbounded" $ \(map T.pack -> input) -> runIdentity (yieldMany input $$ (linesUnboundedC >>= \() -> mempty) =$ sinkList) `shouldBe` T.lines (T.concat input) prop "linesUnboundedAscii" $ \(map S.pack -> input) -> runIdentity (yieldMany input $$ (linesUnboundedAsciiC >>= \() -> mempty) =$ sinkList) `shouldBe` S8.lines (S.concat input) prop "initReplicate" $ \seed delta (min 50 . abs -> cnt) -> do let sink = sumC res1 <- initReplicate (return seed) (return . (+ delta)) cnt $$ sink res1 `shouldBe` cnt * (seed + delta) res2 <- initReplicateConnect (return seed) (return . (+ delta)) cnt sink res2 `shouldBe` res1 prop "initReplicate" $ \seed delta (min 50 . abs -> cnt) -> do let sink = takeC cnt =$ sumC res1 <- initRepeat (return seed) (return . (+ delta)) $$ sink res1 `shouldBe` cnt * (seed + delta) res2 <- initRepeatConnect (return seed) (return . (+ delta)) sink res2 `shouldBe` res1 it "slidingWindow 0" $ let res = runIdentity $ yieldMany [1..5] $= slidingWindow 0 $$ sinkList in res `shouldBe` [[1],[2],[3],[4],[5]] it "slidingWindow 1" $ let res = runIdentity $ yieldMany [1..5] $= slidingWindow 1 $$ sinkList in res `shouldBe` [[1],[2],[3],[4],[5]] it "slidingWindow 2" $ let res = runIdentity $ yieldMany [1..5] $= slidingWindow 2 $$ sinkList in res `shouldBe` [[1,2],[2,3],[3,4],[4,5]] it "slidingWindow 3" $ let res = runIdentity $ yieldMany [1..5] $= slidingWindow 3 $$ sinkList in res `shouldBe` [[1,2,3],[2,3,4],[3,4,5]] it "slidingWindow 4" $ let res = runIdentity $ yieldMany [1..5] $= slidingWindow 4 $$ sinkList in res `shouldBe` [[1,2,3,4],[2,3,4,5]] it "slidingWindow 5" $ let res = runIdentity $ yieldMany [1..5] $= slidingWindow 5 $$ sinkList in res `shouldBe` [[1,2,3,4,5]] it "slidingWindow 6" $ let res = runIdentity $ yieldMany [1..5] $= slidingWindow 6 $$ sinkList in res `shouldBe` [[1,2,3,4,5]] it "chunksOfE 1" $ let res = runIdentity $ yieldMany [[1,2], [3,4], [5,6]] $= chunksOfE 3 $$ sinkList in res `shouldBe` [[1,2,3], [4,5,6]] it "chunksOfE 2 (last smaller)" $ let res = runIdentity $ yieldMany [[1,2], [3,4], [5,6,7]] $= chunksOfE 3 $$ sinkList in res `shouldBe` [[1,2,3], [4,5,6], [7]] it "chunksOfE (ByteString)" $ let res = runIdentity $ yieldMany [S8.pack "01234", "56789ab", "cdef", "h"] $= chunksOfE 4 $$ sinkList in res `shouldBe` ["0123", "4567", "89ab", "cdef", "h"] it "chunksOfExactlyE 1" $ let res = runIdentity $ yieldMany [[1,2], [3,4], [5,6]] $= chunksOfExactlyE 3 $$ sinkList in res `shouldBe` [[1,2,3], [4,5,6]] it "chunksOfExactlyE 2 (last smaller; thus not yielded)" $ let res = runIdentity $ yieldMany [[1,2], [3,4], [5,6,7]] $= chunksOfExactlyE 3 $$ sinkList in res `shouldBe` [[1,2,3], [4,5,6]] prop "vectorBuilder" $ \(values :: [[Int]]) ((+1) . (`mod` 30) . abs -> size) -> do let res = runST $ yieldMany values $$ vectorBuilderC size mapM_CE =$ sinkList expected = loop $ concat values where loop [] = [] loop x = VU.fromList y : loop z where (y, z) = splitAt size x res `shouldBe` expected prop "mapAccumS" $ \input -> let ints = [1..] f a s = liftM (:s) $ mapC (* a) =$ takeC a =$ sinkList res = reverse $ runIdentity $ yieldMany input $$ mapAccumS f [] (yieldMany ints) expected = loop input ints where loop [] _ = [] loop (a:as) xs = let (y, ys) = Prelude.splitAt a xs in map (* a) y : loop as ys in res `shouldBe` expected prop "peekForever" $ \(strs' :: [String]) -> do let strs = filter (not . null) strs' res1 <- yieldMany strs $$ linesUnboundedC =$ sinkList res2 <- yieldMany strs $$ peekForever (lineC $ foldC >>= yield) =$ sinkList res2 `shouldBe` res1 prop "peekForeverE" $ \(strs :: [String]) -> do res1 <- yieldMany strs $$ linesUnboundedC =$ sinkList res2 <- yieldMany strs $$ peekForeverE (lineC $ foldC >>= yield) =$ sinkList res2 `shouldBe` res1 StreamSpec.spec evenInt :: Int -> Bool evenInt = even elemInt :: Int -> [Int] -> Bool elemInt = elem notElemInt :: Int -> [Int] -> Bool notElemInt = notElem addM :: Monad m => Int -> Int -> m Int addM x y = return (x + y) succChar :: Char -> Char succChar = succ showInt :: Int -> String showInt = Prelude.show nocrBL :: L8.ByteString -> L8.ByteString nocrBL = L8.filter (/= '\r') conduit-combinators-1.1.2/test/StreamSpec.hs0000644000000000000000000004667013041073402017254 0ustar0000000000000000{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module StreamSpec where import Control.Arrow (first) import Control.Applicative import qualified Control.Monad import Control.Monad (liftM) import Control.Monad.Identity (Identity, runIdentity) import Control.Monad.State (StateT(..), get, put) import Data.Conduit import Data.Conduit.Combinators import Data.Conduit.Combinators.Internal import Data.Conduit.Combinators.Stream import Data.Conduit.Internal.Fusion import Data.Conduit.Internal.List.Stream (takeS, sourceListS, mapS) import Data.Conduit.List (consume, isolate, sourceList) import qualified Data.List import Data.MonoTraversable import Data.Monoid (Monoid(..)) import qualified Data.NonNull as NonNull import Data.Sequence (Seq) import qualified Data.Sequences as Seq import qualified Data.Text.Lazy as TL import Data.Vector (Vector) import qualified Prelude import Prelude ((.), ($), (>>=), (=<<), return, id, Maybe(..), Either(..), Monad, Bool(..), Int, Eq, Show, String, Functor, fst, snd, either) import qualified Safe import System.Directory (removeFile) import qualified System.IO as IO import System.IO.Unsafe import Test.Hspec import Test.QuickCheck spec :: Spec spec = do describe "Comparing list function to" $ do qit "yieldMany" $ \(mono :: Seq Int) -> yieldMany mono `checkProducer` otoList mono qit "yieldManyS" $ \(mono :: Seq Int) -> yieldManyS mono `checkStreamProducer` otoList mono qit "repeatM" $ \(getBlind -> (f :: M Int)) -> repeatM f `checkInfiniteProducerM` repeatML f qit "repeatMS" $ \(getBlind -> (f :: M Int)) -> repeatMS f `checkInfiniteStreamProducerM` repeatML f qit "repeatWhileM" $ \(getBlind -> (f :: M Int), getBlind -> g) -> repeatWhileM f g `checkInfiniteProducerM` repeatWhileML f g qit "repeatWhileMS" $ \(getBlind -> (f :: M Int), getBlind -> g) -> repeatWhileMS f g `checkInfiniteStreamProducerM` repeatWhileML f g qit "foldl1" $ \(getBlind -> f) -> foldl1 f `checkConsumer` foldl1L f qit "foldl1S" $ \(getBlind -> f) -> foldl1S f `checkStreamConsumer` foldl1L f qit "all" $ \(getBlind -> f) -> all f `checkConsumer` Prelude.all f qit "allS" $ \(getBlind -> f) -> allS f `checkStreamConsumer` Prelude.all f qit "any" $ \(getBlind -> f) -> any f `checkConsumer` Prelude.any f qit "anyS" $ \(getBlind -> f) -> anyS f `checkStreamConsumer` Prelude.any f qit "last" $ \() -> last `checkConsumer` Safe.lastMay qit "lastS" $ \() -> lastS `checkStreamConsumer` Safe.lastMay qit "lastE" $ \(getBlind -> f) -> let g x = Seq.replicate (Prelude.abs (getSmall (f x))) x :: Seq Int in (map g =$= lastE) `checkConsumer` (lastEL . Prelude.map g :: [Int] -> Maybe Int) qit "lastES" $ \(getBlind -> f) -> let g x = Seq.replicate (Prelude.abs (getSmall (f x))) x :: Seq Int in (lastES . mapS g) `checkStreamConsumer` (lastEL . Prelude.map g :: [Int] -> Maybe Int) qit "find" $ \(getBlind -> f) -> find f `checkConsumer` Data.List.find f qit "findS" $ \(getBlind -> f) -> findS f `checkStreamConsumer` Data.List.find f qit "concatMap" $ \(getBlind -> (f :: Int -> Seq Int)) -> concatMap f `checkConduit` concatMapL f qit "concatMapS" $ \(getBlind -> (f :: Int -> Seq Int)) -> concatMapS f `checkStreamConduit` concatMapL f qit "concatMapM" $ \(getBlind -> (f :: Int -> M (Seq Int))) -> concatMapM f `checkConduitM` concatMapML f qit "concatMapMS" $ \(getBlind -> (f :: Int -> M (Seq Int))) -> concatMapMS f `checkStreamConduitM` concatMapML f qit "concat" $ \() -> concat `checkConduit` (concatL :: [Seq Int] -> [Int]) qit "concatS" $ \() -> concatS `checkStreamConduit` (concatL :: [Seq Int] -> [Int]) qit "scanl" $ \(getBlind -> (f :: Int -> Int -> Int), initial) -> scanl f initial `checkConduit` Prelude.scanl f initial qit "scanlS" $ \(getBlind -> (f :: Int -> Int -> Int), initial) -> scanlS f initial `checkStreamConduit` Prelude.scanl f initial qit "scanlM" $ \(getBlind -> (f :: Int -> Int -> M Int), initial) -> scanlM f initial `checkConduitM` scanlML f initial qit "scanlMS" $ \(getBlind -> (f :: Int -> Int -> M Int), initial) -> scanlMS f initial `checkStreamConduitM` scanlML f initial qit "mapAccumWhileS" $ \(getBlind -> ( f :: Int -> [Int] -> Either [Int] ([Int], Int)) , initial :: [Int]) -> mapAccumWhileS f initial `checkStreamConduitResult` mapAccumWhileL f initial qit "mapAccumWhileMS" $ \(getBlind -> ( f :: Int -> [Int] -> M (Either [Int] ([Int], Int))) , initial :: [Int]) -> mapAccumWhileMS f initial `checkStreamConduitResultM` mapAccumWhileML f initial qit "intersperse" $ \(sep :: Int) -> intersperse sep `checkConduit` Data.List.intersperse sep qit "intersperseS" $ \(sep :: Int) -> intersperseS sep `checkStreamConduit` Data.List.intersperse sep qit "filterM" $ \(getBlind -> (f :: Int -> M Bool)) -> filterM f `checkConduitM` Control.Monad.filterM f qit "filterMS" $ \(getBlind -> (f :: Int -> M Bool)) -> filterMS f `checkStreamConduitM` Control.Monad.filterM f describe "comparing normal conduit function to" $ do qit "slidingWindowS" $ \(getSmall -> n) -> slidingWindowS n `checkStreamConduit` (\xs -> runIdentity $ sourceList xs $= preventFusion (slidingWindow n) $$ consume :: [Seq Int]) qit "splitOnUnboundedES" $ \(getBlind -> (f :: Int -> Bool)) -> splitOnUnboundedES f `checkStreamConduit` (\xs -> runIdentity $ sourceList xs $= preventFusion (splitOnUnboundedE f) $$ consume :: [Seq Int]) qit "initReplicateS" $ \(getBlind -> (mseed :: M Int), getBlind -> (f :: Int -> M Int), getSmall -> cnt) -> initReplicateS mseed f cnt `checkStreamProducerM` (preventFusion (initReplicate mseed f cnt) $$ consume) qit "initRepeatS" $ \(getBlind -> (mseed :: M Int), getBlind -> (f :: Int -> M Int)) -> initRepeatS mseed f `checkInfiniteStreamProducerM` (preventFusion (initRepeat mseed f) $= take 10 $$ consume) qit "sinkVectorS" $ \() -> checkStreamConsumerM' unsafePerformIO (sinkVectorS :: forall o. StreamConduitM Int o IO.IO (Vector Int)) (\xs -> sourceList xs $$ preventFusion sinkVector) qit "sinkVectorNS" $ \(getSmall . getNonNegative -> n) -> checkStreamConsumerM' unsafePerformIO (sinkVectorNS n :: forall o. StreamConduitM Int o IO.IO (Vector Int)) (\xs -> sourceList xs $$ preventFusion (sinkVectorN n)) #if !MIN_VERSION_QuickCheck(2,8,2) instance Arbitrary a => Arbitrary (Seq a) where arbitrary = Seq.fromList <$> arbitrary #endif repeatML :: Monad m => m a -> m [a] repeatML = Prelude.sequence . Prelude.repeat repeatWhileML :: Monad m => m a -> (a -> Bool) -> m [a] repeatWhileML m f = go where go = do x <- m if f x then liftM (x:) go else return [] foldl1L :: (a -> a -> a) -> [a] -> Maybe a foldl1L _ [] = Nothing foldl1L f xs = Just $ Prelude.foldl1 f xs lastEL :: Seq.IsSequence seq => [seq] -> Maybe (Element seq) lastEL = Prelude.foldl go Nothing where go _ (NonNull.fromNullable -> Just l) = Just (NonNull.last l) go mlast _ = mlast concatMapL :: MonoFoldable mono => (a -> mono) -> [a] -> [Element mono] concatMapL f = Prelude.concatMap (otoList . f) concatMapML :: (Monad m, MonoFoldable mono) => (a -> m mono) -> [a] -> m [Element mono] concatMapML f = liftM (Prelude.concatMap otoList) . Prelude.mapM f concatL :: MonoFoldable mono => [mono] -> [Element mono] concatL = Prelude.concatMap otoList scanlML :: Monad m => (a -> b -> m a) -> a -> [b] -> m [a] scanlML f = go where go l [] = return [l] go l (r:rs) = do l' <- f l r liftM (l:) (go l' rs) mapAccumWhileL :: (a -> s -> Either s (s, b)) -> s -> [a] -> ([b], s) mapAccumWhileL f = (runIdentity.) . mapAccumWhileML ((return.) . f) mapAccumWhileML :: Monad m => (a -> s -> m (Either s (s, b))) -> s -> [a] -> m ([b], s) mapAccumWhileML f = go where go s [] = return ([], s) go s (a:as) = f a s >>= either (return . ([], )) (\(s', b) -> liftM (first (b:)) $ go s' as) --FIXME: the following code is directly copied from the conduit test --suite. How to share this code?? qit :: (Arbitrary a, Testable prop, Show a) => String -> (a -> prop) -> Spec qit n f = it n $ property $ forAll arbitrary f -------------------------------------------------------------------------------- -- Quickcheck utilities for pure conduits / streams checkProducer :: (Show a, Eq a) => Source Identity a -> [a] -> Property checkProducer c l = checkProducerM' runIdentity c (return l) checkStreamProducer :: (Show a, Eq a) => StreamSource Identity a -> [a] -> Property checkStreamProducer s l = checkStreamProducerM' runIdentity s (return l) checkInfiniteProducer :: (Show a, Eq a) => Source Identity a -> [a] -> Property checkInfiniteProducer c l = checkInfiniteProducerM' runIdentity c (return l) checkInfiniteStreamProducer :: (Show a, Eq a) => StreamSource Identity a -> [a] -> Property checkInfiniteStreamProducer s l = checkInfiniteStreamProducerM' runIdentity s (return l) checkConsumer :: (Show b, Eq b) => Consumer Int Identity b -> ([Int] -> b) -> Property checkConsumer c l = checkConsumerM' runIdentity c (return . l) checkStreamConsumer :: (Show b, Eq b) => StreamConsumer Int Identity b -> ([Int] -> b) -> Property checkStreamConsumer c l = checkStreamConsumerM' runIdentity c (return . l) checkConduit :: (Show a, Arbitrary a, Show b, Eq b) => Conduit a Identity b -> ([a] -> [b]) -> Property checkConduit c l = checkConduitM' runIdentity c (return . l) checkStreamConduit :: (Show a, Arbitrary a, Show b, Eq b) => StreamConduit a Identity b -> ([a] -> [b]) -> Property checkStreamConduit c l = checkStreamConduitM' runIdentity c (return . l) -- checkConduitResult :: (Show a, Arbitrary a, Show b, Eq b, Show r, Eq r) => ConduitM a b Identity r -> ([a] -> ([b], r)) -> Property -- checkConduitResult c l = checkConduitResultM' runIdentity c (return . l) checkStreamConduitResult :: (Show a, Arbitrary a, Show b, Eq b, Show r, Eq r) => StreamConduitM a b Identity r -> ([a] -> ([b], r)) -> Property checkStreamConduitResult c l = checkStreamConduitResultM' runIdentity c (return . l) -------------------------------------------------------------------------------- -- Quickcheck utilities for conduits / streams in the M monad. checkProducerM :: (Show a, Eq a) => Source M a -> M [a] -> Property checkProducerM = checkProducerM' runM checkStreamProducerM :: (Show a, Eq a) => StreamSource M a -> M [a] -> Property checkStreamProducerM = checkStreamProducerM' runM checkInfiniteProducerM :: (Show a, Eq a) => Source M a -> M [a] -> Property checkInfiniteProducerM = checkInfiniteProducerM' (fst . runM) checkInfiniteStreamProducerM :: (Show a, Eq a) => StreamSource M a -> M [a] -> Property checkInfiniteStreamProducerM = checkInfiniteStreamProducerM' (fst . runM) checkConsumerM :: (Show b, Eq b) => Consumer Int M b -> ([Int] -> M b) -> Property checkConsumerM = checkConsumerM' runM checkStreamConsumerM :: (Show b, Eq b) => StreamConsumer Int M b -> ([Int] -> M b) -> Property checkStreamConsumerM = checkStreamConsumerM' runM checkConduitM :: (Show a, Arbitrary a, Show b, Eq b) => Conduit a M b -> ([a] -> M [b]) -> Property checkConduitM = checkConduitM' runM checkStreamConduitM :: (Show a, Arbitrary a, Show b, Eq b) => StreamConduit a M b -> ([a] -> M [b]) -> Property checkStreamConduitM = checkStreamConduitM' runM -- checkConduitResultM :: (Show a, Arbitrary a, Show b, Eq b, Show r, Eq r) => ConduitM a b M r -> ([a] -> M ([b], r)) -> Property -- checkConduitResultM = checkConduitResultM' runM checkStreamConduitResultM :: (Show a, Arbitrary a, Show b, Eq b, Show r, Eq r) => StreamConduitM a b M r -> ([a] -> M ([b], r)) -> Property checkStreamConduitResultM = checkStreamConduitResultM' runM -------------------------------------------------------------------------------- -- Quickcheck utilities for monadic streams / conduits -- These are polymorphic in which Monad is used. checkProducerM' :: (Show a, Monad m, Show b, Eq b) => (m [a] -> b) -> Source m a -> m [a] -> Property checkProducerM' f c l = f (preventFusion c $$ consume) === f l checkStreamProducerM' :: (Show a, Monad m, Show b, Eq b) => (m [a] -> b) -> StreamSource m a -> m [a] -> Property checkStreamProducerM' f s l = f (liftM fst $ evalStream $ s emptyStream) === f l checkInfiniteProducerM' :: (Show a, Monad m, Show b, Eq b) => (m [a] -> b) -> Source m a -> m [a] -> Property checkInfiniteProducerM' f s l = checkProducerM' f (preventFusion s $= isolate 10) (liftM (Prelude.take 10) l) checkInfiniteStreamProducerM' :: (Show a, Monad m, Show b, Eq b) => (m [a] -> b) -> StreamSource m a -> m [a] -> Property checkInfiniteStreamProducerM' f s l = f (liftM snd $ evalStream $ takeS 10 $ s emptyStream) === f (liftM (Prelude.take 10) l) checkConsumerM' :: (Show a, Monad m, Show b, Eq b) => (m a -> b) -> Consumer Int m a -> ([Int] -> m a) -> Property checkConsumerM' f c l = forAll arbitrary $ \xs -> f (sourceList xs $$ preventFusion c) === f (l xs) checkStreamConsumerM' :: (Show a, Monad m, Show b, Eq b) => (m a -> b) -> StreamConsumer Int m a -> ([Int] -> m a) -> Property checkStreamConsumerM' f s l = forAll (arbitrary) $ \xs -> f (liftM snd $ evalStream $ s $ sourceListS xs emptyStream) === f (l xs) checkConduitM' :: (Show a, Arbitrary a, Monad m, Show c, Eq c) => (m [b] -> c) -> Conduit a m b -> ([a] -> m [b]) -> Property checkConduitM' f c l = forAll arbitrary $ \xs -> f (sourceList xs $= preventFusion c $$ consume) === f (l xs) checkStreamConduitM' :: (Show a, Arbitrary a, Monad m, Show c, Eq c) => (m [b] -> c) -> StreamConduit a m b -> ([a] -> m [b]) -> Property checkStreamConduitM' f s l = forAll arbitrary $ \xs -> f (liftM fst $ evalStream $ s $ sourceListS xs emptyStream) === f (l xs) -- TODO: Fixing this would allow comparing conduit consumers against -- their list versions. -- -- checkConduitResultM' :: (Show a, Arbitrary a, Monad m, Show c, Eq c) -- => (m ([b], r) -> c) -- -> ConduitM a b m r -- -> ([a] -> m ([b], r)) -- -> Property -- checkConduitResultM' f c l = FIXME forAll arbitrary $ \xs -> -- f (sourceList xs $= preventFusion c $$ consume) -- === -- f (l xs) checkStreamConduitResultM' :: (Show a, Arbitrary a, Monad m, Show c, Eq c) => (m ([b], r) -> c) -> StreamConduitM a b m r -> ([a] -> m ([b], r)) -> Property checkStreamConduitResultM' f s l = forAll arbitrary $ \xs -> f (evalStream $ s $ sourceListS xs emptyStream) === f (l xs) emptyStream :: Monad m => Stream m () () emptyStream = Stream (\_ -> return $ Stop ()) (return ()) evalStream :: Monad m => Stream m o r -> m ([o], r) evalStream (Stream step s0) = go =<< s0 where go s = do res <- step s case res of Stop r -> return ([], r) Skip s' -> go s' Emit s' x -> liftM (\(l, r) -> (x:l, r)) (go s') -------------------------------------------------------------------------------- -- Misc utilities -- Prefer this to creating an orphan instance for Data.Monoid.Sum: newtype Sum a = Sum a deriving (Eq, Show, Arbitrary) instance Prelude.Num a => Monoid (Sum a) where mempty = Sum 0 mappend (Sum x) (Sum y) = Sum $ x Prelude.+ y preventFusion :: a -> a preventFusion = id {-# INLINE [0] preventFusion #-} newtype M a = M (StateT Int Identity a) deriving (Functor, Applicative, Monad) instance Arbitrary a => Arbitrary (M a) where arbitrary = do f <- arbitrary return $ do s <- M get let (x, s') = f s M (put s') return x runM :: M a -> (a, Int) runM (M m) = runIdentity $ runStateT m 0 -------------------------------------------------------------------------------- -- Utilities from QuickCheck-2.7 (absent in earlier versions) #if !MIN_VERSION_QuickCheck(2,7,0) getBlind :: Blind a -> a getBlind (Blind x) = x -- | @Small x@: generates values of @x@ drawn from a small range. -- The opposite of 'Large'. newtype Small a = Small {getSmall :: a} deriving (Prelude.Ord, Prelude.Eq, Prelude.Enum, Prelude.Show, Prelude.Num) instance Prelude.Integral a => Arbitrary (Small a) where arbitrary = Prelude.fmap Small arbitrarySizedIntegral shrink (Small x) = Prelude.map Small (shrinkIntegral x) (===) :: (Show a, Eq a) => a -> a -> Property x === y = whenFail (Prelude.fail $ Prelude.show x Prelude.++ " should match " Prelude.++ Prelude.show y) (x Prelude.== y) #endif conduit-combinators-1.1.2/LICENSE0000644000000000000000000000206612736421710014700 0ustar0000000000000000The MIT License (MIT) Copyright (c) 2014 FP Complete Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. conduit-combinators-1.1.2/Setup.hs0000644000000000000000000000005612736421710015324 0ustar0000000000000000import Distribution.Simple main = defaultMain conduit-combinators-1.1.2/conduit-combinators.cabal0000644000000000000000000000507413211222302020625 0ustar0000000000000000-- This file has been generated from package.yaml by hpack version 0.20.0. -- -- see: https://github.com/sol/hpack -- -- hash: c9fb108db74e0e70db397f63afc970b475b22ca7c0f48ebe17eafec927475bd7 name: conduit-combinators version: 1.1.2 synopsis: Commonly used conduit functions, for both chunked and unchunked data description: See docs and README at category: Data, Conduit homepage: https://github.com/snoyberg/mono-traversable#readme bug-reports: https://github.com/snoyberg/mono-traversable/issues author: Michael Snoyman maintainer: michael@snoyman.com license: MIT license-file: LICENSE build-type: Simple cabal-version: >= 1.10 extra-source-files: ChangeLog.md fusion-macros.h README.md test/subdir/dummyfile.txt source-repository head type: git location: https://github.com/snoyberg/mono-traversable flag monotrav1 description: Use mono-traversable 1.0 or later manual: False default: True library hs-source-dirs: src ghc-options: -Wall -O2 include-dirs: ./. build-depends: base >=4 && <5 , base16-bytestring , base64-bytestring >=0.1.1.1 , bytestring , conduit >=1.2.8 , conduit-extra >=1.1.1 , filepath , monad-control , mwc-random , primitive , resourcet , text , transformers , transformers-base , unix-compat , vector , void if flag(monotrav1) build-depends: chunked-data >=0.3 , mono-traversable >=1.0 else build-depends: chunked-data <0.3 , mono-traversable >=0.5 && <1.0 if os(windows) cpp-options: -DWINDOWS else build-depends: unix exposed-modules: Conduit Data.Conduit.Combinators Data.Conduit.Combinators.Internal Data.Conduit.Combinators.Stream other-modules: Data.Conduit.Combinators.Unqualified default-language: Haskell2010 test-suite test type: exitcode-stdio-1.0 main-is: Spec.hs hs-source-dirs: test ghc-options: -Wall cpp-options: -DTEST build-depends: QuickCheck >=2.5 , base , base16-bytestring , base64-bytestring , bytestring , chunked-data , conduit , conduit-combinators , containers , directory , filepath , hspec >=1.3 , mono-traversable , mtl , mwc-random , safe , silently , text , transformers , vector if os(windows) cpp-options: -DWINDOWS other-modules: StreamSpec Paths_conduit_combinators default-language: Haskell2010 conduit-combinators-1.1.2/ChangeLog.md0000644000000000000000000000265313211222300016025 0ustar0000000000000000# 1.1.2 * Add `chunksOfE` and `chunksOfExactlyE` combinators # 1.1.1 * Add `asum` combinator # 1.1.0 * Don't generalize I/O functions to `IOData`, instead specialize to `ByteString`. See: http://www.snoyman.com/blog/2016/12/beware-of-readfile#real-world-failures # 1.0.8.3 * Fix version bounds for chunked-data/mono-traversable combos # 1.0.8.2 * Fix foldl1 not being "a strict left fold" as advertised. [#115](https://github.com/snoyberg/mono-traversable/pull/115) # 1.0.8.1 * Break on single elements and defer monoid concatenation until yield [#111](https://github.com/snoyberg/mono-traversable/pull/111) # 1.0.8 * Add lower bound on conduit 1.2.8 (make it easier to follow [the reskin](http://www.snoyman.com/blog/2016/09/proposed-conduit-reskin). # 1.0.7 * Add `sourceFileBS` and `sinkFileBS` # 1.0.6 * Add `peekForeverE` combinator # 1.0.5 * Add head, headDef and lastDef combinators # 1.0.4 * Move into mono-traversable repo, support mono-traversable 1.0 # 1.0.3.1 * Support for QuickCheck 2.8.2 # 1.0.3 * sourceRandomWith [#19](https://github.com/fpco/conduit-combinators/pull/19) # 1.0.2 * Make mapAccumWhile & mapAccumS strict in accumulator state [#18](https://github.com/fpco/conduit-combinators/pull/18) # 1.0.1 * mapAccumWhile, mapAccumWhileM, mapAccumS # 1.0.0 * Drop system-filepath/system-fileio # 0.3.1 * `peekForever` # 0.3.0 Stream fusion enabled, drop compatibility with older conduit conduit-combinators-1.1.2/fusion-macros.h0000644000000000000000000000216412736421710016630 0ustar0000000000000000#define INLINE_RULE0(new,old) ;\ new = old ;\ {-# INLINE [0] new #-} ;\ {-# RULES "inline new" new = old #-} #define INLINE_RULE(new,vars,body) ;\ new vars = body ;\ {-# INLINE [0] new #-} ;\ {-# RULES "inline new" forall vars. new vars = body #-} #define STREAMING0(name, nameC, nameS) ;\ name = nameC ;\ {-# INLINE [0] name #-} ;\ {-# RULES "unstream name" \ name = unstream (streamConduit nameC nameS) \ #-} #define STREAMING(name, nameC, nameS, vars) ;\ name = nameC ;\ {-# INLINE [0] name #-} ;\ {-# RULES "unstream name" forall vars. \ name vars = unstream (streamConduit (nameC vars) (nameS vars)) \ #-} conduit-combinators-1.1.2/README.md0000644000000000000000000000044212736421710015146 0ustar0000000000000000conduit-combinators =================== Commonly used conduit functions, for both chunked and unchunked data. For more information about conduit in general, and how this package in particular fits into the ecosystem, see [the conduit homepage](https://github.com/snoyberg/conduit#readme). conduit-combinators-1.1.2/test/subdir/dummyfile.txt0000644000000000000000000000000012736421710020660 0ustar0000000000000000