conduit-1.3.4.1: Streaming data processing library.
Safe HaskellNone
LanguageHaskell2010

Conduit

Description

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.

Synopsis

Core conduit library

Commonly used combinators

Producers

Pure

yieldMany :: (Monad m, MonoFoldable mono) => mono -> ConduitT i (Element mono) m () Source #

Yield each of the values contained by the given MonoFoldable.

This will work on many data structures, including lists, ByteStrings, and Vectors.

Subject to fusion

Since: 1.3.0

unfoldC :: Monad m => (b -> Maybe (a, b)) -> b -> ConduitT i a m () Source #

Generate a producer from a seed value.

Since: 1.3.0

enumFromToC :: (Monad m, Enum a, Ord a) => a -> a -> ConduitT i a m () Source #

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.3.0

iterateC :: Monad m => (a -> a) -> a -> ConduitT i a m () Source #

Produces an infinite stream of repeated applications of f to x.

Since: 1.3.0

repeatC :: Monad m => a -> ConduitT i a m () Source #

Produce an infinite stream consisting entirely of the given value.

Since: 1.3.0

replicateC :: Monad m => Int -> a -> ConduitT i a m () Source #

Produce a finite stream consisting of n copies of the given value.

Since: 1.3.0

sourceLazy :: (Monad m, LazySequence lazy strict) => lazy -> ConduitT i strict m () Source #

Generate a producer by yielding each of the strict chunks in a LazySequence.

For more information, see toChunks.

Subject to fusion

Since: 1.3.0

Monadic

repeatMC :: Monad m => m a -> ConduitT i a m () Source #

Repeatedly run the given action and yield all values it produces.

Since: 1.3.0

repeatWhileMC :: Monad m => m a -> (a -> Bool) -> ConduitT i a m () Source #

Repeatedly run the given action and yield all values it produces, until the provided predicate returns False.

Since: 1.3.0

replicateMC :: Monad m => Int -> m a -> ConduitT i a m () Source #

Perform the given action n times, yielding each result.

Since: 1.3.0

I/O

sourceFile :: MonadResource m => FilePath -> ConduitT i ByteString m () Source #

Stream the contents of a file as binary data.

Since: 1.3.0

sourceFileBS :: MonadResource m => FilePath -> ConduitT i ByteString m () Source #

Same as sourceFile. The alternate name is a holdover from an older version, when sourceFile was more polymorphic than it is today.

Since: 1.3.0

sourceHandle :: MonadIO m => Handle -> ConduitT i ByteString m () Source #

Stream the contents of a Handle as binary data. Note that this function will not automatically close the Handle when processing completes, since it did not acquire the Handle in the first place.

Since: 1.3.0

sourceHandleUnsafe :: MonadIO m => Handle -> ConduitT i ByteString m () Source #

Same as sourceHandle, but instead of allocating a new buffer for each incoming chunk of data, reuses the same buffer. Therefore, the ByteStrings yielded by this function are not referentially transparent between two different yields.

This function will be slightly more efficient than sourceHandle by avoiding allocations and reducing garbage collections, but should only be used if you can guarantee that you do not reuse a ByteString (or any slice thereof) between two calls to await.

Since: 1.3.0

sourceIOHandle :: MonadResource m => IO Handle -> ConduitT i ByteString m () Source #

An alternative to sourceHandle. Instead of taking a pre-opened Handle, it takes an action that opens a Handle (in read mode), so that it can open it only when needed and close it as soon as possible.

Since: 1.3.0

stdinC :: MonadIO m => ConduitT i ByteString m () Source #

sourceHandle applied to stdin.

Since: 1.3.0

withSourceFile :: (MonadUnliftIO m, MonadIO n) => FilePath -> (ConduitM i ByteString n () -> m a) -> m a Source #

Like withBinaryFile, but provides a source to read bytes from.

Since: 1.3.0

Filesystem

sourceDirectory :: MonadResource m => FilePath -> ConduitT i FilePath m () Source #

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.3.0

sourceDirectoryDeep Source #

Arguments

:: MonadResource m 
=> Bool

Follow directory symlinks

-> FilePath

Root directory

-> ConduitT i FilePath m () 

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.3.0

Consumers

Pure

dropC :: Monad m => Int -> ConduitT a o m () Source #

Ignore a certain number of values in the stream.

Note: since this function doesn't produce anything, you probably want to use it with (>>) instead of directly plugging it into a pipeline:

>>> runConduit $ yieldMany [1..5] .| dropC 2 .| sinkList
[]
>>> runConduit $ yieldMany [1..5] .| (dropC 2 >> sinkList)
[3,4,5]

Since: 1.3.0

dropCE :: (Monad m, IsSequence seq) => Index seq -> ConduitT seq o m () Source #

Drop a certain number of elements from a chunked stream.

Note: you likely want to use it with monadic composition. See the docs for dropC.

Since: 1.3.0

dropWhileC :: Monad m => (a -> Bool) -> ConduitT a o m () Source #

Drop all values which match the given predicate.

Note: you likely want to use it with monadic composition. See the docs for dropC.

Since: 1.3.0

dropWhileCE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> ConduitT seq o m () Source #

Drop all elements in the chunked stream which match the given predicate.

Note: you likely want to use it with monadic composition. See the docs for dropC.

Since: 1.3.0

foldC :: (Monad m, Monoid a) => ConduitT a o m a Source #

Monoidally combine all values in the stream.

Since: 1.3.0

foldCE :: (Monad m, MonoFoldable mono, Monoid (Element mono)) => ConduitT mono o m (Element mono) Source #

Monoidally combine all elements in the chunked stream.

Since: 1.3.0

foldlC :: Monad m => (a -> b -> a) -> a -> ConduitT b o m a Source #

A strict left fold.

Since: 1.3.0

foldlCE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> a) -> a -> ConduitT mono o m a Source #

A strict left fold on a chunked stream.

Since: 1.3.0

foldMapC :: (Monad m, Monoid b) => (a -> b) -> ConduitT a o m b Source #

Apply the provided mapping function and monoidal combine all values.

Since: 1.3.0

foldMapCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> ConduitT mono o m w Source #

Apply the provided mapping function and monoidal combine all elements of the chunked stream.

Since: 1.3.0

allC :: Monad m => (a -> Bool) -> ConduitT a o m Bool Source #

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.3.0

allCE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> ConduitT mono o m Bool Source #

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.3.0

anyC :: Monad m => (a -> Bool) -> ConduitT a o m Bool Source #

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.3.0

anyCE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> ConduitT mono o m Bool Source #

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.3.0

andC :: Monad m => ConduitT Bool o m Bool Source #

Are all values in the stream True?

Consumption stops once the first False is encountered.

Since: 1.3.0

andCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => ConduitT mono o m Bool Source #

Are all elements in the chunked stream True?

Consumption stops once the first False is encountered.

Since: 1.3.0

orC :: Monad m => ConduitT Bool o m Bool Source #

Are any values in the stream True?

Consumption stops once the first True is encountered.

Since: 1.3.0

orCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => ConduitT mono o m Bool Source #

Are any elements in the chunked stream True?

