1{-# OPTIONS_HADDOCK not-home #-}
2{-# LANGUAGE CPP #-}
3{-# LANGUAGE FlexibleContexts #-}
4{-# LANGUAGE RankNTypes #-}
5{-# LANGUAGE GADTs #-}
6{-# LANGUAGE MultiParamTypeClasses     #-}
7{-# LANGUAGE NoImplicitPrelude         #-}
8{-# LANGUAGE NoMonomorphismRestriction #-}
9module Data.Conduit.Combinators.Unqualified
10    ( -- ** Producers
11      -- *** Pure
12      CC.yieldMany
13    , unfoldC
14    , enumFromToC
15    , iterateC
16    , repeatC
17    , replicateC
18    , CC.sourceLazy
19
20      -- *** Monadic
21    , repeatMC
22    , repeatWhileMC
23    , replicateMC
24
25      -- *** I\/O
26    , CC.sourceFile
27    , CC.sourceFileBS
28    , CC.sourceHandle
29    , CC.sourceHandleUnsafe
30    , CC.sourceIOHandle
31    , stdinC
32    , CC.withSourceFile
33
34      -- *** Filesystem
35    , CC.sourceDirectory
36    , CC.sourceDirectoryDeep
37
38      -- ** Consumers
39      -- *** Pure
40    , dropC
41    , dropCE
42    , dropWhileC
43    , dropWhileCE
44    , foldC
45    , foldCE
46    , foldlC
47    , foldlCE
48    , foldMapC
49    , foldMapCE
50    , allC
51    , allCE
52    , anyC
53    , anyCE
54    , andC
55    , andCE
56    , orC
57    , orCE
58    , asumC
59    , elemC
60    , elemCE
61    , notElemC
62    , notElemCE
63    , CC.sinkLazy
64    , CC.sinkList
65    , CC.sinkVector
66    , CC.sinkVectorN
67    , CC.sinkLazyBuilder
68    , CC.sinkNull
69    , CC.awaitNonNull
70    , headC
71    , headDefC
72    , headCE
73    , peekC
74    , peekCE
75    , lastC
76    , lastDefC
77    , lastCE
78    , lengthC
79    , lengthCE
80    , lengthIfC
81    , lengthIfCE
82    , maximumC
83    , maximumCE
84    , minimumC
85    , minimumCE
86    , nullC
87    , nullCE
88    , sumC
89    , sumCE
90    , productC
91    , productCE
92    , findC
93
94      -- *** Monadic
95    , mapM_C
96    , mapM_CE
97    , foldMC
98    , foldMCE
99    , foldMapMC
100    , foldMapMCE
101
102      -- *** I\/O
103    , CC.sinkFile
104    , CC.sinkFileCautious
105    , CC.sinkTempFile
106    , CC.sinkSystemTempFile
107    , CC.sinkFileBS
108    , CC.sinkHandle
109    , CC.sinkIOHandle
110    , printC
111    , stdoutC
112    , stderrC
113    , CC.withSinkFile
114    , CC.withSinkFileBuilder
115    , CC.withSinkFileCautious
116    , CC.sinkHandleBuilder
117    , CC.sinkHandleFlush
118
119      -- ** Transformers
120      -- *** Pure
121    , mapC
122    , mapCE
123    , omapCE
124    , concatMapC
125    , concatMapCE
126    , takeC
127    , takeCE
128    , takeWhileC
129    , takeWhileCE
130    , takeExactlyC
131    , takeExactlyCE
132    , concatC
133    , filterC
134    , filterCE
135    , mapWhileC
136    , conduitVector
137    , scanlC
138    , mapAccumWhileC
139    , concatMapAccumC
140    , intersperseC
141    , slidingWindowC
142    , chunksOfCE
143    , chunksOfExactlyCE
144
145      -- *** Monadic
146    , mapMC
147    , mapMCE
148    , omapMCE
149    , concatMapMC
150    , filterMC
151    , filterMCE
152    , iterMC
153    , scanlMC
154    , mapAccumWhileMC
155    , concatMapAccumMC
156
157      -- *** Textual
158    , encodeUtf8C
159    , decodeUtf8C
160    , decodeUtf8LenientC
161    , lineC
162    , lineAsciiC
163    , unlinesC
164    , unlinesAsciiC
165    , linesUnboundedC
166    , linesUnboundedAsciiC
167
168      -- ** Builders
169    , CC.builderToByteString
170    , CC.unsafeBuilderToByteString
171    , CC.builderToByteStringWith
172    , CC.builderToByteStringFlush
173    , CC.builderToByteStringWithFlush
174    , CC.BufferAllocStrategy
175    , CC.allNewBuffersStrategy
176    , CC.reuseBufferStrategy
177
178      -- ** Special
179    , vectorBuilderC
180    , CC.mapAccumS
181    , CC.peekForever
182    , CC.peekForeverE
183    ) where
184
185-- BEGIN IMPORTS
186
187import qualified Data.Conduit.Combinators as CC
188-- BEGIN IMPORTS
189
190import qualified Data.Traversable
191import           Control.Applicative         (Alternative)
192import           Control.Monad.IO.Class      (MonadIO (..))
193import           Control.Monad.Primitive     (PrimMonad, PrimState)
194import           Control.Monad.Trans.Resource (MonadThrow)
195import           Data.Conduit
196import           Data.Monoid                 (Monoid (..))
197import           Data.MonoTraversable
198import qualified Data.Sequences              as Seq
199import qualified Data.Vector.Generic         as V
200import           Prelude                     (Bool (..), Eq (..), Int,
201                                              Maybe (..), Monad (..), Num (..),
202                                              Ord (..), Functor (..), Either (..),
203                                              Enum, Show, Char)
204import Data.Word (Word8)
205import Data.ByteString (ByteString)
206import Data.Text (Text)
207
208import qualified Data.Sequences as DTE
209
210
211-- END IMPORTS
212
213-- | Generate a producer from a seed value.
214--
215-- @since 1.3.0
216unfoldC :: Monad m
217       => (b -> Maybe (a, b))
218       -> b
219       -> ConduitT i a m ()
220unfoldC = CC.unfold
221{-# INLINE unfoldC #-}
222
223-- | Enumerate from a value to a final value, inclusive, via 'succ'.
224--
225-- This is generally more efficient than using @Prelude@\'s @enumFromTo@ and
226-- combining with @sourceList@ since this avoids any intermediate data
227-- structures.
228--
229-- @since 1.3.0
230enumFromToC :: (Monad m, Enum a, Ord a) => a -> a -> ConduitT i a m ()
231enumFromToC = CC.enumFromTo
232{-# INLINE enumFromToC #-}
233
234-- | Produces an infinite stream of repeated applications of f to x.
235--
236-- @since 1.3.0
237iterateC :: Monad m => (a -> a) -> a -> ConduitT i a m ()
238iterateC = CC.iterate
239{-# INLINE iterateC #-}
240
241-- | Produce an infinite stream consisting entirely of the given value.
242--
243-- @since 1.3.0
244repeatC :: Monad m => a -> ConduitT i a m ()
245repeatC = CC.repeat
246{-# INLINE repeatC #-}
247
248-- | Produce a finite stream consisting of n copies of the given value.
249--
250-- @since 1.3.0
251replicateC :: Monad m
252          => Int
253          -> a
254          -> ConduitT i a m ()
255replicateC = CC.replicate
256{-# INLINE replicateC #-}
257
258-- | Repeatedly run the given action and yield all values it produces.
259--
260-- @since 1.3.0
261repeatMC :: Monad m
262        => m a
263        -> ConduitT i a m ()
264repeatMC = CC.repeatM
265{-# INLINE repeatMC #-}
266
267-- | Repeatedly run the given action and yield all values it produces, until
268-- the provided predicate returns @False@.
269--
270-- @since 1.3.0
271repeatWhileMC :: Monad m
272             => m a
273             -> (a -> Bool)
274             -> ConduitT i a m ()
275repeatWhileMC = CC.repeatWhileM
276{-# INLINE repeatWhileMC #-}
277
278-- | Perform the given action n times, yielding each result.
279--
280-- @since 1.3.0
281replicateMC :: Monad m
282           => Int
283           -> m a
284           -> ConduitT i a m ()
285replicateMC = CC.replicateM
286{-# INLINE replicateMC #-}
287
288-- | @sourceHandle@ applied to @stdin@.
289--
290-- @since 1.3.0
291stdinC :: MonadIO m => ConduitT i ByteString m ()
292stdinC = CC.stdin
293{-# INLINE stdinC #-}
294
295-- | Ignore a certain number of values in the stream.
296--
297-- Note: since this function doesn't produce anything, you probably want to
298-- use it with ('>>') instead of directly plugging it into a pipeline:
299--
300-- >>> runConduit $ yieldMany [1..5] .| dropC 2 .| sinkList
301-- []
302-- >>> runConduit $ yieldMany [1..5] .| (dropC 2 >> sinkList)
303-- [3,4,5]
304--
305-- @since 1.3.0
306dropC :: Monad m
307     => Int
308     -> ConduitT a o m ()
309dropC = CC.drop
310{-# INLINE dropC #-}
311
312-- | Drop a certain number of elements from a chunked stream.
313--
314-- Note: you likely want to use it with monadic composition. See the docs
315-- for 'dropC'.
316--
317-- @since 1.3.0
318dropCE :: (Monad m, Seq.IsSequence seq)
319      => Seq.Index seq
320      -> ConduitT seq o m ()
321dropCE = CC.dropE
322{-# INLINE dropCE #-}
323
324-- | Drop all values which match the given predicate.
325--
326-- Note: you likely want to use it with monadic composition. See the docs
327-- for 'dropC'.
328--
329-- @since 1.3.0
330dropWhileC :: Monad m
331          => (a -> Bool)
332          -> ConduitT a o m ()
333dropWhileC = CC.dropWhile
334{-# INLINE dropWhileC #-}
335
336-- | Drop all elements in the chunked stream which match the given predicate.
337--
338-- Note: you likely want to use it with monadic composition. See the docs
339-- for 'dropC'.
340--
341-- @since 1.3.0
342dropWhileCE :: (Monad m, Seq.IsSequence seq)
343           => (Element seq -> Bool)
344           -> ConduitT seq o m ()
345dropWhileCE = CC.dropWhileE
346{-# INLINE dropWhileCE #-}
347
348-- | Monoidally combine all values in the stream.
349--
350-- @since 1.3.0
351foldC :: (Monad m, Monoid a)
352     => ConduitT a o m a
353foldC = CC.fold
354{-# INLINE foldC #-}
355
356-- | Monoidally combine all elements in the chunked stream.
357--
358-- @since 1.3.0
359foldCE :: (Monad m, MonoFoldable mono, Monoid (Element mono))
360      => ConduitT mono o m (Element mono)
361foldCE = CC.foldE
362{-# INLINE foldCE #-}
363
364-- | A strict left fold.
365--
366-- @since 1.3.0
367foldlC :: Monad m => (a -> b -> a) -> a -> ConduitT b o m a
368foldlC = CC.foldl
369{-# INLINE foldlC #-}
370
371-- | A strict left fold on a chunked stream.
372--
373-- @since 1.3.0
374foldlCE :: (Monad m, MonoFoldable mono)
375       => (a -> Element mono -> a)
376       -> a
377       -> ConduitT mono o m a
378foldlCE = CC.foldlE
379{-# INLINE foldlCE #-}
380
381-- | Apply the provided mapping function and monoidal combine all values.
382--
383-- @since 1.3.0
384foldMapC :: (Monad m, Monoid b)
385        => (a -> b)
386        -> ConduitT a o m b
387foldMapC = CC.foldMap
388{-# INLINE foldMapC #-}
389
390-- | Apply the provided mapping function and monoidal combine all elements of the chunked stream.
391--
392-- @since 1.3.0
393foldMapCE :: (Monad m, MonoFoldable mono, Monoid w)
394         => (Element mono -> w)
395         -> ConduitT mono o m w
396foldMapCE = CC.foldMapE
397{-# INLINE foldMapCE #-}
398
399-- | Check that all values in the stream return True.
400--
401-- Subject to shortcut logic: at the first False, consumption of the stream
402-- will stop.
403--
404-- @since 1.3.0
405allC :: Monad m
406    => (a -> Bool)
407    -> ConduitT a o m Bool
408allC = CC.all
409{-# INLINE allC #-}
410
411-- | Check that all elements in the chunked stream return True.
412--
413-- Subject to shortcut logic: at the first False, consumption of the stream
414-- will stop.
415--
416-- @since 1.3.0
417allCE :: (Monad m, MonoFoldable mono)
418     => (Element mono -> Bool)
419     -> ConduitT mono o m Bool
420allCE = CC.allE
421{-# INLINE allCE #-}
422
423-- | Check that at least one value in the stream returns True.
424--
425-- Subject to shortcut logic: at the first True, consumption of the stream
426-- will stop.
427--
428-- @since 1.3.0
429anyC :: Monad m
430    => (a -> Bool)
431    -> ConduitT a o m Bool
432anyC = CC.any
433{-# INLINE anyC #-}
434
435-- | Check that at least one element in the chunked stream returns True.
436--
437-- Subject to shortcut logic: at the first True, consumption of the stream
438-- will stop.
439--
440-- @since 1.3.0
441anyCE :: (Monad m, MonoFoldable mono)
442     => (Element mono -> Bool)
443     -> ConduitT mono o m Bool
444anyCE = CC.anyE
445{-# INLINE anyCE #-}
446
447-- | Are all values in the stream True?
448--
449-- Consumption stops once the first False is encountered.
450--
451-- @since 1.3.0
452andC :: Monad m => ConduitT Bool o m Bool
453andC = CC.and
454{-# INLINE andC #-}
455
456-- | Are all elements in the chunked stream True?
457--
458-- Consumption stops once the first False is encountered.
459--
460-- @since 1.3.0
461andCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool)
462     => ConduitT mono o m Bool
463andCE = CC.andE
464{-# INLINE andCE #-}
465
466-- | Are any values in the stream True?
467--
468-- Consumption stops once the first True is encountered.
469--
470-- @since 1.3.0
471orC :: Monad m => ConduitT Bool o m Bool
472orC = CC.or
473{-# INLINE orC #-}
474
475-- | Are any elements in the chunked stream True?
476--
477-- Consumption stops once the first True is encountered.
478--
479-- @since 1.3.0
480orCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool)
481    => ConduitT mono o m Bool
482orCE = CC.orE
483{-# INLINE orCE #-}
484
485-- | 'Alternative'ly combine all values in the stream.
486--
487-- @since 1.3.0
488asumC :: (Monad m, Alternative f) => ConduitT (f a) o m (f a)
489asumC = CC.asum
490
491-- | Are any values in the stream equal to the given value?
492--
493-- Stops consuming as soon as a match is found.
494--
495-- @since 1.3.0
496elemC :: (Monad m, Eq a) => a -> ConduitT a o m Bool
497elemC = CC.elem
498{-# INLINE elemC #-}
499
500-- | Are any elements in the chunked stream equal to the given element?
501--
502-- Stops consuming as soon as a match is found.
503--
504-- @since 1.3.0
505#if MIN_VERSION_mono_traversable(1,0,0)
506elemCE :: (Monad m, Seq.IsSequence seq, Eq (Element seq))
507#else
508elemCE :: (Monad m, Seq.EqSequence seq)
509#endif
510      => Element seq
511      -> ConduitT seq o m Bool
512elemCE = CC.elemE
513{-# INLINE elemCE #-}
514
515-- | Are no values in the stream equal to the given value?
516--
517-- Stops consuming as soon as a match is found.
518--
519-- @since 1.3.0
520notElemC :: (Monad m, Eq a) => a -> ConduitT a o m Bool
521notElemC = CC.notElem
522{-# INLINE notElemC #-}
523
524-- | Are no elements in the chunked stream equal to the given element?
525--
526-- Stops consuming as soon as a match is found.
527--
528-- @since 1.3.0
529#if MIN_VERSION_mono_traversable(1,0,0)
530notElemCE :: (Monad m, Seq.IsSequence seq, Eq (Element seq))
531#else
532notElemCE :: (Monad m, Seq.EqSequence seq)
533#endif
534         => Element seq
535         -> ConduitT seq o m Bool
536notElemCE = CC.notElemE
537{-# INLINE notElemCE #-}
538
539-- | Take a single value from the stream, if available.
540--
541-- @since 1.3.0
542headC :: Monad m => ConduitT a o m (Maybe a)
543headC = CC.head
544
545-- | Same as 'headC', but returns a default value if none are available from the stream.
546--
547-- @since 1.3.0
548headDefC :: Monad m => a -> ConduitT a o m a
549headDefC = CC.headDef
550
551-- | Get the next element in the chunked stream.
552--
553-- @since 1.3.0
554headCE :: (Monad m, Seq.IsSequence seq) => ConduitT seq o m (Maybe (Element seq))
555headCE = CC.headE
556{-# INLINE headCE #-}
557
558-- | View the next value in the stream without consuming it.
559--
560-- @since 1.3.0
561peekC :: Monad m => ConduitT a o m (Maybe a)
562peekC = CC.peek
563{-# INLINE peekC #-}
564
565-- | View the next element in the chunked stream without consuming it.
566--
567-- @since 1.3.0
568peekCE :: (Monad m, MonoFoldable mono) => ConduitT mono o m (Maybe (Element mono))
569peekCE = CC.peekE
570{-# INLINE peekCE #-}
571
572-- | Retrieve the last value in the stream, if present.
573--
574-- @since 1.3.0
575lastC :: Monad m => ConduitT a o m (Maybe a)
576lastC = CC.last
577{-# INLINE lastC #-}
578
579-- | Same as 'lastC', but returns a default value if none are available from the stream.
580--
581-- @since 1.3.0
582lastDefC :: Monad m => a -> ConduitT a o m a
583lastDefC = CC.lastDef
584
585-- | Retrieve the last element in the chunked stream, if present.
586--
587-- @since 1.3.0
588lastCE :: (Monad m, Seq.IsSequence seq) => ConduitT seq o m (Maybe (Element seq))
589lastCE = CC.lastE
590{-# INLINE lastCE #-}
591
592-- | Count how many values are in the stream.
593--
594-- @since 1.3.0
595lengthC :: (Monad m, Num len) => ConduitT a o m len
596lengthC = CC.length
597{-# INLINE lengthC #-}
598
599-- | Count how many elements are in the chunked stream.
600--
601-- @since 1.3.0
602lengthCE :: (Monad m, Num len, MonoFoldable mono) => ConduitT mono o m len
603lengthCE = CC.lengthE
604{-# INLINE lengthCE #-}
605
606-- | Count how many values in the stream pass the given predicate.
607--
608-- @since 1.3.0
609lengthIfC :: (Monad m, Num len) => (a -> Bool) -> ConduitT a o m len
610lengthIfC = CC.lengthIf
611{-# INLINE lengthIfC #-}
612
613-- | Count how many elements in the chunked stream pass the given predicate.
614--
615-- @since 1.3.0
616lengthIfCE :: (Monad m, Num len, MonoFoldable mono)
617          => (Element mono -> Bool) -> ConduitT mono o m len
618lengthIfCE = CC.lengthIfE
619{-# INLINE lengthIfCE #-}
620
621-- | Get the largest value in the stream, if present.
622--
623-- @since 1.3.0
624maximumC :: (Monad m, Ord a) => ConduitT a o m (Maybe a)
625maximumC = CC.maximum
626{-# INLINE maximumC #-}
627
628-- | Get the largest element in the chunked stream, if present.
629--
630-- @since 1.3.0
631#if MIN_VERSION_mono_traversable(1,0,0)
632maximumCE :: (Monad m, Seq.IsSequence seq, Ord (Element seq)) => ConduitT seq o m (Maybe (Element seq))
633#else
634maximumCE :: (Monad m, Seq.OrdSequence seq) => ConduitT seq o m (Maybe (Element seq))
635#endif
636maximumCE = CC.maximumE
637{-# INLINE maximumCE #-}
638
639-- | Get the smallest value in the stream, if present.
640--
641-- @since 1.3.0
642minimumC :: (Monad m, Ord a) => ConduitT a o m (Maybe a)
643minimumC = CC.minimum
644{-# INLINE minimumC #-}
645
646-- | Get the smallest element in the chunked stream, if present.
647--
648-- @since 1.3.0
649#if MIN_VERSION_mono_traversable(1,0,0)
650minimumCE :: (Monad m, Seq.IsSequence seq, Ord (Element seq)) => ConduitT seq o m (Maybe (Element seq))
651#else
652minimumCE :: (Monad m, Seq.OrdSequence seq) => ConduitT seq o m (Maybe (Element seq))
653#endif
654minimumCE = CC.minimumE
655{-# INLINE minimumCE #-}
656
657-- | True if there are no values in the stream.
658--
659-- This function does not modify the stream.
660--
661-- @since 1.3.0
662nullC :: Monad m => ConduitT a o m Bool
663nullC = CC.null
664{-# INLINE nullC #-}
665
666-- | True if there are no elements in the chunked stream.
667--
668-- This function may remove empty leading chunks from the stream, but otherwise
669-- will not modify it.
670--
671-- @since 1.3.0
672nullCE :: (Monad m, MonoFoldable mono)
673      => ConduitT mono o m Bool
674nullCE = CC.nullE
675{-# INLINE nullCE #-}
676
677-- | Get the sum of all values in the stream.
678--
679-- @since 1.3.0
680sumC :: (Monad m, Num a) => ConduitT a o m a
681sumC = CC.sum
682{-# INLINE sumC #-}
683
684-- | Get the sum of all elements in the chunked stream.
685--
686-- @since 1.3.0
687sumCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => ConduitT mono o m (Element mono)
688sumCE = CC.sumE
689{-# INLINE sumCE #-}
690
691-- | Get the product of all values in the stream.
692--
693-- @since 1.3.0
694productC :: (Monad m, Num a) => ConduitT a o m a
695productC = CC.product
696{-# INLINE productC #-}
697
698-- | Get the product of all elements in the chunked stream.
699--
700-- @since 1.3.0
701productCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => ConduitT mono o m (Element mono)
702productCE = CC.productE
703{-# INLINE productCE #-}
704
705-- | Find the first matching value.
706--
707-- @since 1.3.0
708findC :: Monad m => (a -> Bool) -> ConduitT a o m (Maybe a)
709findC = CC.find
710{-# INLINE findC #-}
711
712-- | Apply the action to all values in the stream.
713--
714-- Note: if you want to /pass/ the values instead of /consuming/ them, use
715-- 'iterM' instead.
716--
717-- @since 1.3.0
718mapM_C :: Monad m => (a -> m ()) -> ConduitT a o m ()
719mapM_C = CC.mapM_
720{-# INLINE mapM_C #-}
721
722-- | Apply the action to all elements in the chunked stream.
723--
724-- Note: the same caveat as with 'mapM_C' applies. If you don't want to
725-- consume the values, you can use 'iterM':
726--
727-- > iterM (omapM_ f)
728--
729-- @since 1.3.0
730mapM_CE :: (Monad m, MonoFoldable mono) => (Element mono -> m ()) -> ConduitT mono o m ()
731mapM_CE = CC.mapM_E
732{-# INLINE mapM_CE #-}
733
734-- | A monadic strict left fold.
735--
736-- @since 1.3.0
737foldMC :: Monad m => (a -> b -> m a) -> a -> ConduitT b o m a
738foldMC = CC.foldM
739{-# INLINE foldMC #-}
740
741-- | A monadic strict left fold on a chunked stream.
742--
743-- @since 1.3.0
744foldMCE :: (Monad m, MonoFoldable mono)
745       => (a -> Element mono -> m a)
746       -> a
747       -> ConduitT mono o m a
748foldMCE = CC.foldME
749{-# INLINE foldMCE #-}
750
751-- | Apply the provided monadic mapping function and monoidal combine all values.
752--
753-- @since 1.3.0
754foldMapMC :: (Monad m, Monoid w) => (a -> m w) -> ConduitT a o m w
755foldMapMC = CC.foldMapM
756{-# INLINE foldMapMC #-}
757
758-- | Apply the provided monadic mapping function and monoidal combine all
759-- elements in the chunked stream.
760--
761-- @since 1.3.0
762foldMapMCE :: (Monad m, MonoFoldable mono, Monoid w)
763          => (Element mono -> m w)
764          -> ConduitT mono o m w
765foldMapMCE = CC.foldMapME
766{-# INLINE foldMapMCE #-}
767
768-- | Print all incoming values to stdout.
769--
770-- @since 1.3.0
771printC :: (Show a, MonadIO m) => ConduitT a o m ()
772printC = CC.print
773{-# INLINE printC #-}
774
775-- | @sinkHandle@ applied to @stdout@.
776--
777-- @since 1.3.0
778stdoutC :: MonadIO m => ConduitT ByteString o m ()
779stdoutC = CC.stdout
780{-# INLINE stdoutC #-}
781
782-- | @sinkHandle@ applied to @stderr@.
783--
784-- @since 1.3.0
785stderrC :: MonadIO m => ConduitT ByteString o m ()
786stderrC = CC.stderr
787{-# INLINE stderrC #-}
788
789-- | Apply a transformation to all values in a stream.
790--
791-- @since 1.3.0
792mapC :: Monad m => (a -> b) -> ConduitT a b m ()
793mapC = CC.map
794{-# INLINE mapC #-}
795
796-- | Apply a transformation to all elements in a chunked stream.
797--
798-- @since 1.3.0
799mapCE :: (Monad m, Functor f) => (a -> b) -> ConduitT (f a) (f b) m ()
800mapCE = CC.mapE
801{-# INLINE mapCE #-}
802
803-- | Apply a monomorphic transformation to all elements in a chunked stream.
804--
805-- Unlike @mapE@, this will work on types like @ByteString@ and @Text@ which
806-- are @MonoFunctor@ but not @Functor@.
807--
808-- @since 1.3.0
809omapCE :: (Monad m, MonoFunctor mono) => (Element mono -> Element mono) -> ConduitT mono mono m ()
810omapCE = CC.omapE
811{-# INLINE omapCE #-}
812
813-- | Apply the function to each value in the stream, resulting in a foldable
814-- value (e.g., a list). Then yield each of the individual values in that
815-- foldable value separately.
816--
817-- Generalizes concatMap, mapMaybe, and mapFoldable.
818--
819-- @since 1.3.0
820concatMapC :: (Monad m, MonoFoldable mono)
821          => (a -> mono)
822          -> ConduitT a (Element mono) m ()
823concatMapC = CC.concatMap
824{-# INLINE concatMapC #-}
825
826-- | Apply the function to each element in the chunked stream, resulting in a
827-- foldable value (e.g., a list). Then yield each of the individual values in
828-- that foldable value separately.
829--
830-- Generalizes concatMap, mapMaybe, and mapFoldable.
831--
832-- @since 1.3.0
833concatMapCE :: (Monad m, MonoFoldable mono, Monoid w)
834           => (Element mono -> w)
835           -> ConduitT mono w m ()
836concatMapCE = CC.concatMapE
837{-# INLINE concatMapCE #-}
838
839-- | Stream up to n number of values downstream.
840--
841-- Note that, if downstream terminates early, not all values will be consumed.
842-- If you want to force /exactly/ the given number of values to be consumed,
843-- see 'takeExactly'.
844--
845-- @since 1.3.0
846takeC :: Monad m => Int -> ConduitT a a m ()
847takeC = CC.take
848{-# INLINE takeC #-}
849
850-- | Stream up to n number of elements downstream in a chunked stream.
851--
852-- Note that, if downstream terminates early, not all values will be consumed.
853-- If you want to force /exactly/ the given number of values to be consumed,
854-- see 'takeExactlyE'.
855--
856-- @since 1.3.0
857takeCE :: (Monad m, Seq.IsSequence seq)
858      => Seq.Index seq
859      -> ConduitT seq seq m ()
860takeCE = CC.takeE
861{-# INLINE takeCE #-}
862
863-- | Stream all values downstream that match the given predicate.
864--
865-- Same caveats regarding downstream termination apply as with 'take'.
866--
867-- @since 1.3.0
868takeWhileC :: Monad m
869          => (a -> Bool)
870          -> ConduitT a a m ()
871takeWhileC = CC.takeWhile
872{-# INLINE takeWhileC #-}
873
874-- | Stream all elements downstream that match the given predicate in a chunked stream.
875--
876-- Same caveats regarding downstream termination apply as with 'takeE'.
877--
878-- @since 1.3.0
879takeWhileCE :: (Monad m, Seq.IsSequence seq)
880           => (Element seq -> Bool)
881           -> ConduitT seq seq m ()
882takeWhileCE = CC.takeWhileE
883{-# INLINE takeWhileCE #-}
884
885-- | Consume precisely the given number of values and feed them downstream.
886--
887-- This function is in contrast to 'take', which will only consume up to the
888-- given number of values, and will terminate early if downstream terminates
889-- early. This function will discard any additional values in the stream if
890-- they are unconsumed.
891--
892-- Note that this function takes a downstream @ConduitT@ as a parameter, as
893-- opposed to working with normal fusion. For more information, see
894-- <http://www.yesodweb.com/blog/2013/10/core-flaw-pipes-conduit>, the section
895-- titled \"pipes and conduit: isolate\".
896--
897-- @since 1.3.0
898takeExactlyC :: Monad m
899            => Int
900            -> ConduitT a b m r
901            -> ConduitT a b m r
902takeExactlyC = CC.takeExactly
903{-# INLINE takeExactlyC #-}
904
905-- | Same as 'takeExactly', but for chunked streams.
906--
907-- @since 1.3.0
908takeExactlyCE :: (Monad m, Seq.IsSequence a)
909             => Seq.Index a
910             -> ConduitT a b m r
911             -> ConduitT a b m r
912takeExactlyCE = CC.takeExactlyE
913{-# INLINE takeExactlyCE #-}
914
915-- | Flatten out a stream by yielding the values contained in an incoming
916-- @MonoFoldable@ as individually yielded values.
917--
918-- @since 1.3.0
919concatC :: (Monad m, MonoFoldable mono)
920       => ConduitT mono (Element mono) m ()
921concatC = CC.concat
922{-# INLINE concatC #-}
923
924-- | Keep only values in the stream passing a given predicate.
925--
926-- @since 1.3.0
927filterC :: Monad m => (a -> Bool) -> ConduitT a a m ()
928filterC = CC.filter
929{-# INLINE filterC #-}
930
931-- | Keep only elements in the chunked stream passing a given predicate.
932--
933-- @since 1.3.0
934filterCE :: (Seq.IsSequence seq, Monad m) => (Element seq -> Bool) -> ConduitT seq seq m ()
935filterCE = CC.filterE
936{-# INLINE filterCE #-}
937
938-- | Map values as long as the result is @Just@.
939--
940-- @since 1.3.0
941mapWhileC :: Monad m => (a -> Maybe b) -> ConduitT a b m ()
942mapWhileC = CC.mapWhile
943{-# INLINE mapWhileC #-}
944
945-- | Break up a stream of values into vectors of size n. The final vector may
946-- be smaller than n if the total number of values is not a strict multiple of
947-- n. No empty vectors will be yielded.
948--
949-- @since 1.3.0
950conduitVector :: (V.Vector v a, PrimMonad m)
951              => Int -- ^ maximum allowed size
952              -> ConduitT a (v a) m ()
953conduitVector = CC.conduitVector
954{-# INLINE conduitVector #-}
955
956-- | Analog of 'Prelude.scanl' for lists.
957--
958-- @since 1.3.0
959scanlC :: Monad m => (a -> b -> a) -> a -> ConduitT b a m ()
960scanlC = CC.scanl
961{-# INLINE scanlC #-}
962
963-- | 'mapWhileC' with a break condition dependent on a strict accumulator.
964-- Equivalently, 'CL.mapAccum' as long as the result is @Right@. Instead of
965-- producing a leftover, the breaking input determines the resulting
966-- accumulator via @Left@.
967mapAccumWhileC :: Monad m =>
968    (a -> s -> Either s (s, b)) -> s -> ConduitT a b m s
969mapAccumWhileC = CC.mapAccumWhile
970{-# INLINE mapAccumWhileC #-}
971
972-- | 'concatMap' with an accumulator.
973--
974-- @since 1.3.0
975concatMapAccumC :: Monad m => (a -> accum -> (accum, [b])) -> accum -> ConduitT a b m ()
976concatMapAccumC = CC.concatMapAccum
977{-# INLINE concatMapAccumC #-}
978
979-- | Insert the given value between each two values in the stream.
980--
981-- @since 1.3.0
982intersperseC :: Monad m => a -> ConduitT a a m ()
983intersperseC = CC.intersperse
984{-# INLINE intersperseC #-}
985
986-- | Sliding window of values
987-- 1,2,3,4,5 with window size 2 gives
988-- [1,2],[2,3],[3,4],[4,5]
989--
990-- Best used with structures that support O(1) snoc.
991--
992-- @since 1.3.0
993slidingWindowC :: (Monad m, Seq.IsSequence seq, Element seq ~ a) => Int -> ConduitT a seq m ()
994slidingWindowC = CC.slidingWindow
995{-# INLINE slidingWindowC #-}
996
997
998-- | Split input into chunk of size 'chunkSize'
999--
1000-- The last element may be smaller than the 'chunkSize' (see also
1001-- 'chunksOfExactlyE' which will not yield this last element)
1002--
1003-- @since 1.3.0
1004chunksOfCE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> ConduitT seq seq m ()
1005chunksOfCE = CC.chunksOfE
1006{-# INLINE chunksOfCE #-}
1007
1008-- | Split input into chunk of size 'chunkSize'
1009--
1010-- If the input does not split into chunks exactly, the remainder will be
1011-- leftover (see also 'chunksOfE')
1012--
1013-- @since 1.3.0
1014chunksOfExactlyCE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> ConduitT seq seq m ()
1015chunksOfExactlyCE = CC.chunksOfExactlyE
1016{-# INLINE chunksOfExactlyCE #-}
1017
1018-- | Apply a monadic transformation to all values in a stream.
1019--
1020-- If you do not need the transformed values, and instead just want the monadic
1021-- side-effects of running the action, see 'mapM_'.
1022--
1023-- @since 1.3.0
1024mapMC :: Monad m => (a -> m b) -> ConduitT a b m ()
1025mapMC = CC.mapM
1026{-# INLINE mapMC #-}
1027
1028-- | Apply a monadic transformation to all elements in a chunked stream.
1029--
1030-- @since 1.3.0
1031mapMCE :: (Monad m, Data.Traversable.Traversable f) => (a -> m b) -> ConduitT (f a) (f b) m ()
1032mapMCE = CC.mapME
1033{-# INLINE mapMCE #-}
1034
1035-- | Apply a monadic monomorphic transformation to all elements in a chunked stream.
1036--
1037-- Unlike @mapME@, this will work on types like @ByteString@ and @Text@ which
1038-- are @MonoFunctor@ but not @Functor@.
1039--
1040-- @since 1.3.0
1041omapMCE :: (Monad m, MonoTraversable mono)
1042       => (Element mono -> m (Element mono))
1043       -> ConduitT mono mono m ()
1044omapMCE = CC.omapME
1045{-# INLINE omapMCE #-}
1046
1047-- | Apply the monadic function to each value in the stream, resulting in a
1048-- foldable value (e.g., a list). Then yield each of the individual values in
1049-- that foldable value separately.
1050--
1051-- Generalizes concatMapM, mapMaybeM, and mapFoldableM.
1052--
1053-- @since 1.3.0
1054concatMapMC :: (Monad m, MonoFoldable mono)
1055           => (a -> m mono)
1056           -> ConduitT a (Element mono) m ()
1057concatMapMC = CC.concatMapM
1058{-# INLINE concatMapMC #-}
1059
1060-- | Keep only values in the stream passing a given monadic predicate.
1061--
1062-- @since 1.3.0
1063filterMC :: Monad m
1064        => (a -> m Bool)
1065        -> ConduitT a a m ()
1066filterMC = CC.filterM
1067{-# INLINE filterMC #-}
1068
1069-- | Keep only elements in the chunked stream passing a given monadic predicate.
1070--
1071-- @since 1.3.0
1072filterMCE :: (Monad m, Seq.IsSequence seq) => (Element seq -> m Bool) -> ConduitT seq seq m ()
1073filterMCE = CC.filterME
1074{-# INLINE filterMCE #-}
1075
1076-- | Apply a monadic action on all values in a stream.
1077--
1078-- This @Conduit@ can be used to perform a monadic side-effect for every
1079-- value, whilst passing the value through the @Conduit@ as-is.
1080--
1081-- > iterM f = mapM (\a -> f a >>= \() -> return a)
1082--
1083-- @since 1.3.0
1084iterMC :: Monad m => (a -> m ()) -> ConduitT a a m ()
1085iterMC = CC.iterM
1086{-# INLINE iterMC #-}
1087
1088-- | Analog of 'Prelude.scanl' for lists, monadic.
1089--
1090-- @since 1.3.0
1091scanlMC :: Monad m => (a -> b -> m a) -> a -> ConduitT b a m ()
1092scanlMC = CC.scanlM
1093{-# INLINE scanlMC #-}
1094
1095-- | Monadic `mapAccumWhileC`.
1096mapAccumWhileMC :: Monad m => (a -> s -> m (Either s (s, b))) -> s -> ConduitT a b m s
1097mapAccumWhileMC = CC.mapAccumWhileM
1098{-# INLINE mapAccumWhileMC #-}
1099
1100-- | 'concatMapM' with an accumulator.
1101--
1102-- @since 1.3.0
1103concatMapAccumMC :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> ConduitT a b m ()
1104concatMapAccumMC = CC.concatMapAccumM
1105{-# INLINE concatMapAccumMC #-}
1106
1107-- | Encode a stream of text as UTF8.
1108--
1109-- @since 1.3.0
1110encodeUtf8C :: (Monad m, DTE.Utf8 text binary) => ConduitT text binary m ()
1111encodeUtf8C = CC.encodeUtf8
1112{-# INLINE encodeUtf8C #-}
1113
1114-- | Decode a stream of binary data as UTF8.
1115--
1116-- @since 1.3.0
1117decodeUtf8C :: MonadThrow m => ConduitT ByteString Text m ()
1118decodeUtf8C = CC.decodeUtf8
1119{-# INLINE decodeUtf8C #-}
1120
1121-- | Decode a stream of binary data as UTF8, replacing any invalid bytes with
1122-- the Unicode replacement character.
1123--
1124-- @since 1.3.0
1125decodeUtf8LenientC :: Monad m => ConduitT ByteString Text m ()
1126decodeUtf8LenientC = CC.decodeUtf8Lenient
1127{-# INLINE decodeUtf8LenientC #-}
1128
1129-- | Stream in the entirety of a single line.
1130--
1131-- Like @takeExactly@, this will consume the entirety of the line regardless of
1132-- the behavior of the inner Conduit.
1133--
1134-- @since 1.3.0
1135lineC :: (Monad m, Seq.IsSequence seq, Element seq ~ Char)
1136     => ConduitT seq o m r
1137     -> ConduitT seq o m r
1138lineC = CC.line
1139{-# INLINE lineC #-}
1140
1141-- | Same as 'line', but operates on ASCII/binary data.
1142--
1143-- @since 1.3.0
1144lineAsciiC :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8)
1145          => ConduitT seq o m r
1146          -> ConduitT seq o m r
1147lineAsciiC = CC.lineAscii
1148{-# INLINE lineAsciiC #-}
1149
1150-- | Insert a newline character after each incoming chunk of data.
1151--
1152-- @since 1.3.0
1153unlinesC :: (Monad m, Seq.IsSequence seq, Element seq ~ Char) => ConduitT seq seq m ()
1154unlinesC = CC.unlines
1155{-# INLINE unlinesC #-}
1156
1157-- | Same as 'unlines', but operates on ASCII/binary data.
1158--
1159-- @since 1.3.0
1160unlinesAsciiC :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8) => ConduitT seq seq m ()
1161unlinesAsciiC = CC.unlinesAscii
1162{-# INLINE unlinesAsciiC #-}
1163
1164-- | Convert a stream of arbitrarily-chunked textual data into a stream of data
1165-- where each chunk represents a single line. Note that, if you have
1166-- unknown/untrusted input, this function is /unsafe/, since it would allow an
1167-- attacker to form lines of massive length and exhaust memory.
1168--
1169-- @since 1.3.0
1170linesUnboundedC :: (Monad m, Seq.IsSequence seq, Element seq ~ Char)
1171               => ConduitT seq seq m ()
1172linesUnboundedC = CC.linesUnbounded
1173{-# INLINE linesUnboundedC #-}
1174
1175-- | Same as 'linesUnbounded', but for ASCII/binary data.
1176--
1177-- @since 1.3.0
1178linesUnboundedAsciiC :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8)
1179                    => ConduitT seq seq m ()
1180linesUnboundedAsciiC = CC.linesUnboundedAscii
1181{-# INLINE linesUnboundedAsciiC #-}
1182
1183-- | Generally speaking, yielding values from inside a Conduit requires
1184-- some allocation for constructors. This can introduce an overhead,
1185-- similar to the overhead needed to represent a list of values instead of
1186-- a vector. This overhead is even more severe when talking about unboxed
1187-- values.
1188--
1189-- This combinator allows you to overcome this overhead, and efficiently
1190-- fill up vectors. It takes two parameters. The first is the size of each
1191-- mutable vector to be allocated. The second is a function. The function
1192-- takes an argument which will yield the next value into a mutable
1193-- vector.
1194--
1195-- Under the surface, this function uses a number of tricks to get high
1196-- performance. For more information on both usage and implementation,
1197-- please see:
1198-- <https://www.fpcomplete.com/user/snoyberg/library-documentation/vectorbuilder>
1199--
1200-- @since 1.3.0
1201vectorBuilderC :: (PrimMonad m, V.Vector v e, PrimMonad n, PrimState m ~ PrimState n)
1202              => Int -- ^ size
1203              -> ((e -> n ()) -> ConduitT i Void m r)
1204              -> ConduitT i (v e) m r
1205vectorBuilderC = CC.vectorBuilder
1206{-# INLINE vectorBuilderC #-}
1207