Copyright | 2011 Michael Snoyman, 2010-2011 John Millikin |
---|---|
License | MIT |
Safe Haskell | None |
Language | Haskell98 |
Handle streams of text.
Parts of this code were taken from enumerator and adapted for conduits.
For many purposes, it's recommended to use the conduit-combinators library, which provides a more complete set of functions.
- data Codec
- encode :: MonadThrow m => Codec -> Conduit Text m ByteString
- decode :: MonadThrow m => Codec -> Conduit ByteString m Text
- utf8 :: Codec
- utf16_le :: Codec
- utf16_be :: Codec
- utf32_le :: Codec
- utf32_be :: Codec
- ascii :: Codec
- iso8859_1 :: Codec
- lines :: Monad m => Conduit Text m Text
- linesBounded :: MonadThrow m => Int -> Conduit Text m Text
- data TextException
- takeWhile :: Monad m => (Char -> Bool) -> Conduit Text m Text
- dropWhile :: Monad m => (Char -> Bool) -> Consumer Text m ()
- take :: Monad m => Int -> Conduit Text m Text
- drop :: Monad m => Int -> Consumer Text m ()
- foldLines :: Monad m => (a -> ConduitM Text o m a) -> a -> ConduitM Text o m a
- withLine :: Monad m => Sink Text m a -> Consumer Text m (Maybe a)
- decodeUtf8 :: MonadThrow m => Conduit ByteString m Text
- decodeUtf8Lenient :: Monad m => Conduit ByteString m Text
- encodeUtf8 :: Monad m => Conduit Text m ByteString
- detectUtf :: MonadThrow m => Conduit ByteString m Text
Text codecs
encode :: MonadThrow m => Codec -> Conduit Text m ByteString Source
Convert text into bytes, using the provided codec. If the codec is not capable of representing an input character, an exception will be thrown.
Since 0.3.0
decode :: MonadThrow m => Codec -> Conduit ByteString m Text Source
Convert bytes into text, using the provided codec. If the codec is not capable of decoding an input byte sequence, an exception will be thrown.
Since 0.3.0
linesBounded :: MonadThrow m => Int -> Conduit Text m Text Source
Variant of the lines function with an integer parameter. The text length of any emitted line never exceeds the value of the parameter. Whenever this is about to happen a LengthExceeded exception is thrown. This function should be used instead of the lines function whenever we are dealing with user input (e.g. a file upload) because we can't be sure that user input won't have extraordinarily large lines which would require large amounts of memory if consumed.
data TextException Source
Since 0.3.0
decodeUtf8 :: MonadThrow m => Conduit ByteString m Text Source
Decode a stream of UTF8-encoded bytes into a stream of text, throwing an exception on invalid input.
Since 1.0.15
decodeUtf8Lenient :: Monad m => Conduit ByteString m Text Source
Decode a stream of UTF8 data, and replace invalid bytes with the Unicode replacement character.
Since 1.1.1
encodeUtf8 :: Monad m => Conduit Text m ByteString Source
Encode a stream of text into a stream of bytes.
Since 1.0.15
detectUtf :: MonadThrow m => Conduit ByteString m Text Source
Automatically determine which UTF variant is being used. This function checks for BOMs, removing them as necessary. It defaults to assuming UTF-8.
Since 1.1.9