Consumption stops once the first True is encountered.

Since: 1.3.0

asumC :: (Monad m, Alternative f) => ConduitT (f a) o m (f a) Source #

Alternatively combine all values in the stream.

Since: 1.3.0

elemC :: (Monad m, Eq a) => a -> ConduitT a o m Bool Source #

Are any values in the stream equal to the given value?

Stops consuming as soon as a match is found.

Since: 1.3.0

elemCE :: (Monad m, IsSequence seq, Eq (Element seq)) => Element seq -> ConduitT seq o m Bool Source #

Are any elements in the chunked stream equal to the given element?

Stops consuming as soon as a match is found.

Since: 1.3.0

notElemC :: (Monad m, Eq a) => a -> ConduitT a o m Bool Source #

Are no values in the stream equal to the given value?

Stops consuming as soon as a match is found.

Since: 1.3.0

notElemCE :: (Monad m, IsSequence seq, Eq (Element seq)) => Element seq -> ConduitT seq o m Bool Source #

Are no elements in the chunked stream equal to the given element?

Stops consuming as soon as a match is found.

Since: 1.3.0

sinkLazy :: (Monad m, LazySequence lazy strict) => ConduitT strict o m lazy Source #

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.3.0

sinkList :: Monad m => ConduitT a o m [a] Source #

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.3.0

sinkVector :: (Vector v a, PrimMonad m) => ConduitT a o m (v a) Source #

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.3.0

sinkVectorN Source #

Arguments

:: (Vector v a, PrimMonad m) 
=> Int

maximum allowed size

-> ConduitT a o m (v a) 

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.3.0

sinkLazyBuilder :: Monad m => ConduitT Builder o m ByteString Source #

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.3.0

sinkNull :: Monad m => ConduitT a o m () Source #

Consume and discard all remaining values in the stream.

Subject to fusion

Since: 1.3.0

awaitNonNull :: (Monad m, MonoFoldable a) => ConduitT a o m (Maybe (NonNull a)) Source #

Same as await, but discards any leading onull values.

Since: 1.3.0

headC :: Monad m => ConduitT a o m (Maybe a) Source #

Take a single value from the stream, if available.

Since: 1.3.0

headDefC :: Monad m => a -> ConduitT a o m a Source #

Same as headC, but returns a default value if none are available from the stream.

Since: 1.3.0

headCE :: (Monad m, IsSequence seq) => ConduitT seq o m (Maybe (Element seq)) Source #

Get the next element in the chunked stream.

Since: 1.3.0

peekC :: Monad m => ConduitT a o m (Maybe a) Source #

View the next value in the stream without consuming it.

Since: 1.3.0

peekCE :: (Monad m, MonoFoldable mono) => ConduitT mono o m (Maybe (Element mono)) Source #

View the next element in the chunked stream without consuming it.

Since: 1.3.0

lastC :: Monad m => ConduitT a o m (Maybe a) Source #

Retrieve the last value in the stream, if present.

Since: 1.3.0

lastDefC :: Monad m => a -> ConduitT a o m a Source #

Same as lastC, but returns a default value if none are available from the stream.

Since: 1.3.0

lastCE :: (Monad m, IsSequence seq) => ConduitT seq o m (Maybe (Element seq)) Source #

Retrieve the last element in the chunked stream, if present.

Since: 1.3.0

lengthC :: (Monad m, Num len) => ConduitT a o m len Source #

Count how many values are in the stream.

Since: 1.3.0

lengthCE :: (Monad m, Num len, MonoFoldable mono) => ConduitT mono o m len Source #

Count how many elements are in the chunked stream.

Since: 1.3.0

lengthIfC :: (Monad m, Num len) => (a -> Bool) -> ConduitT a o m len Source #

Count how many values in the stream pass the given predicate.

Since: 1.3.0

lengthIfCE :: (Monad m, Num len, MonoFoldable mono) => (Element mono -> Bool) -> ConduitT mono o m len Source #

Count how many elements in the chunked stream pass the given predicate.

Since: 1.3.0

maximumC :: (Monad m, Ord a) => ConduitT a o m (Maybe a) Source #

Get the largest value in the stream, if present.

Since: 1.3.0

maximumCE :: (Monad m, IsSequence seq, Ord (Element seq)) => ConduitT seq o m (Maybe (Element seq)) Source #

Get the largest element in the chunked stream, if present.

Since: 1.3.0

minimumC :: (Monad m, Ord a) => ConduitT a o m (Maybe a) Source #

Get the smallest value in the stream, if present.

Since: 1.3.0

minimumCE :: (Monad m, IsSequence seq, Ord (Element seq)) => ConduitT seq o m (Maybe (Element seq)) Source #

Get the smallest element in the chunked stream, if present.

Since: 1.3.0

nullC :: Monad m => ConduitT a o m Bool Source #

True if there are no values in the stream.

This function does not modify the stream.

Since: 1.3.0

nullCE :: (Monad m, MonoFoldable mono) => ConduitT mono o m Bool Source #

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.3.0

sumC :: (Monad m, Num a) => ConduitT a o m a Source #

Get the sum of all values in the stream.

Since: 1.3.0

sumCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => ConduitT mono o m (Element mono) Source #

Get the sum of all elements in the chunked stream.

Since: 1.3.0

productC :: (Monad m, Num a) => ConduitT a o m a Source #

Get the product of all values in the stream.

Since: 1.3.0

productCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => ConduitT mono o m (Element mono) Source #

Get the product of all elements in the chunked stream.

Since: 1.3.0

findC :: Monad m => (a -> Bool) -> ConduitT a o m (Maybe a) Source #

Find the first matching value.

Since: 1.3.0

Monadic

mapM_C :: Monad m => (a -> m ()) -> ConduitT a o m () Source #

Apply the action to all values in the stream.

Note: if you want to pass the values instead of consuming them, use iterM instead.

Since: 1.3.0

mapM_CE :: (Monad m, MonoFoldable mono) => (Element mono -> m ()) -> ConduitT mono o m () Source #

Apply the action to all elements in the chunked stream.

Note: the same caveat as with mapM_C applies. If you don't want to consume the values, you can use iterM:

iterM (omapM_ f)

Since: 1.3.0

foldMC :: Monad m => (a -> b -> m a) -> a -> ConduitT b o m a Source #

A monadic strict left fold.

Since: 1.3.0

foldMCE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> m a) -> a -> ConduitT mono o m a Source #

A monadic strict left fold on a chunked stream.

Since: 1.3.0

foldMapMC :: (Monad m, Monoid w) => (a -> m w) -> ConduitT a o m w Source #

Apply the provided monadic mapping function and monoidal combine all values.

Since: 1.3.0

foldMapMCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> m w) -> ConduitT mono o m w Source #

Apply the provided monadic mapping function and monoidal combine all elements in the chunked stream.

Since: 1.3.0

I/O

sinkFile :: MonadResource m => FilePath -> ConduitT ByteString o m () Source #

Stream all incoming data to the given file.

Since: 1.3.0

sinkFileCautious :: MonadResource m => FilePath -> ConduitM ByteString o m () Source #

