{-# OPTIONS_HADDOCK not-home #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module Data.Conduit.Combinators.Unqualified
(
CC.yieldMany
, unfoldC
, enumFromToC
, iterateC
, repeatC
, replicateC
, CC.sourceLazy
, repeatMC
, repeatWhileMC
, replicateMC
, CC.sourceFile
, CC.sourceFileBS
, CC.sourceHandle
, CC.sourceHandleUnsafe
, CC.sourceIOHandle
, stdinC
, CC.withSourceFile
, CC.sourceDirectory
, CC.sourceDirectoryDeep
, dropC
, dropCE
, dropWhileC
, dropWhileCE
, foldC
, foldCE
, foldlC
, foldlCE
, foldMapC
, foldMapCE
, allC
, allCE
, anyC
, anyCE
, andC
, andCE
, orC
, orCE
, asumC
, elemC
, elemCE
, notElemC
, notElemCE
, CC.sinkLazy
, CC.sinkList
, CC.sinkVector
, CC.sinkVectorN
, CC.sinkLazyBuilder
, CC.sinkNull
, CC.awaitNonNull
, headC
, headDefC
, headCE
, peekC
, peekCE
, lastC
, lastDefC
, lastCE
, lengthC
, lengthCE
, lengthIfC
, lengthIfCE
, maximumC
, maximumCE
, minimumC
, minimumCE
, nullC
, nullCE
, sumC
, sumCE
, productC
, productCE
, findC
, mapM_C
, mapM_CE
, foldMC
, foldMCE
, foldMapMC
, foldMapMCE
, CC.sinkFile
, CC.sinkFileCautious
, CC.sinkTempFile
, CC.sinkSystemTempFile
, CC.sinkFileBS
, CC.sinkHandle
, CC.sinkIOHandle
, printC
, stdoutC
, stderrC
, CC.withSinkFile
, CC.withSinkFileBuilder
, CC.withSinkFileCautious
, CC.sinkHandleBuilder
, CC.sinkHandleFlush
, mapC
, mapCE
, omapCE
, concatMapC
, concatMapCE
, takeC
, takeCE
, takeWhileC
, takeWhileCE
, takeExactlyC
, takeExactlyCE
, concatC
, filterC
, filterCE
, mapWhileC
, conduitVector
, scanlC
, mapAccumWhileC
, concatMapAccumC
, intersperseC
, slidingWindowC
, chunksOfCE
, chunksOfExactlyCE
, mapMC
, mapMCE
, omapMCE
, concatMapMC
, filterMC
, filterMCE
, iterMC
, scanlMC
, mapAccumWhileMC
, concatMapAccumMC
, encodeUtf8C
, decodeUtf8C
, decodeUtf8LenientC
, lineC
, lineAsciiC
, unlinesC
, unlinesAsciiC
, linesUnboundedC
, linesUnboundedAsciiC
, CC.builderToByteString
, CC.unsafeBuilderToByteString
, CC.builderToByteStringWith
, CC.builderToByteStringFlush
, CC.builderToByteStringWithFlush
, CC.BufferAllocStrategy
, CC.allNewBuffersStrategy
, CC.reuseBufferStrategy
, vectorBuilderC
, CC.mapAccumS
, CC.peekForever
, CC.peekForeverE
) where
import qualified Data.Conduit.Combinators as CC
import qualified Data.Traversable
import Control.Applicative (Alternative)
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Primitive (PrimMonad, PrimState)
import Control.Monad.Trans.Resource (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)
import Data.Word (Word8)
import Data.ByteString (ByteString)
import Data.Text (Text)
import qualified Data.Sequences as DTE
unfoldC :: Monad m
=> (b -> Maybe (a, b))
-> b
-> ConduitT i a m ()
unfoldC :: (b -> Maybe (a, b)) -> b -> ConduitT i a m ()
unfoldC = (b -> Maybe (a, b)) -> b -> ConduitT i a m ()
forall (m :: * -> *) b a i.
Monad m =>
(b -> Maybe (a, b)) -> b -> ConduitT i a m ()
CC.unfold
{-# INLINE unfoldC #-}
enumFromToC :: (Monad m, Enum a, Ord a) => a -> a -> ConduitT i a m ()
enumFromToC :: a -> a -> ConduitT i a m ()
enumFromToC = a -> a -> ConduitT i a m ()
forall (m :: * -> *) a i.
(Monad m, Enum a, Ord a) =>
a -> a -> ConduitT i a m ()
CC.enumFromTo
{-# INLINE enumFromToC #-}
iterateC :: Monad m => (a -> a) -> a -> ConduitT i a m ()
iterateC :: (a -> a) -> a -> ConduitT i a m ()
iterateC = (a -> a) -> a -> ConduitT i a m ()
forall (m :: * -> *) a i.
Monad m =>
(a -> a) -> a -> ConduitT i a m ()
CC.iterate
{-# INLINE iterateC #-}
repeatC :: Monad m => a -> ConduitT i a m ()
repeatC :: a -> ConduitT i a m ()
repeatC = a -> ConduitT i a m ()
forall (m :: * -> *) a i. Monad m => a -> ConduitT i a m ()
CC.repeat
{-# INLINE repeatC #-}
replicateC :: Monad m
=> Int
-> a
-> ConduitT i a m ()
replicateC :: Int -> a -> ConduitT i a m ()
replicateC = Int -> a -> ConduitT i a m ()
forall (m :: * -> *) a i. Monad m => Int -> a -> ConduitT i a m ()
CC.replicate
{-# INLINE replicateC #-}
repeatMC :: Monad m
=> m a
-> ConduitT i a m ()
repeatMC :: m a -> ConduitT i a m ()
repeatMC = m a -> ConduitT i a m ()
forall (m :: * -> *) a i. Monad m => m a -> ConduitT i a m ()
CC.repeatM
{-# INLINE repeatMC #-}
repeatWhileMC :: Monad m
=> m a
-> (a -> Bool)
-> ConduitT i a m ()
repeatWhileMC :: m a -> (a -> Bool) -> ConduitT i a m ()
repeatWhileMC = m a -> (a -> Bool) -> ConduitT i a m ()
forall (m :: * -> *) a i.
Monad m =>
m a -> (a -> Bool) -> ConduitT i a m ()
CC.repeatWhileM
{-# INLINE repeatWhileMC #-}
replicateMC :: Monad m
=> Int
-> m a
-> ConduitT i a m ()
replicateMC :: Int -> m a -> ConduitT i a m ()
replicateMC = Int -> m a -> ConduitT i a m ()
forall (m :: * -> *) a i.
Monad m =>
Int -> m a -> ConduitT i a m ()
CC.replicateM
{-# INLINE replicateMC #-}
stdinC :: MonadIO m => ConduitT i ByteString m ()
stdinC :: ConduitT i ByteString m ()
stdinC = ConduitT i ByteString m ()
forall (m :: * -> *) i. MonadIO m => ConduitT i ByteString m ()
CC.stdin
{-# INLINE stdinC #-}
dropC :: Monad m
=> Int
-> ConduitT a o m ()
dropC :: Int -> ConduitT a o m ()
dropC = Int -> ConduitT a o m ()
forall (m :: * -> *) a o. Monad m => Int -> ConduitT a o m ()
CC.drop
{-# INLINE dropC #-}
dropCE :: (Monad m, Seq.IsSequence seq)
=> Seq.Index seq
-> ConduitT seq o m ()
dropCE :: Index seq -> ConduitT seq o m ()
dropCE = Index seq -> ConduitT seq o m ()
forall (m :: * -> *) seq o.
(Monad m, IsSequence seq) =>
Index seq -> ConduitT seq o m ()
CC.dropE
{-# INLINE dropCE #-}
dropWhileC :: Monad m
=> (a -> Bool)
-> ConduitT a o m ()
dropWhileC :: (a -> Bool) -> ConduitT a o m ()
dropWhileC = (a -> Bool) -> ConduitT a o m ()
forall (m :: * -> *) a o.
Monad m =>
(a -> Bool) -> ConduitT a o m ()
CC.dropWhile
{-# INLINE dropWhileC #-}
dropWhileCE :: (Monad m, Seq.IsSequence seq)
=> (Element seq -> Bool)
-> ConduitT seq o m ()
dropWhileCE :: (Element seq -> Bool) -> ConduitT seq o m ()
dropWhileCE = (Element seq -> Bool) -> ConduitT seq o m ()
forall (m :: * -> *) seq o.
(Monad m, IsSequence seq) =>
(Element seq -> Bool) -> ConduitT seq o m ()
CC.dropWhileE
{-# INLINE dropWhileCE #-}
foldC :: (Monad m, Monoid a)
=> ConduitT a o m a
foldC :: ConduitT a o m a
foldC = ConduitT a o m a
forall (m :: * -> *) a o. (Monad m, Monoid a) => ConduitT a o m a
CC.fold
{-# INLINE foldC #-}
foldCE :: (Monad m, MonoFoldable mono, Monoid (Element mono))
=> ConduitT mono o m (Element mono)
foldCE :: ConduitT mono o m (Element mono)
foldCE = ConduitT mono o m (Element mono)
forall (m :: * -> *) mono o.
(Monad m, MonoFoldable mono, Monoid (Element mono)) =>
ConduitT mono o m (Element mono)
CC.foldE
{-# INLINE foldCE #-}
foldlC :: Monad m => (a -> b -> a) -> a -> ConduitT b o m a
foldlC :: (a -> b -> a) -> a -> ConduitT b o m a
foldlC = (a -> b -> a) -> a -> ConduitT b o m a
forall (m :: * -> *) a b o.
Monad m =>
(a -> b -> a) -> a -> ConduitT b o m a
CC.foldl
{-# INLINE foldlC #-}
foldlCE :: (Monad m, MonoFoldable mono)
=> (a -> Element mono -> a)
-> a
-> ConduitT mono o m a
foldlCE :: (a -> Element mono -> a) -> a -> ConduitT mono o m a
foldlCE = (a -> Element mono -> a) -> a -> ConduitT mono o m a
forall (m :: * -> *) mono a o.
(Monad m, MonoFoldable mono) =>
(a -> Element mono -> a) -> a -> ConduitT mono o m a
CC.foldlE
{-# INLINE foldlCE #-}
foldMapC :: (Monad m, Monoid b)
=> (a -> b)
-> ConduitT a o m b
foldMapC :: (a -> b) -> ConduitT a o m b
foldMapC = (a -> b) -> ConduitT a o m b
forall (m :: * -> *) b a o.
(Monad m, Monoid b) =>
(a -> b) -> ConduitT a o m b
CC.foldMap
{-# INLINE foldMapC #-}
foldMapCE :: (Monad m, MonoFoldable mono, Monoid w)
=> (Element mono -> w)
-> ConduitT mono o m w
foldMapCE :: (Element mono -> w) -> ConduitT mono o m w
foldMapCE = (Element mono -> w) -> ConduitT mono o m w
forall (m :: * -> *) mono w o.
(Monad m, MonoFoldable mono, Monoid w) =>
(Element mono -> w) -> ConduitT mono o m w
CC.foldMapE
{-# INLINE foldMapCE #-}
allC :: Monad m
=> (a -> Bool)
-> ConduitT a o m Bool
allC :: (a -> Bool) -> ConduitT a o m Bool
allC = (a -> Bool) -> ConduitT a o m Bool
forall (m :: * -> *) a o.
Monad m =>
(a -> Bool) -> ConduitT a o m Bool
CC.all
{-# INLINE allC #-}
allCE :: (Monad m, MonoFoldable mono)
=> (Element mono -> Bool)
-> ConduitT mono o m Bool
allCE :: (Element mono -> Bool) -> ConduitT mono o m Bool
allCE = (Element mono -> Bool) -> ConduitT mono o m Bool
forall (m :: * -> *) mono o.
(Monad m, MonoFoldable mono) =>
(Element mono -> Bool) -> ConduitT mono o m Bool
CC.allE
{-# INLINE allCE #-}
anyC :: Monad m
=> (a -> Bool)
-> ConduitT a o m Bool
anyC :: (a -> Bool) -> ConduitT a o m Bool
anyC = (a -> Bool) -> ConduitT a o m Bool
forall (m :: * -> *) a o.
Monad m =>
(a -> Bool) -> ConduitT a o m Bool
CC.any
{-# INLINE anyC #-}
anyCE :: (Monad m, MonoFoldable mono)
=> (Element mono -> Bool)
-> ConduitT mono o m Bool
anyCE :: (Element mono -> Bool) -> ConduitT mono o m Bool
anyCE = (Element mono -> Bool) -> ConduitT mono o m Bool
forall (m :: * -> *) mono o.
(Monad m, MonoFoldable mono) =>
(Element mono -> Bool) -> ConduitT mono o m Bool
CC.anyE
{-# INLINE anyCE #-}
andC :: Monad m => ConduitT Bool o m Bool
andC :: ConduitT Bool o m Bool
andC = ConduitT Bool o m Bool
forall (m :: * -> *) o. Monad m => ConduitT Bool o m Bool
CC.and
{-# INLINE andC #-}
andCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool)
=> ConduitT mono o m Bool
andCE :: ConduitT mono o m Bool
andCE = ConduitT mono o m Bool
forall (m :: * -> *) mono o.
(Monad m, MonoFoldable mono, Element mono ~ Bool) =>
ConduitT mono o m Bool
CC.andE
{-# INLINE andCE #-}
orC :: Monad m => ConduitT Bool o m Bool
orC :: ConduitT Bool o m Bool
orC = ConduitT Bool o m Bool
forall (m :: * -> *) o. Monad m => ConduitT Bool o m Bool
CC.or
{-# INLINE orC #-}
orCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool)
=> ConduitT mono o m Bool
orCE :: ConduitT mono o m Bool
orCE = ConduitT mono o m Bool
forall (m :: * -> *) mono o.
(Monad m, MonoFoldable mono, Element mono ~ Bool) =>
ConduitT mono o m Bool
CC.orE
{-# INLINE orCE #-}
asumC :: (Monad m, Alternative f) => ConduitT (f a) o m (f a)
asumC :: ConduitT (f a) o m (f a)
asumC = ConduitT (f a) o m (f a)
forall (m :: * -> *) (f :: * -> *) a o.
(Monad m, Alternative f) =>
ConduitT (f a) o m (f a)
CC.asum
elemC :: (Monad m, Eq a) => a -> ConduitT a o m Bool
elemC :: a -> ConduitT a o m Bool
elemC = a -> ConduitT a o m Bool
forall (m :: * -> *) a o.
(Monad m, Eq a) =>
a -> ConduitT a o m Bool
CC.elem
{-# INLINE elemC #-}
#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
-> ConduitT seq o m Bool
elemCE :: Element seq -> ConduitT seq o m Bool
elemCE = Element seq -> ConduitT seq o m Bool
forall (m :: * -> *) seq o.
(Monad m, IsSequence seq, Eq (Element seq)) =>
Element seq -> ConduitT seq o m Bool
CC.elemE
{-# INLINE elemCE #-}
notElemC :: (Monad m, Eq a) => a -> ConduitT a o m Bool
notElemC :: a -> ConduitT a o m Bool
notElemC = a -> ConduitT a o m Bool
forall (m :: * -> *) a o.
(Monad m, Eq a) =>
a -> ConduitT a o m Bool
CC.notElem
{-# INLINE notElemC #-}
#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
-> ConduitT seq o m Bool
notElemCE :: Element seq -> ConduitT seq o m Bool
notElemCE = Element seq -> ConduitT seq o m Bool
forall (m :: * -> *) seq o.
(Monad m, IsSequence seq, Eq (Element seq)) =>
Element seq -> ConduitT seq o m Bool
CC.notElemE
{-# INLINE notElemCE #-}
headC :: Monad m => ConduitT a o m (Maybe a)
headC :: ConduitT a o m (Maybe a)
headC = ConduitT a o m (Maybe a)
forall (m :: * -> *) a o. Monad m => ConduitT a o m (Maybe a)
CC.head
headDefC :: Monad m => a -> ConduitT a o m a
headDefC :: a -> ConduitT a o m a
headDefC = a -> ConduitT a o m a
forall (m :: * -> *) a o. Monad m => a -> ConduitT a o m a
CC.headDef
headCE :: (Monad m, Seq.IsSequence seq) => ConduitT seq o m (Maybe (Element seq))
headCE :: ConduitT seq o m (Maybe (Element seq))
headCE = ConduitT seq o m (Maybe (Element seq))
forall (m :: * -> *) seq o.
(Monad m, IsSequence seq) =>
ConduitT seq o m (Maybe (Element seq))
CC.headE
{-# INLINE headCE #-}
peekC :: Monad m => ConduitT a o m (Maybe a)
peekC :: ConduitT a o m (Maybe a)
peekC = ConduitT a o m (Maybe a)
forall (m :: * -> *) a o. Monad m => ConduitT a o m (Maybe a)
CC.peek
{-# INLINE peekC #-}
peekCE :: (Monad m, MonoFoldable mono) => ConduitT mono o m (Maybe (Element mono))
peekCE :: ConduitT mono o m (Maybe (Element mono))
peekCE = ConduitT mono o m (Maybe (Element mono))
forall (m :: * -> *) mono o.
(Monad m, MonoFoldable mono) =>
ConduitT mono o m (Maybe (Element mono))
CC.peekE
{-# INLINE peekCE #-}
lastC :: Monad m => ConduitT a o m (Maybe a)
lastC :: ConduitT a o m (Maybe a)
lastC = ConduitT a o m (Maybe a)
forall (m :: * -> *) a o. Monad m => ConduitT a o m (Maybe a)
CC.last
{-# INLINE lastC #-}
lastDefC :: Monad m => a -> ConduitT a o m a
lastDefC :: a -> ConduitT a o m a
lastDefC = a -> ConduitT a o m a
forall (m :: * -> *) a o. Monad m => a -> ConduitT a o m a
CC.lastDef
lastCE :: (Monad m, Seq.IsSequence seq) => ConduitT seq o m (Maybe (Element seq))
lastCE :: ConduitT seq o m (Maybe (Element seq))
lastCE = ConduitT seq o m (Maybe (Element seq))
forall (m :: * -> *) seq o.
(Monad m, IsSequence seq) =>
ConduitT seq o m (Maybe (Element seq))
CC.lastE
{-# INLINE lastCE #-}
lengthC :: (Monad m, Num len) => ConduitT a o m len
lengthC :: ConduitT a o m len
lengthC = ConduitT a o m len
forall (m :: * -> *) len a o.
(Monad m, Num len) =>
ConduitT a o m len
CC.length
{-# INLINE lengthC #-}
lengthCE :: (Monad m, Num len, MonoFoldable mono) => ConduitT mono o m len
lengthCE :: ConduitT mono o m len
lengthCE = ConduitT mono o m len
forall (m :: * -> *) len mono o.
(Monad m, Num len, MonoFoldable mono) =>
ConduitT mono o m len
CC.lengthE
{-# INLINE lengthCE #-}
lengthIfC :: (Monad m, Num len) => (a -> Bool) -> ConduitT a o m len
lengthIfC :: (a -> Bool) -> ConduitT a o m len
lengthIfC = (a -> Bool) -> ConduitT a o m len
forall (m :: * -> *) len a o.
(Monad m, Num len) =>
(a -> Bool) -> ConduitT a o m len
CC.lengthIf
{-# INLINE lengthIfC #-}
lengthIfCE :: (Monad m, Num len, MonoFoldable mono)
=> (Element mono -> Bool) -> ConduitT mono o m len
lengthIfCE :: (Element mono -> Bool) -> ConduitT mono o m len
lengthIfCE = (Element mono -> Bool) -> ConduitT mono o m len
forall (m :: * -> *) len mono o.
(Monad m, Num len, MonoFoldable mono) =>
(Element mono -> Bool) -> ConduitT mono o m len
CC.lengthIfE
{-# INLINE lengthIfCE #-}
maximumC :: (Monad m, Ord a) => ConduitT a o m (Maybe a)
maximumC :: ConduitT a o m (Maybe a)
maximumC = ConduitT a o m (Maybe a)
forall (m :: * -> *) a o.
(Monad m, Ord a) =>
ConduitT a o m (Maybe a)
CC.maximum
{-# INLINE maximumC #-}
#if MIN_VERSION_mono_traversable(1,0,0)
maximumCE :: (Monad m, Seq.IsSequence seq, Ord (Element seq)) => ConduitT seq o m (Maybe (Element seq))
#else
maximumCE :: (Monad m, Seq.OrdSequence seq) => ConduitT seq o m (Maybe (Element seq))
#endif
maximumCE :: ConduitT seq o m (Maybe (Element seq))
maximumCE = ConduitT seq o m (Maybe (Element seq))
forall (m :: * -> *) seq o.
(Monad m, IsSequence seq, Ord (Element seq)) =>
ConduitT seq o m (Maybe (Element seq))
CC.maximumE
{-# INLINE maximumCE #-}
minimumC :: (Monad m, Ord a) => ConduitT a o m (Maybe a)
minimumC :: ConduitT a o m (Maybe a)
minimumC = ConduitT a o m (Maybe a)
forall (m :: * -> *) a o.
(Monad m, Ord a) =>
ConduitT a o m (Maybe a)
CC.minimum
{-# INLINE minimumC #-}
#if MIN_VERSION_mono_traversable(1,0,0)
minimumCE :: (Monad m, Seq.IsSequence seq, Ord (Element seq)) => ConduitT seq o m (Maybe (Element seq))
#else
minimumCE :: (Monad m, Seq.OrdSequence seq) => ConduitT seq o m (Maybe (Element seq))
#endif
minimumCE :: ConduitT seq o m (Maybe (Element seq))
minimumCE = ConduitT seq o m (Maybe (Element seq))
forall (m :: * -> *) seq o.
(Monad m, IsSequence seq, Ord (Element seq)) =>
ConduitT seq o m (Maybe (Element seq))
CC.minimumE
{-# INLINE minimumCE #-}
nullC :: Monad m => ConduitT a o m Bool
nullC :: ConduitT a o m Bool
nullC = ConduitT a o m Bool
forall (m :: * -> *) a o. Monad m => ConduitT a o m Bool
CC.null
{-# INLINE nullC #-}
nullCE :: (Monad m, MonoFoldable mono)
=> ConduitT mono o m Bool
nullCE :: ConduitT mono o m Bool
nullCE = ConduitT mono o m Bool
forall (m :: * -> *) mono o.
(Monad m, MonoFoldable mono) =>
ConduitT mono o m Bool
CC.nullE
{-# INLINE nullCE #-}
sumC :: (Monad m, Num a) => ConduitT a o m a
sumC :: ConduitT a o m a
sumC = ConduitT a o m a
forall (m :: * -> *) a o. (Monad m, Num a) => ConduitT a o m a
CC.sum
{-# INLINE sumC #-}
sumCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => ConduitT mono o m (Element mono)
sumCE :: ConduitT mono o m (Element mono)
sumCE = ConduitT mono o m (Element mono)
forall (m :: * -> *) mono o.
(Monad m, MonoFoldable mono, Num (Element mono)) =>
ConduitT mono o m (Element mono)
CC.sumE
{-# INLINE sumCE #-}
productC :: (Monad m, Num a) => ConduitT a o m a
productC :: ConduitT a o m a
productC = ConduitT a o m a
forall (m :: * -> *) a o. (Monad m, Num a) => ConduitT a o m a
CC.product
{-# INLINE productC #-}
productCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => ConduitT mono o m (Element mono)
productCE :: ConduitT mono o m (Element mono)
productCE = ConduitT mono o m (Element mono)
forall (m :: * -> *) mono o.
(Monad m, MonoFoldable mono, Num (Element mono)) =>
ConduitT mono o m (Element mono)
CC.productE
{-# INLINE productCE #-}
findC :: Monad m => (a -> Bool) -> ConduitT a o m (Maybe a)
findC :: (a -> Bool) -> ConduitT a o m (Maybe a)
findC = (a -> Bool) -> ConduitT a o m (Maybe a)
forall (m :: * -> *) a o.
Monad m =>
(a -> Bool) -> ConduitT a o m (Maybe a)
CC.find
{-# INLINE findC #-}
mapM_C :: Monad m => (a -> m ()) -> ConduitT a o m ()
mapM_C :: (a -> m ()) -> ConduitT a o m ()
mapM_C = (a -> m ()) -> ConduitT a o m ()
forall (m :: * -> *) a o.
Monad m =>
(a -> m ()) -> ConduitT a o m ()
CC.mapM_
{-# INLINE mapM_C #-}
mapM_CE :: (Monad m, MonoFoldable mono) => (Element mono -> m ()) -> ConduitT mono o m ()
mapM_CE :: (Element mono -> m ()) -> ConduitT mono o m ()
mapM_CE = (Element mono -> m ()) -> ConduitT mono o m ()
forall (m :: * -> *) mono o.
(Monad m, MonoFoldable mono) =>
(Element mono -> m ()) -> ConduitT mono o m ()
CC.mapM_E
{-# INLINE mapM_CE #-}
foldMC :: Monad m => (a -> b -> m a) -> a -> ConduitT b o m a
foldMC :: (a -> b -> m a) -> a -> ConduitT b o m a
foldMC = (a -> b -> m a) -> a -> ConduitT b o m a
forall (m :: * -> *) a b o.
Monad m =>
(a -> b -> m a) -> a -> ConduitT b o m a
CC.foldM
{-# INLINE foldMC #-}
foldMCE :: (Monad m, MonoFoldable mono)
=> (a -> Element mono -> m a)
-> a
-> ConduitT mono o m a
foldMCE :: (a -> Element mono -> m a) -> a -> ConduitT mono o m a
foldMCE = (a -> Element mono -> m a) -> a -> ConduitT mono o m a
forall (m :: * -> *) mono a o.
(Monad m, MonoFoldable mono) =>
(a -> Element mono -> m a) -> a -> ConduitT mono o m a
CC.foldME
{-# INLINE foldMCE #-}
foldMapMC :: (Monad m, Monoid w) => (a -> m w) -> ConduitT a o m w
foldMapMC :: (a -> m w) -> ConduitT a o m w
foldMapMC = (a -> m w) -> ConduitT a o m w
forall (m :: * -> *) w a o.
(Monad m, Monoid w) =>
(a -> m w) -> ConduitT a o m w
CC.foldMapM
{-# INLINE foldMapMC #-}
foldMapMCE :: (Monad m, MonoFoldable mono, Monoid w)
=> (Element mono -> m w)
-> ConduitT mono o m w
foldMapMCE :: (Element mono -> m w) -> ConduitT mono o m w
foldMapMCE = (Element mono -> m w) -> ConduitT mono o m w
forall (m :: * -> *) mono w o.
(Monad m, MonoFoldable mono, Monoid w) =>
(Element mono -> m w) -> ConduitT mono o m w
CC.foldMapME
{-# INLINE foldMapMCE #-}
printC :: (Show a, MonadIO m) => ConduitT a o m ()
printC :: ConduitT a o m ()
printC = ConduitT a o m ()
forall a (m :: * -> *) o. (Show a, MonadIO m) => ConduitT a o m ()
CC.print
{-# INLINE printC #-}
stdoutC :: MonadIO m => ConduitT ByteString o m ()
stdoutC :: ConduitT ByteString o m ()
stdoutC = ConduitT ByteString o m ()
forall (m :: * -> *) o. MonadIO m => ConduitT ByteString o m ()
CC.stdout
{-# INLINE stdoutC #-}
stderrC :: MonadIO m => ConduitT ByteString o m ()
stderrC :: ConduitT ByteString o m ()
stderrC = ConduitT ByteString o m ()
forall (m :: * -> *) o. MonadIO m => ConduitT ByteString o m ()
CC.stderr
{-# INLINE stderrC #-}
mapC :: Monad m => (a -> b) -> ConduitT a b m ()
mapC :: (a -> b) -> ConduitT a b m ()
mapC = (a -> b) -> ConduitT a b m ()
forall (m :: * -> *) a b. Monad m => (a -> b) -> ConduitT a b m ()
CC.map
{-# INLINE mapC #-}
mapCE :: (Monad m, Functor f) => (a -> b) -> ConduitT (f a) (f b) m ()
mapCE :: (a -> b) -> ConduitT (f a) (f b) m ()
mapCE = (a -> b) -> ConduitT (f a) (f b) m ()
forall (m :: * -> *) (f :: * -> *) a b.
(Monad m, Functor f) =>
(a -> b) -> ConduitT (f a) (f b) m ()
CC.mapE
{-# INLINE mapCE #-}
omapCE :: (Monad m, MonoFunctor mono) => (Element mono -> Element mono) -> ConduitT mono mono m ()
omapCE :: (Element mono -> Element mono) -> ConduitT mono mono m ()
omapCE = (Element mono -> Element mono) -> ConduitT mono mono m ()
forall (m :: * -> *) mono.
(Monad m, MonoFunctor mono) =>
(Element mono -> Element mono) -> ConduitT mono mono m ()
CC.omapE
{-# INLINE omapCE #-}
concatMapC :: (Monad m, MonoFoldable mono)
=> (a -> mono)
-> ConduitT a (Element mono) m ()
concatMapC :: (a -> mono) -> ConduitT a (Element mono) m ()
concatMapC = (a -> mono) -> ConduitT a (Element mono) m ()
forall (m :: * -> *) mono a.
(Monad m, MonoFoldable mono) =>
(a -> mono) -> ConduitT a (Element mono) m ()
CC.concatMap
{-# INLINE concatMapC #-}
concatMapCE :: (Monad m, MonoFoldable mono, Monoid w)
=> (Element mono -> w)
-> ConduitT mono w m ()
concatMapCE :: (Element mono -> w) -> ConduitT mono w m ()
concatMapCE = (Element mono -> w) -> ConduitT mono w m ()
forall (m :: * -> *) mono w.
(Monad m, MonoFoldable mono, Monoid w) =>
(Element mono -> w) -> ConduitT mono w m ()
CC.concatMapE
{-# INLINE concatMapCE #-}
takeC :: Monad m => Int -> ConduitT a a m ()
takeC :: Int -> ConduitT a a m ()
takeC = Int -> ConduitT a a m ()
forall (m :: * -> *) a. Monad m => Int -> ConduitT a a m ()
CC.take
{-# INLINE takeC #-}
takeCE :: (Monad m, Seq.IsSequence seq)
=> Seq.Index seq
-> ConduitT seq seq m ()
takeCE :: Index seq -> ConduitT seq seq m ()
takeCE = Index seq -> ConduitT seq seq m ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq) =>
Index seq -> ConduitT seq seq m ()
CC.takeE
{-# INLINE takeCE #-}
takeWhileC :: Monad m
=> (a -> Bool)
-> ConduitT a a m ()
takeWhileC :: (a -> Bool) -> ConduitT a a m ()
takeWhileC = (a -> Bool) -> ConduitT a a m ()
forall (m :: * -> *) a. Monad m => (a -> Bool) -> ConduitT a a m ()
CC.takeWhile
{-# INLINE takeWhileC #-}
takeWhileCE :: (Monad m, Seq.IsSequence seq)
=> (Element seq -> Bool)
-> ConduitT seq seq m ()
takeWhileCE :: (Element seq -> Bool) -> ConduitT seq seq m ()
takeWhileCE = (Element seq -> Bool) -> ConduitT seq seq m ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq) =>
(Element seq -> Bool) -> ConduitT seq seq m ()
CC.takeWhileE
{-# INLINE takeWhileCE #-}
takeExactlyC :: Monad m
=> Int
-> ConduitT a b m r
-> ConduitT a b m r
takeExactlyC :: Int -> ConduitT a b m r -> ConduitT a b m r
takeExactlyC = Int -> ConduitT a b m r -> ConduitT a b m r
forall (m :: * -> *) a b r.
Monad m =>
Int -> ConduitT a b m r -> ConduitT a b m r
CC.takeExactly
{-# INLINE takeExactlyC #-}
takeExactlyCE :: (Monad m, Seq.IsSequence a)
=> Seq.Index a
-> ConduitT a b m r
-> ConduitT a b m r
takeExactlyCE :: Index a -> ConduitT a b m r -> ConduitT a b m r
takeExactlyCE = Index a -> ConduitT a b m r -> ConduitT a b m r
forall (m :: * -> *) a b r.
(Monad m, IsSequence a) =>
Index a -> ConduitT a b m r -> ConduitT a b m r
CC.takeExactlyE
{-# INLINE takeExactlyCE #-}
concatC :: (Monad m, MonoFoldable mono)
=> ConduitT mono (Element mono) m ()
concatC :: ConduitT mono (Element mono) m ()
concatC = ConduitT mono (Element mono) m ()
forall (m :: * -> *) mono.
(Monad m, MonoFoldable mono) =>
ConduitT mono (Element mono) m ()
CC.concat
{-# INLINE concatC #-}
filterC :: Monad m => (a -> Bool) -> ConduitT a a m ()
filterC :: (a -> Bool) -> ConduitT a a m ()
filterC = (a -> Bool) -> ConduitT a a m ()
forall (m :: * -> *) a. Monad m => (a -> Bool) -> ConduitT a a m ()
CC.filter
{-# INLINE filterC #-}
filterCE :: (Seq.IsSequence seq, Monad m) => (Element seq -> Bool) -> ConduitT seq seq m ()
filterCE :: (Element seq -> Bool) -> ConduitT seq seq m ()
filterCE = (Element seq -> Bool) -> ConduitT seq seq m ()
forall seq (m :: * -> *).
(IsSequence seq, Monad m) =>
(Element seq -> Bool) -> ConduitT seq seq m ()
CC.filterE
{-# INLINE filterCE #-}
mapWhileC :: Monad m => (a -> Maybe b) -> ConduitT a b m ()
mapWhileC :: (a -> Maybe b) -> ConduitT a b m ()
mapWhileC = (a -> Maybe b) -> ConduitT a b m ()
forall (m :: * -> *) a b.
Monad m =>
(a -> Maybe b) -> ConduitT a b m ()
CC.mapWhile
{-# INLINE mapWhileC #-}
conduitVector :: (V.Vector v a, PrimMonad m)
=> Int
-> ConduitT a (v a) m ()
conduitVector :: Int -> ConduitT a (v a) m ()
conduitVector = Int -> ConduitT a (v a) m ()
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Int -> ConduitT a (v a) m ()
CC.conduitVector
{-# INLINE conduitVector #-}
scanlC :: Monad m => (a -> b -> a) -> a -> ConduitT b a m ()
scanlC :: (a -> b -> a) -> a -> ConduitT b a m ()
scanlC = (a -> b -> a) -> a -> ConduitT b a m ()
forall (m :: * -> *) a b.
Monad m =>
(a -> b -> a) -> a -> ConduitT b a m ()
CC.scanl
{-# INLINE scanlC #-}
mapAccumWhileC :: Monad m =>
(a -> s -> Either s (s, b)) -> s -> ConduitT a b m s
mapAccumWhileC :: (a -> s -> Either s (s, b)) -> s -> ConduitT a b m s
mapAccumWhileC = (a -> s -> Either s (s, b)) -> s -> ConduitT a b m s
forall (m :: * -> *) a s b.
Monad m =>
(a -> s -> Either s (s, b)) -> s -> ConduitT a b m s
CC.mapAccumWhile
{-# INLINE mapAccumWhileC #-}
concatMapAccumC :: Monad m => (a -> accum -> (accum, [b])) -> accum -> ConduitT a b m ()
concatMapAccumC :: (a -> accum -> (accum, [b])) -> accum -> ConduitT a b m ()
concatMapAccumC = (a -> accum -> (accum, [b])) -> accum -> ConduitT a b m ()
forall (m :: * -> *) a accum b.
Monad m =>
(a -> accum -> (accum, [b])) -> accum -> ConduitT a b m ()
CC.concatMapAccum
{-# INLINE concatMapAccumC #-}
intersperseC :: Monad m => a -> ConduitT a a m ()
intersperseC :: a -> ConduitT a a m ()
intersperseC = a -> ConduitT a a m ()
forall (m :: * -> *) a. Monad m => a -> ConduitT a a m ()
CC.intersperse
{-# INLINE intersperseC #-}
slidingWindowC :: (Monad m, Seq.IsSequence seq, Element seq ~ a) => Int -> ConduitT a seq m ()
slidingWindowC :: Int -> ConduitT a seq m ()
slidingWindowC = Int -> ConduitT a seq m ()
forall (m :: * -> *) seq a.
(Monad m, IsSequence seq, Element seq ~ a) =>
Int -> ConduitT a seq m ()
CC.slidingWindow
{-# INLINE slidingWindowC #-}
chunksOfCE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> ConduitT seq seq m ()
chunksOfCE :: Index seq -> ConduitT seq seq m ()
chunksOfCE = Index seq -> ConduitT seq seq m ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq) =>
Index seq -> ConduitT seq seq m ()
CC.chunksOfE
{-# INLINE chunksOfCE #-}
chunksOfExactlyCE :: (Monad m, Seq.IsSequence seq) => Seq.Index seq -> ConduitT seq seq m ()
chunksOfExactlyCE :: Index seq -> ConduitT seq seq m ()
chunksOfExactlyCE = Index seq -> ConduitT seq seq m ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq) =>
Index seq -> ConduitT seq seq m ()
CC.chunksOfExactlyE
{-# INLINE chunksOfExactlyCE #-}
mapMC :: Monad m => (a -> m b) -> ConduitT a b m ()
mapMC :: (a -> m b) -> ConduitT a b m ()
mapMC = (a -> m b) -> ConduitT a b m ()
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ConduitT a b m ()
CC.mapM
{-# INLINE mapMC #-}
mapMCE :: (Monad m, Data.Traversable.Traversable f) => (a -> m b) -> ConduitT (f a) (f b) m ()
mapMCE :: (a -> m b) -> ConduitT (f a) (f b) m ()
mapMCE = (a -> m b) -> ConduitT (f a) (f b) m ()
forall (m :: * -> *) (f :: * -> *) a b.
(Monad m, Traversable f) =>
(a -> m b) -> ConduitT (f a) (f b) m ()
CC.mapME
{-# INLINE mapMCE #-}
omapMCE :: (Monad m, MonoTraversable mono)
=> (Element mono -> m (Element mono))
-> ConduitT mono mono m ()
omapMCE :: (Element mono -> m (Element mono)) -> ConduitT mono mono m ()
omapMCE = (Element mono -> m (Element mono)) -> ConduitT mono mono m ()
forall (m :: * -> *) mono.
(Monad m, MonoTraversable mono) =>
(Element mono -> m (Element mono)) -> ConduitT mono mono m ()
CC.omapME
{-# INLINE omapMCE #-}
concatMapMC :: (Monad m, MonoFoldable mono)
=> (a -> m mono)
-> ConduitT a (Element mono) m ()
concatMapMC :: (a -> m mono) -> ConduitT a (Element mono) m ()
concatMapMC = (a -> m mono) -> ConduitT a (Element mono) m ()
forall (m :: * -> *) mono a.
(Monad m, MonoFoldable mono) =>
(a -> m mono) -> ConduitT a (Element mono) m ()
CC.concatMapM
{-# INLINE concatMapMC #-}
filterMC :: Monad m
=> (a -> m Bool)
-> ConduitT a a m ()
filterMC :: (a -> m Bool) -> ConduitT a a m ()
filterMC = (a -> m Bool) -> ConduitT a a m ()
forall (m :: * -> *) a.
Monad m =>
(a -> m Bool) -> ConduitT a a m ()
CC.filterM
{-# INLINE filterMC #-}
filterMCE :: (Monad m, Seq.IsSequence seq) => (Element seq -> m Bool) -> ConduitT seq seq m ()
filterMCE :: (Element seq -> m Bool) -> ConduitT seq seq m ()
filterMCE = (Element seq -> m Bool) -> ConduitT seq seq m ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq) =>
(Element seq -> m Bool) -> ConduitT seq seq m ()
CC.filterME
{-# INLINE filterMCE #-}
iterMC :: Monad m => (a -> m ()) -> ConduitT a a m ()
iterMC :: (a -> m ()) -> ConduitT a a m ()
iterMC = (a -> m ()) -> ConduitT a a m ()
forall (m :: * -> *) a. Monad m => (a -> m ()) -> ConduitT a a m ()
CC.iterM
{-# INLINE iterMC #-}
scanlMC :: Monad m => (a -> b -> m a) -> a -> ConduitT b a m ()
scanlMC :: (a -> b -> m a) -> a -> ConduitT b a m ()
scanlMC = (a -> b -> m a) -> a -> ConduitT b a m ()
forall (m :: * -> *) a b.
Monad m =>
(a -> b -> m a) -> a -> ConduitT b a m ()
CC.scanlM
{-# INLINE scanlMC #-}
mapAccumWhileMC :: Monad m => (a -> s -> m (Either s (s, b))) -> s -> ConduitT a b m s
mapAccumWhileMC :: (a -> s -> m (Either s (s, b))) -> s -> ConduitT a b m s
mapAccumWhileMC = (a -> s -> m (Either s (s, b))) -> s -> ConduitT a b m s
forall (m :: * -> *) a s b.
Monad m =>
(a -> s -> m (Either s (s, b))) -> s -> ConduitT a b m s
CC.mapAccumWhileM
{-# INLINE mapAccumWhileMC #-}
concatMapAccumMC :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> ConduitT a b m ()
concatMapAccumMC :: (a -> accum -> m (accum, [b])) -> accum -> ConduitT a b m ()
concatMapAccumMC = (a -> accum -> m (accum, [b])) -> accum -> ConduitT a b m ()
forall (m :: * -> *) a accum b.
Monad m =>
(a -> accum -> m (accum, [b])) -> accum -> ConduitT a b m ()
CC.concatMapAccumM
{-# INLINE concatMapAccumMC #-}
encodeUtf8C :: (Monad m, DTE.Utf8 text binary) => ConduitT text binary m ()
encodeUtf8C :: ConduitT text binary m ()
encodeUtf8C = ConduitT text binary m ()
forall (m :: * -> *) text binary.
(Monad m, Utf8 text binary) =>
ConduitT text binary m ()
CC.encodeUtf8
{-# INLINE encodeUtf8C #-}
decodeUtf8C :: MonadThrow m => ConduitT ByteString Text m ()
decodeUtf8C :: ConduitT ByteString Text m ()
decodeUtf8C = ConduitT ByteString Text m ()
forall (m :: * -> *). MonadThrow m => ConduitT ByteString Text m ()
CC.decodeUtf8
{-# INLINE decodeUtf8C #-}
decodeUtf8LenientC :: Monad m => ConduitT ByteString Text m ()
decodeUtf8LenientC :: ConduitT ByteString Text m ()
decodeUtf8LenientC = ConduitT ByteString Text m ()
forall (m :: * -> *). Monad m => ConduitT ByteString Text m ()
CC.decodeUtf8Lenient
{-# INLINE decodeUtf8LenientC #-}
lineC :: (Monad m, Seq.IsSequence seq, Element seq ~ Char)
=> ConduitT seq o m r
-> ConduitT seq o m r
lineC :: ConduitT seq o m r -> ConduitT seq o m r
lineC = ConduitT seq o m r -> ConduitT seq o m r
forall (m :: * -> *) seq o r.
(Monad m, IsSequence seq, Element seq ~ Char) =>
ConduitT seq o m r -> ConduitT seq o m r
CC.line
{-# INLINE lineC #-}
lineAsciiC :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8)
=> ConduitT seq o m r
-> ConduitT seq o m r
lineAsciiC :: ConduitT seq o m r -> ConduitT seq o m r
lineAsciiC = ConduitT seq o m r -> ConduitT seq o m r
forall (m :: * -> *) seq o r.
(Monad m, IsSequence seq, Element seq ~ Word8) =>
ConduitT seq o m r -> ConduitT seq o m r
CC.lineAscii
{-# INLINE lineAsciiC #-}
unlinesC :: (Monad m, Seq.IsSequence seq, Element seq ~ Char) => ConduitT seq seq m ()
unlinesC :: ConduitT seq seq m ()
unlinesC = ConduitT seq seq m ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq, Element seq ~ Char) =>
ConduitT seq seq m ()
CC.unlines
{-# INLINE unlinesC #-}
unlinesAsciiC :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8) => ConduitT seq seq m ()
unlinesAsciiC :: ConduitT seq seq m ()
unlinesAsciiC = ConduitT seq seq m ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq, Element seq ~ Word8) =>
ConduitT seq seq m ()
CC.unlinesAscii
{-# INLINE unlinesAsciiC #-}
linesUnboundedC :: (Monad m, Seq.IsSequence seq, Element seq ~ Char)
=> ConduitT seq seq m ()
linesUnboundedC :: ConduitT seq seq m ()
linesUnboundedC = ConduitT seq seq m ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq, Element seq ~ Char) =>
ConduitT seq seq m ()
CC.linesUnbounded
{-# INLINE linesUnboundedC #-}
linesUnboundedAsciiC :: (Monad m, Seq.IsSequence seq, Element seq ~ Word8)
=> ConduitT seq seq m ()
linesUnboundedAsciiC :: ConduitT seq seq m ()
linesUnboundedAsciiC = ConduitT seq seq m ()
forall (m :: * -> *) seq.
(Monad m, IsSequence seq, Element seq ~ Word8) =>
ConduitT seq seq m ()
CC.linesUnboundedAscii
{-# INLINE linesUnboundedAsciiC #-}
vectorBuilderC :: (PrimMonad m, V.Vector v e, PrimMonad n, PrimState m ~ PrimState n)
=> Int
-> ((e -> n ()) -> ConduitT i Void m r)
-> ConduitT i (v e) m r
vectorBuilderC :: Int -> ((e -> n ()) -> ConduitT i Void m r) -> ConduitT i (v e) m r
vectorBuilderC = Int -> ((e -> n ()) -> ConduitT i Void m r) -> ConduitT i (v e) m r
forall (m :: * -> *) (n :: * -> *) (v :: * -> *) e i r.
(PrimMonad m, PrimMonad n, Vector v e,
PrimState m ~ PrimState n) =>
Int -> ((e -> n ()) -> ConduitT i Void m r) -> ConduitT i (v e) m r
CC.vectorBuilder
{-# INLINE vectorBuilderC #-}