Cautious version of sinkFile. The idea here is to stream the values to a temporary file in the same directory of the destination file, and only on successfully writing the entire file, moves it atomically to the destination path.

In the event of an exception occurring, the temporary file will be deleted and no move will be made. If the application shuts down without running exception handling (such as machine failure or a SIGKILL), the temporary file will remain and the destination file will be untouched.

Since: 1.3.0

sinkTempFile Source #

Arguments

:: MonadResource m 
=> FilePath

temp directory

-> String

filename pattern

-> ConduitM ByteString o m FilePath 

Stream data into a temporary file in the given directory with the given filename pattern, and return the temporary filename. The temporary file will be automatically deleted when exiting the active ResourceT block, if it still exists.

Since: 1.3.0

sinkSystemTempFile Source #

Arguments

:: MonadResource m 
=> String

filename pattern

-> ConduitM ByteString o m FilePath 

Same as sinkTempFile, but will use the default temp file directory for the system as the first argument.

Since: 1.3.0

sinkFileBS :: MonadResource m => FilePath -> ConduitT ByteString o m () Source #

sinkFile specialized to ByteString to help with type inference.

Since: 1.3.0

sinkHandle :: MonadIO m => Handle -> ConduitT ByteString o m () Source #

Stream all incoming data to the given Handle. Note that this function does not flush and will not close the Handle when processing completes.

Since: 1.3.0

sinkIOHandle :: MonadResource m => IO Handle -> ConduitT ByteString o m () Source #

An alternative to sinkHandle. Instead of taking a pre-opened Handle, it takes an action that opens a Handle (in write mode), so that it can open it only when needed and close it as soon as possible.

Since: 1.3.0

printC :: (Show a, MonadIO m) => ConduitT a o m () Source #

Print all incoming values to stdout.

Since: 1.3.0

stdoutC :: MonadIO m => ConduitT ByteString o m () Source #

sinkHandle applied to stdout.

Since: 1.3.0

stderrC :: MonadIO m => ConduitT ByteString o m () Source #

sinkHandle applied to stderr.

Since: 1.3.0

withSinkFile :: (MonadUnliftIO m, MonadIO n) => FilePath -> (ConduitM ByteString o n () -> m a) -> m a Source #

Like withBinaryFile, but provides a sink to write bytes to.

Since: 1.3.0

withSinkFileBuilder :: (MonadUnliftIO m, MonadIO n) => FilePath -> (ConduitM Builder o n () -> m a) -> m a Source #

Same as withSinkFile, but lets you use a Builder.

Since: 1.3.0

withSinkFileCautious :: (MonadUnliftIO m, MonadIO n) => FilePath -> (ConduitM ByteString o n () -> m a) -> m a Source #

Like sinkFileCautious, but uses the with pattern instead of MonadResource.

Since: 1.3.0

sinkHandleBuilder :: MonadIO m => Handle -> ConduitM Builder o m () Source #

Stream incoming builders, executing them directly on the buffer of the given Handle. Note that this function does not automatically close the Handle when processing completes. Pass flush to flush the buffer.

Since: 1.3.0

sinkHandleFlush :: MonadIO m => Handle -> ConduitM (Flush ByteString) o m () Source #

Stream incoming Flushes, executing them on IO.Handle Note that this function does not automatically close the Handle when processing completes

Since: 1.3.0

Transformers

Pure

mapC :: Monad m => (a -> b) -> ConduitT a b m () Source #

Apply a transformation to all values in a stream.

Since: 1.3.0

mapCE :: (Monad m, Functor f) => (a -> b) -> ConduitT (f a) (f b) m () Source #

Apply a transformation to all elements in a chunked stream.

Since: 1.3.0

omapCE :: (Monad m, MonoFunctor mono) => (Element mono -> Element mono) -> ConduitT mono mono m () Source #

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.3.0

concatMapC :: (Monad m, MonoFoldable mono) => (a -> mono) -> ConduitT a (Element mono) m () Source #

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.3.0

concatMapCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> ConduitT mono w m () Source #

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.3.0

takeC :: Monad m => Int -> ConduitT a a m () Source #

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.3.0

takeCE :: (Monad m, IsSequence seq) => Index seq -> ConduitT seq seq m () Source #

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.3.0

takeWhileC :: Monad m => (a -> Bool) -> ConduitT a a m () Source #

Stream all values downstream that match the given predicate.

Same caveats regarding downstream termination apply as with take.

Since: 1.3.0

takeWhileCE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> ConduitT seq seq m () Source #

Stream all elements downstream that match the given predicate in a chunked stream.

Same caveats regarding downstream termination apply as with takeE.

Since: 1.3.0

takeExactlyC :: Monad m => Int -> ConduitT a b m r -> ConduitT a b m r Source #

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 ConduitT as a parameter, as opposed to working with normal fusion. For more information, see http://www.yesodweb.com/blog/2013/10/core-flaw-pipes-conduit, the section titled "pipes and conduit: isolate".

Since: 1.3.0

takeExactlyCE :: (Monad m, IsSequence a) => Index a -> ConduitT a b m r -> ConduitT a b m r Source #

Same as takeExactly, but for chunked streams.

Since: 1.3.0

concatC :: (Monad m, MonoFoldable mono) => ConduitT mono (Element mono) m () Source #

Flatten out a stream by yielding the values contained in an incoming MonoFoldable as individually yielded values.

Since: 1.3.0

filterC :: Monad m => (a -> Bool) -> ConduitT a a m () Source #

Keep only values in the stream passing a given predicate.

Since: 1.3.0

filterCE :: (IsSequence seq, Monad m) => (Element seq -> Bool) -> ConduitT seq seq m () Source #

Keep only elements in the chunked stream passing a given predicate.

Since: 1.3.0

mapWhileC :: Monad m => (a -> Maybe b) -> ConduitT a b m () Source #

Map values as long as the result is Just.

Since: 1.3.0

conduitVector Source #

Arguments

:: (Vector v a, PrimMonad m) 
=> Int

maximum allowed size

-> ConduitT a (v a) m () 

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.3.0

scanlC :: Monad m => (a -> b -> a) -> a -> ConduitT b a m () Source #

Analog of scanl for lists.

Since: 1.3.0

mapAccumWhileC :: Monad m => (a -> s -> Either s (s, b)) -> s -> ConduitT a b m s Source #

mapWhileC with a break condition dependent on a strict accumulator. Equivalently, mapAccum as long as the result is Right. Instead of producing a leftover, the breaking input determines the resulting accumulator via Left.

concatMapAccumC :: Monad m => (a -> accum -> (accum, [b])) -> accum -> ConduitT a b m () Source #

concatMap with an accumulator.

Since: 1.3.0

intersperseC :: Monad m => a -> ConduitT a a m () Source #

Insert the given value between each two values in the stream.

Since: 1.3.0

slidingWindowC :: (Monad m, IsSequence seq, Element seq ~ a) => Int -> ConduitT a seq m () Source #

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.3.0

chunksOfCE :: (Monad m, IsSequence seq) => Index seq -> ConduitT seq seq m () Source #

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.3.0

chunksOfExactlyCE :: (Monad m, IsSequence seq) => Index seq -> ConduitT seq seq m () Source #

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.3.0

Monadic

mapMC :: Monad m => (a -> m b) -> ConduitT a b m () Source #

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.3.0

mapMCE :: (Monad m, Traversable f) => (a -> m b) -> ConduitT (f a) (f b) m () Source #

Apply a monadic transformation to all elements in a chunked stream.

Since: 1.3.0

omapMCE :: (Monad m, MonoTraversable mono) => (Element mono -> m (Element mono)) -> ConduitT mono mono m () Source #

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.3.0

concatMapMC :: (Monad m, MonoFoldable mono) => (a -> m mono) -> ConduitT a (Element mono) m () Source #

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.3.0

filterMC :: Monad m => (a -> m Bool) -> ConduitT a a m () Source #

Keep only values in the stream passing a given monadic predicate.

Since: 1.3.0

filterMCE :: (Monad m, IsSequence seq) => (Element seq -> m Bool) -> ConduitT seq seq m () Source #

Keep only elements in the chunked stream passing a given monadic predicate.

Since: 1.3.0

iterMC :: Monad m => (a -> m ()) -> ConduitT a a m () Source #

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.3.0

scanlMC :: Monad m => (a -> b -> m a) -> a -> ConduitT b a m () Source #

Analog of scanl for lists, monadic.

Since: 1.3.0

mapAccumWhileMC :: Monad m => (a -> s -> m (Either s (s, b))) -> s -> ConduitT a b m s Source #

concatMapAccumMC :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> ConduitT a b m () Source #

concatMapM with an accumulator.

Since: 1.3.0

Textual

encodeUtf8C :: (Monad m, Utf8 text binary) => ConduitT text binary m () Source #

Encode a stream of text as UTF8.

Since: 1.3.0

decodeUtf8C :: MonadThrow m => ConduitT ByteString Text m () Source #

Decode a stream of binary data as UTF8.

Since: 1.3.0

decodeUtf8LenientC :: Monad m => ConduitT ByteString Text m () Source #

Decode a stream of binary data as UTF8, replacing any invalid bytes with the Unicode replacement character.

Since: 1.3.0

lineC :: (Monad m, IsSequence seq, Element seq ~ Char) => ConduitT seq o m r -> ConduitT seq o m r Source #

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.3.0

lineAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => ConduitT seq o m r -> ConduitT seq o m r Source #

Same as line, but operates on ASCII/binary data.

Since: 1.3.0

unlinesC :: (Monad m, IsSequence seq, Element seq ~ Char) => ConduitT seq seq m () Source #

Insert a newline character after each incoming chunk of data.

Since: 1.3.0

unlinesAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => ConduitT seq seq m () Source #

Same as unlines, but operates on ASCII/binary data.

Since: 1.3.0

linesUnboundedC :: (Monad m, IsSequence seq, Element seq ~ Char) => ConduitT seq seq m () Source #

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 unknownuntrusted input, this function is unsafe/, since it would allow an attacker to form lines of massive length and exhaust memory.

Since: 1.3.0

linesUnboundedAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => ConduitT seq seq m () Source #

Same as linesUnbounded, but for ASCII/binary data.

Since: 1.3.0

Builders

builderToByteString :: PrimMonad m => ConduitT Builder ByteString m () Source #

Incrementally execute builders and pass on the filled chunks as bytestrings.

Since: 1.3.0

unsafeBuilderToByteString :: PrimMonad m => ConduitT Builder ByteString m () Source #

Incrementally execute builders on the given buffer and pass on the filled chunks as bytestrings. Note that, if the given buffer is too small for the execution of a build step, a larger one will be allocated.

WARNING: This conduit yields bytestrings that are NOT referentially transparent. Their content will be overwritten as soon as control is returned from the inner sink!

Since: 1.3.0

builderToByteStringWith :: PrimMonad m => BufferAllocStrategy -> ConduitT Builder ByteString m () Source #

A conduit that incrementally executes builders and passes on the filled chunks as bytestrings to an inner sink.

INV: All bytestrings passed to the inner sink are non-empty.

Since: 1.3.0

builderToByteStringFlush :: PrimMonad m => ConduitT (Flush Builder) (Flush ByteString) m () Source #

Same as builderToByteString, but input and output are wrapped in Flush.

Since: 1.3.0

type BufferAllocStrategy = (IO Buffer, Int -> Buffer -> IO (IO Buffer)) Source #

A buffer allocation strategy (buf0, nextBuf) specifies the initial buffer to use and how to compute a new buffer nextBuf minSize buf with at least size minSize from a filled buffer buf. The double nesting of the IO monad helps to ensure that the reference to the filled buffer buf is lost as soon as possible, but the new buffer doesn't have to be allocated too early.

Since: 1.3.0

allNewBuffersStrategy :: Int -> BufferAllocStrategy Source #

The simplest buffer allocation strategy: whenever a buffer is requested, allocate a new one that is big enough for the next build step to execute.

NOTE that this allocation strategy may spill quite some memory upon direct insertion of a bytestring by the builder. Thats no problem for garbage collection, but it may lead to unreasonably high memory consumption in special circumstances.

Since: 1.3.0

reuseBufferStrategy :: IO Buffer -> BufferAllocStrategy Source #

An unsafe, but possibly more efficient buffer allocation strategy: reuse the buffer, if it is big enough for the next build step to execute.

Since: 1.3.0

Special

vectorBuilderC Source #

Arguments

:: (PrimMonad m, Vector v e, PrimMonad n, PrimState m ~ PrimState n) 
=> Int

size

-> ((e -> n ()) -> ConduitT i Void m r) 
-> ConduitT i (v e) m r 

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: https://www.fpcomplete.com/user/snoyberg/library-documentation/vectorbuilder

Since: 1.3.0

mapAccumS :: Monad m => (a -> s -> ConduitT b Void m s) -> s -> ConduitT () b m () -> ConduitT a Void m s Source #

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]]

peekForever :: Monad m => ConduitT i o m () -> ConduitT i o m () Source #

Run a consuming conduit repeatedly, only stopping when there is no more data available from upstream.

Since: 1.3.0

peekForeverE :: (Monad m, MonoFoldable i) => ConduitT i o m () -> ConduitT i o m () Source #

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.3.0

Monadic lifting

class Monad m => MonadIO (m :: Type -> Type) where #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances

Instances details
MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Methods

liftIO :: IO a -> IO a #

MonadIO Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftIO :: IO a -> Q a #

MonadIO Acquire 
Instance details

Defined in Data.Acquire.Internal

Methods

liftIO :: IO a -> Acquire a #

MonadIO m => MonadIO (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (CatchT m) 
Instance details

Defined in Control.Monad.Catch.Pure

Methods

liftIO :: IO a -> CatchT m a #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftIO :: IO a -> ResourceT m a #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a #

MonadIO m => MonadIO (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftIO :: IO a -> IdentityT m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, Functor m, MonadIO m) => MonadIO (AccumT w m) 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

liftIO :: IO a -> AccumT w m a #

MonadIO m => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (SelectT r m) 
Instance details

Defined in Control.Monad.Trans.Select

Methods

liftIO :: IO a -> SelectT r m a #

MonadIO m => MonadIO (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

liftIO :: IO a -> ContT r m a #

MonadIO m => MonadIO (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

liftIO :: IO a -> ConduitT i o m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

liftIO :: IO a -> RWST r w s m a #

MonadIO m => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Methods

liftIO :: IO a -> RWST r w s m a #

MonadIO m => MonadIO (Pipe l i o u m) Source # 
Instance details

Defined in Data.Conduit.Internal.Pipe

Methods

liftIO :: IO a -> Pipe l i o u m a #

class MonadTrans (t :: (Type -> Type) -> Type -> Type) where #

The class of monad transformers. Instances should satisfy the following laws, which state that lift is a monad transformation:

Methods

lift :: Monad m => m a -> t m a #

Lift a computation from the argument monad to the constructed monad.

Instances

Instances details
MonadTrans MaybeT 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

lift :: Monad m => m a -> MaybeT m a #

MonadTrans CatchT 
Instance details

Defined in Control.Monad.Catch.Pure

Methods

lift :: Monad m => m a -> CatchT m a #

MonadTrans ListT 
Instance details

Defined in Control.Monad.Trans.List

Methods

lift :: Monad m => m a -> ListT m a #

MonadTrans ResourceT 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

lift :: Monad m => m a -> ResourceT m a #

MonadTrans (ExceptT e) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

lift :: Monad m => m a -> ExceptT e m a #

MonadTrans (IdentityT :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

lift :: Monad m => m a -> IdentityT m a #

MonadTrans (ErrorT e) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

lift :: Monad m => m a -> ErrorT e m a #

MonadTrans (ReaderT r) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

lift :: Monad m => m a -> ReaderT r m a #

MonadTrans (StateT s) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

lift :: Monad m => m a -> StateT s m a #

MonadTrans (StateT s) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

lift :: Monad m => m a -> StateT s m a #

Monoid w => MonadTrans (WriterT w) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

lift :: Monad m => m a -> WriterT w m a #

Monoid w => MonadTrans (WriterT w) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

lift :: Monad m => m a -> WriterT w m a #

Monoid w => MonadTrans (AccumT w) 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

lift :: Monad m => m a -> AccumT w m a #

MonadTrans (WriterT w) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

lift :: Monad m => m a -> WriterT w m a #

MonadTrans (SelectT r) 
Instance details

Defined in Control.Monad.Trans.Select

Methods

lift :: Monad m => m a -> SelectT r m a #

MonadTrans (ContT r) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

lift :: Monad m => m a -> ContT r m a #

MonadTrans (ConduitT i o) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

lift :: Monad m => m a -> ConduitT i o m a #

Monoid w => MonadTrans (RWST r w s) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

lift :: Monad m => m a -> RWST r w s m a #

Monoid w => MonadTrans (RWST r w s) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

lift :: Monad m => m a -> RWST r w s m a #

MonadTrans (RWST r w s) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Methods

lift :: Monad m => m a -> RWST r w s m a #

MonadTrans (Pipe l i o u) Source # 
Instance details

Defined in Data.Conduit.Internal.Pipe

Methods

lift :: Monad m => m a -> Pipe l i o u m a #

class Monad m => MonadThrow (m :: Type -> Type) where #

A class for monads in which exceptions may be thrown.

Instances should obey the following law:

throwM e >> x = throwM e

In other words, throwing an exception short-circuits the rest of the monadic computation.

Methods

throwM :: Exception e => e -> m a #

Throw an exception. Note that this throws when this action is run in the monad m, not when it is applied. It is a generalization of Control.Exception's throwIO.

Should satisfy the law:

throwM e >> f = throwM e

Instances

Instances details
MonadThrow [] 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> [a] #

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Maybe a #

MonadThrow IO 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IO a #

MonadThrow Q 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Q a #

MonadThrow STM 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> STM a #

e ~ SomeException => MonadThrow (Either e) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> Either e a #

MonadThrow (ST s) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ST s a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> MaybeT m a #

Monad m => MonadThrow (CatchT m) 
Instance details

Defined in Control.Monad.Catch.Pure

Methods

throwM :: Exception e => e -> CatchT m a #

MonadThrow m => MonadThrow (ListT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ListT m a #

MonadThrow m => MonadThrow (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

throwM :: Exception e => e -> ResourceT m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ExceptT e m a #

MonadThrow m => MonadThrow (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IdentityT m a #

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ErrorT e m a #

MonadThrow m => MonadThrow (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ReaderT r m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a #

MonadThrow m => MonadThrow (ContT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ContT r m a #

MonadThrow m => MonadThrow (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

throwM :: Exception e => e -> ConduitT i o m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a #

MonadThrow m => MonadThrow (Pipe l i o u m) Source # 
Instance details

Defined in Data.Conduit.Internal.Pipe

Methods

throwM :: Exception e => e -> Pipe l i o u m a #

class MonadIO m => MonadUnliftIO (m :: Type -> Type) where #

Monads which allow their actions to be run in IO.

While MonadIO allows an IO action to be lifted into another monad, this class captures the opposite concept: allowing you to capture the monadic context. Note that, in order to meet the laws given below, the intuition is that a monad must have no monadic state, but may have monadic context. This essentially limits MonadUnliftIO to ReaderT and IdentityT transformers on top of IO.

Laws. For any value u returned by askUnliftIO, it must meet the monad transformer laws as reformulated for MonadUnliftIO:

  • unliftIO u . return = return
  • unliftIO u (m >>= f) = unliftIO u m >>= unliftIO u . f

Instances of MonadUnliftIO must also satisfy the idempotency law:

  • askUnliftIO >>= \u -> (liftIO . unliftIO u) m = m

This law showcases two properties. First, askUnliftIO doesn't change the monadic context, and second, liftIO . unliftIO u is equivalent to id IF called in the same monadic context as askUnliftIO.

Since: unliftio-core-0.1.0.0

Methods

withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b #

Convenience function for capturing the monadic context and running an IO action with a runner function. The runner function is used to run a monadic action m in IO.

Since: unliftio-core-0.1.0.0

Instances

Instances details
MonadUnliftIO IO 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

withRunInIO :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

MonadUnliftIO m => MonadUnliftIO (ResourceT m)

Since: resourcet-1.1.10

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

withRunInIO :: ((forall a. ResourceT m a -> IO a) -> IO b) -> ResourceT m b #

MonadUnliftIO m => MonadUnliftIO (IdentityT m) 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

withRunInIO :: ((forall a. IdentityT m a -> IO a) -> IO b) -> IdentityT m b #

MonadUnliftIO m => MonadUnliftIO (ReaderT r m) 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

withRunInIO :: ((forall a. ReaderT r m a -> IO a) -> IO b) -> ReaderT r m b #

class Monad m => PrimMonad (m :: Type -> Type) where #

Class of monads which can perform primitive state-transformer actions

Associated Types

type PrimState (m :: Type -> Type) #

State token type

Methods

primitive :: (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a #

Execute a primitive operation

Instances

Instances details
PrimMonad IO 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState IO #

Methods

primitive :: (State# (PrimState IO) -> (# State# (PrimState IO), a #)) -> IO a #

PrimMonad (ST s) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ST s) #

Methods

primitive :: (State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), a #)) -> ST s a #

PrimMonad (ST s) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ST s) #

Methods

primitive :: (State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), a #)) -> ST s a #

PrimMonad m => PrimMonad (MaybeT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (MaybeT m) #

Methods

primitive :: (State# (PrimState (MaybeT m)) -> (# State# (PrimState (MaybeT m)), a #)) -> MaybeT m a #

PrimMonad m => PrimMonad (ListT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ListT m) #

Methods

primitive :: (State# (PrimState (ListT m)) -> (# State# (PrimState (ListT m)), a #)) -> ListT m a #

PrimMonad m => PrimMonad (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Associated Types

type PrimState (ResourceT m) #

Methods

primitive :: (State# (PrimState (ResourceT m)) -> (# State# (PrimState (ResourceT m)), a #)) -> ResourceT m a #

PrimMonad m => PrimMonad (ExceptT e m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ExceptT e m) #

Methods

primitive :: (State# (PrimState (ExceptT e m)) -> (# State# (PrimState (ExceptT e m)), a #)) -> ExceptT e m a #

PrimMonad m => PrimMonad (IdentityT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (IdentityT m) #

Methods

primitive :: (State# (PrimState (IdentityT m)) -> (# State# (PrimState (IdentityT m)), a #)) -> IdentityT m a #

(Error e, PrimMonad m) => PrimMonad (ErrorT e m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ErrorT e m) #

Methods

primitive :: (State# (PrimState (ErrorT e m)) -> (# State# (PrimState (ErrorT e m)), a #)) -> ErrorT e m a #

PrimMonad m => PrimMonad (ReaderT r m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ReaderT r m) #

Methods

primitive :: (State# (PrimState (ReaderT r m)) -> (# State# (PrimState (ReaderT r m)), a #)) -> ReaderT r m a #

PrimMonad m => PrimMonad (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (StateT s m) #

Methods

primitive :: (State# (PrimState (StateT s m)) -> (# State# (PrimState (StateT s m)), a #)) -> StateT s m a #

PrimMonad m => PrimMonad (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (StateT s m) #

Methods

primitive :: (State# (PrimState (StateT s m)) -> (# State# (PrimState (StateT s m)), a #)) -> StateT s m a #

(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) #

Methods

primitive :: (State# (PrimState (WriterT w m)) -> (# State# (PrimState (WriterT w m)), a #)) -> WriterT w m a #

(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) #

Methods

primitive :: (State# (PrimState (WriterT w m)) -> (# State# (PrimState (WriterT w m)), a #)) -> WriterT w m a #

(Monoid w, PrimMonad m) => PrimMonad (AccumT w m)

Since: primitive-0.6.3.0

Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (AccumT w m) #

Methods

primitive :: (State# (PrimState (AccumT w m)) -> (# State# (PrimState (AccumT w m)), a #)) -> AccumT w m a #

(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) #

Methods

primitive :: (State# (PrimState (WriterT w m)) -> (# State# (PrimState (WriterT w m)), a #)) -> WriterT w m a #

PrimMonad m => PrimMonad (SelectT r m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (SelectT r m) #

Methods

primitive :: (State# (PrimState (SelectT r m)) -> (# State# (PrimState (SelectT r m)), a #)) -> SelectT r m a #

PrimMonad m => PrimMonad (ContT r m)

Since: primitive-0.6.3.0

Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ContT r m) #

Methods

primitive :: (State# (PrimState (ContT r m)) -> (# State# (PrimState (ContT r m)), a #)) -> ContT r m a #

PrimMonad m => PrimMonad (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Associated Types

type PrimState (ConduitT i o m) #

Methods

primitive :: (State# (PrimState (ConduitT i o m)) -> (# State# (PrimState (ConduitT i o m)), a #)) -> ConduitT i o m a #

(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) #

Methods

primitive :: (State# (PrimState (RWST r w s m)) -> (# State# (PrimState (RWST r w s m)), a #)) -> RWST r w s m a #

(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) #

Methods

primitive :: (State# (PrimState (RWST r w s m)) -> (# State# (PrimState (RWST r w s m)), a #)) -> RWST r w s m a #

(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) #

Methods

primitive :: (State# (PrimState (RWST r w s m)) -> (# State# (PrimState (RWST r w s m)), a #)) -> RWST r w s m a #

PrimMonad m => PrimMonad (Pipe l i o u m) Source # 
Instance details

Defined in Data.Conduit.Internal.Pipe

Associated Types

type PrimState (Pipe l i o u m) #

Methods

primitive :: (State# (PrimState (Pipe l i o u m)) -> (# State# (PrimState (Pipe l i o u m)), a #)) -> Pipe l i o u m a #

ResourceT

class MonadIO m => MonadResource (m :: Type -> Type) #

A Monad which allows for safe resource allocation. In theory, any monad transformer stack which includes a ResourceT can be an instance of MonadResource.

Note: runResourceT has a requirement for a MonadUnliftIO m monad, which allows control operations to be lifted. A MonadResource does not have this requirement. This means that transformers such as ContT can be an instance of MonadResource. However, the ContT wrapper will need to be unwrapped before calling runResourceT.

Since 0.3.0

Minimal complete definition

liftResourceT

Instances

Instances details
MonadResource m => MonadResource (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> MaybeT m a #

MonadResource m => MonadResource (ListT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ListT m a #

MonadIO m => MonadResource (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ResourceT m a #

MonadResource m => MonadResource (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ExceptT e m a #

MonadResource m => MonadResource (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> IdentityT m a #

MonadResource m => MonadResource (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ReaderT r m a #

MonadResource m => MonadResource (StateT s m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> StateT s m a #

MonadResource m => MonadResource (StateT s m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> StateT s m a #

(Monoid w, MonadResource m) => MonadResource (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> WriterT w m a #

(Monoid w, MonadResource m) => MonadResource (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> WriterT w m a #

MonadResource m => MonadResource (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ContT r m a #

MonadResource m => MonadResource (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

liftResourceT :: ResourceT IO a -> ConduitT i o m a #

(Monoid w, MonadResource m) => MonadResource (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> RWST r w s m a #

(Monoid w, MonadResource m) => MonadResource (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> RWST r w s m a #

MonadResource m => MonadResource (Pipe l i o u m) Source # 
Instance details

Defined in Data.Conduit.Internal.Pipe

Methods

liftResourceT :: ResourceT IO a -> Pipe l i o u m a #

data ResourceT (m :: Type -> Type) a #

The Resource transformer. This transformer keeps track of all registered actions, and calls them upon exit (via runResourceT). Actions may be registered via register, or resources may be allocated atomically via allocate. allocate corresponds closely to bracket.

Releasing may be performed before exit via the release function. This is a highly recommended optimization, as it will ensure that scarce resources are freed early. Note that calling release will deregister the action, so that a release action will only ever be called once.

Since 0.3.0

Instances

Instances details
MonadTrans ResourceT 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

lift :: Monad m => m a -> ResourceT m a #

MonadRWS r w s m => MonadRWS r w s (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

MonadWriter w m => MonadWriter w (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

writer :: (a, w) -> ResourceT m a #

tell :: w -> ResourceT m () #

listen :: ResourceT m a -> ResourceT m (a, w) #

pass :: ResourceT m (a, w -> w) -> ResourceT m a #

MonadState s m => MonadState s (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

get :: ResourceT m s #

put :: s -> ResourceT m () #

state :: (s -> (a, s)) -> ResourceT m a #

MonadReader r m => MonadReader r (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

ask :: ResourceT m r #

local :: (r -> r) -> ResourceT m a -> ResourceT m a #

reader :: (r -> a) -> ResourceT m a #

MonadError e m => MonadError e (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

throwError :: e -> ResourceT m a #

catchError :: ResourceT m a -> (e -> ResourceT m a) -> ResourceT m a #

Monad m => Monad (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

(>>=) :: ResourceT m a -> (a -> ResourceT m b) -> ResourceT m b #

(>>) :: ResourceT m a -> ResourceT m b -> ResourceT m b #

return :: a -> ResourceT m a #

Functor m => Functor (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

fmap :: (a -> b) -> ResourceT m a -> ResourceT m b #

(<$) :: a -> ResourceT m b -> ResourceT m a #

MonadFix m => MonadFix (ResourceT m)

Since: resourcet-1.1.8

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

mfix :: (a -> ResourceT m a) -> ResourceT m a #

MonadFail m => MonadFail (ResourceT m)

Since: resourcet-1.2.2

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

fail :: String -> ResourceT m a #

Applicative m => Applicative (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

pure :: a -> ResourceT m a #

(<*>) :: ResourceT m (a -> b) -> ResourceT m a -> ResourceT m b #

liftA2 :: (a -> b -> c) -> ResourceT m a -> ResourceT m b -> ResourceT m c #

(*>) :: ResourceT m a -> ResourceT m b -> ResourceT m b #

(<*) :: ResourceT m a -> ResourceT m b -> ResourceT m a #

MonadIO m => MonadIO (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftIO :: IO a -> ResourceT m a #

Alternative m => Alternative (ResourceT m)

Since 1.1.5

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

empty :: ResourceT m a #

(<|>) :: ResourceT m a -> ResourceT m a -> ResourceT m a #

some :: ResourceT m a -> ResourceT m [a] #

many :: ResourceT m a -> ResourceT m [a] #

MonadPlus m => MonadPlus (ResourceT m)

Since 1.1.5

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

mzero :: ResourceT m a #

mplus :: ResourceT m a -> ResourceT m a -> ResourceT m a #

MonadThrow m => MonadThrow (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

throwM :: Exception e => e -> ResourceT m a #

MonadCatch m => MonadCatch (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

catch :: Exception e => ResourceT m a -> (e -> ResourceT m a) -> ResourceT m a #

MonadMask m => MonadMask (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

mask :: ((forall a. ResourceT m a -> ResourceT m a) -> ResourceT m b) -> ResourceT m b #

uninterruptibleMask :: ((forall a. ResourceT m a -> ResourceT m a) -> ResourceT m b) -> ResourceT m b #

generalBracket :: ResourceT m a -> (a -> ExitCase b -> ResourceT m c) -> (a -> ResourceT m b) -> ResourceT m (b, c) #

MonadCont m => MonadCont (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

callCC :: ((a -> ResourceT m b) -> ResourceT m a) -> ResourceT m a #

PrimMonad m => PrimMonad (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Associated Types

type PrimState (ResourceT m) #

Methods

primitive :: (State# (PrimState (ResourceT m)) -> (# State# (PrimState (ResourceT m)), a #)) -> ResourceT m a #

MonadIO m => MonadResource (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ResourceT m a #

MonadUnliftIO m => MonadUnliftIO (ResourceT m)

Since: resourcet-1.1.10

Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

withRunInIO :: ((forall a. ResourceT m a -> IO a) -> IO b) -> ResourceT m b #

type PrimState (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

runResourceT :: MonadUnliftIO m => ResourceT m a -> m a #

Unwrap a ResourceT transformer, and call all registered release actions.

Note that there is some reference counting involved due to resourceForkIO. If multiple threads are sharing the same collection of resources, only the last call to runResourceT will deallocate the resources.

NOTE Since version 1.2.0, this function will throw a ResourceCleanupException if any of the cleanup functions throw an exception.

Since: resourcet-0.3.0

Acquire

withAcquire :: MonadUnliftIO m => Acquire a -> (a -> m b) -> m b #

Longer name for with, in case with is not obvious enough in context.

Since: resourcet-1.2.0

allocateAcquire :: MonadResource m => Acquire a -> m (ReleaseKey, a) #

Allocate a resource and register an action with the MonadResource to free the resource.

Since: resourcet-1.1.0

mkAcquireType #

Arguments

:: IO a

acquire the resource

-> (a -> ReleaseType -> IO ())

free the resource

-> Acquire a 

Same as mkAcquire, but the cleanup function will be informed of how cleanup was initiated. This allows you to distinguish, for example, between normal and exceptional exits.

Since: resourcet-1.1.2

mkAcquire #

Arguments

:: IO a

acquire the resource

-> (a -> IO ())

free the resource

-> Acquire a 

Create an Acquire value using the given allocate and free functions.

Since: resourcet-1.1.0

data ReleaseType #

The way in which a release is called.

Since: resourcet-1.1.2

Instances

Instances details
Bounded ReleaseType 
Instance details

Defined in Data.Acquire.Internal

Enum ReleaseType 
Instance details

Defined in Data.Acquire.Internal

Eq ReleaseType 
Instance details

Defined in Data.Acquire.Internal

Ord ReleaseType 
Instance details

Defined in Data.Acquire.Internal

Read ReleaseType 
Instance details

Defined in Data.Acquire.Internal

Show ReleaseType 
Instance details

Defined in Data.Acquire.Internal

data Acquire a #

A method for acquiring a scarce resource, providing the means of freeing it when no longer needed. This data type provides Functor/Applicative/Monad instances for composing different resources together. You can allocate these resources using either the bracket pattern (via with) or using ResourceT (via allocateAcquire).

This concept was originally introduced by Gabriel Gonzalez and described at: http://www.haskellforall.com/2013/06/the-resource-applicative.html. The implementation in this package is slightly different, due to taking a different approach to async exception safety.

Since: resourcet-1.1.0

Instances

Instances details
Monad Acquire 
Instance details

Defined in Data.Acquire.Internal

Methods

(>>=) :: Acquire a -> (a -> Acquire b) -> Acquire b #

(>>) :: Acquire a -> Acquire b -> Acquire b #

return :: a -> Acquire a #

Functor Acquire 
Instance details

Defined in Data.Acquire.Internal

Methods

fmap :: (a -> b) -> Acquire a -> Acquire b #

(<$) :: a -> Acquire b -> Acquire a #

Applicative Acquire 
Instance details

Defined in Data.Acquire.Internal

Methods

pure :: a -> Acquire a #

(<*>) :: Acquire (a -> b) -> Acquire a -> Acquire b #

liftA2 :: (a -> b -> c) -> Acquire a -> Acquire b -> Acquire c #

(*>) :: Acquire a -> Acquire b -> Acquire b #

(<*) :: Acquire a -> Acquire b -> Acquire a #

MonadIO Acquire 
Instance details

Defined in Data.Acquire.Internal

Methods

liftIO :: IO a -> Acquire a #

Pure pipelines

newtype Identity a #

Identity functor and monad. (a non-strict monad)

Since: base-4.8.0.0

Constructors

Identity 

Fields

Instances

Instances details
Monad Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

(>>) :: Identity a -> Identity b -> Identity b #

return :: a -> Identity a #

Functor Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

MonadFix Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mfix :: (a -> Identity a) -> Identity a #

Applicative Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

liftA2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Foldable Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

fold :: Monoid m => Identity m -> m #

foldMap :: Monoid m => (a -> m) -> Identity a -> m #

foldMap' :: Monoid m => (a -> m) -> Identity a -> m #

foldr :: (a -> b -> b) -> b -> Identity a -> b #

foldr' :: (a -> b -> b) -> b -> Identity a -> b #

foldl :: (b -> a -> b) -> b -> Identity a -> b #

foldl' :: (b -> a -> b) -> b -> Identity a -> b #

foldr1 :: (a -> a -> a) -> Identity a -> a #

foldl1 :: (a -> a -> a) -> Identity a -> a #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

elem :: Eq a => a -> Identity a -> Bool #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

sum :: Num a => Identity a -> a #

product :: Num a => Identity a -> a #

Traversable Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) #

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) #

sequence :: Monad m => Identity (m a) -> m (Identity a) #

Eq1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Identity a -> Identity b -> Bool #

Ord1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Identity a -> Identity b -> Ordering #

Read1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Identity a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Identity a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Identity a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Identity a] #

Show1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Identity a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Identity a] -> ShowS #

Hashable1 Identity 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Identity a -> Int #

Unbox a => Vector Vector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Unbox a => MVector MVector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Bounded a => Bounded (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Enum a => Enum (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Eq a => Eq (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(==) :: Identity a -> Identity a -> Bool #

(/=) :: Identity a -> Identity a -> Bool #

Floating a => Floating (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Fractional a => Fractional (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Integral a => Integral (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Num a => Num (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Ord a => Ord (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

compare :: Identity a -> Identity a -> Ordering #

(<) :: Identity a -> Identity a -> Bool #

(<=) :: Identity a -> Identity a -> Bool #

(>) :: Identity a -> Identity a -> Bool #

(>=) :: Identity a -> Identity a -> Bool #

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Read a => Read (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Real a => Real (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

toRational :: Identity a -> Rational #

RealFloat a => RealFloat (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

RealFrac a => RealFrac (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

properFraction :: Integral b => Identity a -> (b, Identity a) #

truncate :: Integral b => Identity a -> b #

round :: Integral b => Identity a -> b #

ceiling :: Integral b => Identity a -> b #

floor :: Integral b => Identity a -> b #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Ix a => Ix (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

IsString a => IsString (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.String

Methods

fromString :: String -> Identity a #

Generic (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: Type -> Type #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Semigroup a => Semigroup (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Storable a => Storable (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Bits a => Bits (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

FiniteBits a => FiniteBits (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Hashable a => Hashable (Identity a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Identity a -> Int #

hash :: Identity a -> Int #

MonoFunctor (Identity a) 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Identity a) -> Element (Identity a)) -> Identity a -> Identity a #

MonoFoldable (Identity a) 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Identity a) -> m) -> Identity a -> m #

ofoldr :: (Element (Identity a) -> b -> b) -> b -> Identity a -> b #

ofoldl' :: (a0 -> Element (Identity a) -> a0) -> a0 -> Identity a -> a0 #

otoList :: Identity a -> [Element (Identity a)] #

oall :: (Element (Identity a) -> Bool) -> Identity a -> Bool #

oany :: (Element (Identity a) -> Bool) -> Identity a -> Bool #

onull :: Identity a -> Bool #

olength :: Identity a -> Int #

olength64 :: Identity a -> Int64 #

ocompareLength :: Integral i => Identity a -> i -> Ordering #

otraverse_ :: Applicative f => (Element (Identity a) -> f b) -> Identity a -> f () #

ofor_ :: Applicative f => Identity a -> (Element (Identity a) -> f b) -> f () #

omapM_ :: Applicative m => (Element (Identity a) -> m ()) -> Identity a -> m () #

oforM_ :: Applicative m => Identity a -> (Element (Identity a) -> m ()) -> m () #

ofoldlM :: Monad m => (a0 -> Element (Identity a) -> m a0) -> a0 -> Identity a -> m a0 #

ofoldMap1Ex :: Semigroup m => (Element (Identity a) -> m) -> Identity a -> m #

ofoldr1Ex :: (Element (Identity a) -> Element (Identity a) -> Element (Identity a)) -> Identity a -> Element (Identity a) #

ofoldl1Ex' :: (Element (Identity a) -> Element (Identity a) -> Element (Identity a)) -> Identity a -> Element (Identity a) #

headEx :: Identity a -> Element (Identity a) #

lastEx :: Identity a -> Element (Identity a) #

unsafeHead :: Identity a -> Element (Identity a) #

unsafeLast :: Identity a -> Element (Identity a) #

maximumByEx :: (Element (Identity a) -> Element (Identity a) -> Ordering) -> Identity a -> Element (Identity a) #

minimumByEx :: (Element (Identity a) -> Element (Identity a) -> Ordering) -> Identity a -> Element (Identity a) #

oelem :: Element (Identity a) -> Identity a -> Bool #

onotElem :: Element (Identity a) -> Identity a -> Bool #

MonoTraversable (Identity a) 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Identity a) -> f (Element (Identity a))) -> Identity a -> f (Identity a) #

omapM :: Applicative m => (Element (Identity a) -> m (Element (Identity a))) -> Identity a -> m (Identity a) #

MonoPointed (Identity a) 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Identity a) -> Identity a #

Prim a => Prim (Identity a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Unbox a => Unbox (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Generic1 Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep1 Identity :: k -> Type #

Methods

from1 :: forall (a :: k). Identity a -> Rep1 Identity a #

to1 :: forall (a :: k). Rep1 Identity a -> Identity a #

newtype MVector s (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Identity a) = MV_Identity (MVector s a)
type Rep (Identity a) 
Instance details

Defined in Data.Functor.Identity

type Rep (Identity a) = D1 ('MetaData "Identity" "Data.Functor.Identity" "base" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Element (Identity a) 
Instance details

Defined in Data.MonoTraversable

type Element (Identity a) = a
newtype Vector (Identity a) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Identity a) = V_Identity (Vector a)
type Rep1 Identity 
Instance details

Defined in Data.Functor.Identity

type Rep1 Identity = D1 ('MetaData "Identity" "Data.Functor.Identity" "base" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))