Copyright | (c) 2018 Composewell Technologies (c) Bjoern Hoehrmann 2008-2009 |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- decodeLatin1 :: (IsStream t, Monad m) => t m Word8 -> t m Char
- decodeUtf8 :: (Monad m, IsStream t) => t m Word8 -> t m Char
- decodeUtf8' :: (Monad m, IsStream t) => t m Word8 -> t m Char
- decodeUtf8_ :: (Monad m, IsStream t) => t m Word8 -> t m Char
- data DecodeError = DecodeError !DecodeState !CodePoint
- type DecodeState = Word8
- type CodePoint = Int
- decodeUtf8Either :: (Monad m, IsStream t) => t m Word8 -> t m (Either DecodeError Char)
- resumeDecodeUtf8Either :: (Monad m, IsStream t) => DecodeState -> CodePoint -> t m Word8 -> t m (Either DecodeError Char)
- decodeUtf8Arrays :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char
- decodeUtf8Arrays' :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char
- decodeUtf8Arrays_ :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char
- encodeLatin1 :: (IsStream t, Monad m) => t m Char -> t m Word8
- encodeLatin1' :: (IsStream t, Monad m) => t m Char -> t m Word8
- encodeLatin1_ :: (IsStream t, Monad m) => t m Char -> t m Word8
- encodeUtf8 :: (Monad m, IsStream t) => t m Char -> t m Word8
- encodeUtf8' :: (Monad m, IsStream t) => t m Char -> t m Word8
- encodeUtf8_ :: (Monad m, IsStream t) => t m Char -> t m Word8
- encodeStrings :: (MonadIO m, IsStream t) => (SerialT m Char -> SerialT m Word8) -> t m String -> t m (Array Word8)
- stripHead :: (Monad m, IsStream t) => t m Char -> t m Char
- lines :: (Monad m, IsStream t) => Fold m Char b -> t m Char -> t m b
- words :: (Monad m, IsStream t) => Fold m Char b -> t m Char -> t m b
- unlines :: (MonadIO m, IsStream t) => Unfold m a Char -> t m a -> t m Char
- unwords :: (MonadIO m, IsStream t) => Unfold m a Char -> t m a -> t m Char
- decodeUtf8D :: Monad m => Stream m Word8 -> Stream m Char
- decodeUtf8D' :: Monad m => Stream m Word8 -> Stream m Char
- decodeUtf8D_ :: Monad m => Stream m Word8 -> Stream m Char
- encodeUtf8D :: Monad m => Stream m Char -> Stream m Word8
- encodeUtf8D' :: Monad m => Stream m Char -> Stream m Word8
- encodeUtf8D_ :: Monad m => Stream m Char -> Stream m Word8
- decodeUtf8EitherD :: Monad m => Stream m Word8 -> Stream m (Either DecodeError Char)
- resumeDecodeUtf8EitherD :: Monad m => DecodeState -> CodePoint -> Stream m Word8 -> Stream m (Either DecodeError Char)
- decodeUtf8ArraysD :: MonadIO m => Stream m (Array Word8) -> Stream m Char
- decodeUtf8ArraysD' :: MonadIO m => Stream m (Array Word8) -> Stream m Char
- decodeUtf8ArraysD_ :: MonadIO m => Stream m (Array Word8) -> Stream m Char
- decodeUtf8Lax :: (IsStream t, Monad m) => t m Word8 -> t m Char
- encodeLatin1Lax :: (IsStream t, Monad m) => t m Char -> t m Word8
- encodeUtf8Lax :: (IsStream t, Monad m) => t m Char -> t m Word8
Construction (Decoding)
decodeLatin1 :: (IsStream t, Monad m) => t m Word8 -> t m Char Source #
Decode a stream of bytes to Unicode characters by mapping each byte to a
corresponding Unicode Char
in 0-255 range.
Since: 0.7.0 (Streamly.Data.Unicode.Stream)
Since: 0.8.0
UTF-8 Decoding
decodeUtf8 :: (Monad m, IsStream t) => t m Word8 -> t m Char Source #
Decode a UTF-8 encoded bytestream to a stream of Unicode characters. Any invalid codepoint encountered is replaced with the unicode replacement character.
Since: 0.7.0 (Streamly.Data.Unicode.Stream)
Since: 0.8.0 (Lenient Behaviour)
decodeUtf8' :: (Monad m, IsStream t) => t m Word8 -> t m Char Source #
Decode a UTF-8 encoded bytestream to a stream of Unicode characters. The function throws an error if an invalid codepoint is encountered.
Since: 0.8.0
decodeUtf8_ :: (Monad m, IsStream t) => t m Word8 -> t m Char Source #
Decode a UTF-8 encoded bytestream to a stream of Unicode characters. Any invalid codepoint encountered is dropped.
Since: 0.8.0
Resumable UTF-8 Decoding
data DecodeError Source #
Instances
Show DecodeError Source # | |
Defined in Streamly.Internal.Unicode.Stream showsPrec :: Int -> DecodeError -> ShowS # show :: DecodeError -> String # showList :: [DecodeError] -> ShowS # |
type DecodeState = Word8 Source #
decodeUtf8Either :: (Monad m, IsStream t) => t m Word8 -> t m (Either DecodeError Char) Source #
Pre-release
resumeDecodeUtf8Either :: (Monad m, IsStream t) => DecodeState -> CodePoint -> t m Word8 -> t m (Either DecodeError Char) Source #
Pre-release
UTF-8 Array Stream Decoding
Elimination (Encoding)
Latin1 Encoding
encodeLatin1 :: (IsStream t, Monad m) => t m Char -> t m Word8 Source #
Like encodeLatin1'
but silently maps input codepoints beyond 255 to
arbitrary Latin1 chars in 0-255 range. No error or exception is thrown when
such mapping occurs.
Since: 0.7.0 (Streamly.Data.Unicode.Stream)
Since: 0.8.0 (Lenient Behaviour)
encodeLatin1' :: (IsStream t, Monad m) => t m Char -> t m Word8 Source #
Encode a stream of Unicode characters to bytes by mapping each character to a byte in 0-255 range. Throws an error if the input stream contains characters beyond 255.
Since: 0.8.0
encodeLatin1_ :: (IsStream t, Monad m) => t m Char -> t m Word8 Source #
Like encodeLatin1
but drops the input characters beyond 255.
Since: 0.8.0
UTF-8 Encoding
encodeUtf8 :: (Monad m, IsStream t) => t m Char -> t m Word8 Source #
Encode a stream of Unicode characters to a UTF-8 encoded bytestream. Any Invalid characters (U+D800-U+D8FF) in the input stream are replaced by the Unicode replacement character U+FFFD.
Since: 0.7.0 (Streamly.Data.Unicode.Stream)
Since: 0.8.0 (Lenient Behaviour)
encodeUtf8' :: (Monad m, IsStream t) => t m Char -> t m Word8 Source #
Encode a stream of Unicode characters to a UTF-8 encoded bytestream. When any invalid character (U+D800-U+D8FF) is encountered in the input stream the function errors out.
Since: 0.8.0
encodeUtf8_ :: (Monad m, IsStream t) => t m Char -> t m Word8 Source #
Encode a stream of Unicode characters to a UTF-8 encoded bytestream. Any Invalid characters (U+D800-U+D8FF) in the input stream are dropped.
Since: 0.8.0
encodeStrings :: (MonadIO m, IsStream t) => (SerialT m Char -> SerialT m Word8) -> t m String -> t m (Array Word8) Source #
Encode a stream of String
using the supplied encoding scheme. Each
string is encoded as an Array Word8
.
Since: 0.8.0
Transformation
stripHead :: (Monad m, IsStream t) => t m Char -> t m Char Source #
Remove leading whitespace from a string.
stripHead = S.dropWhile isSpace
Pre-release
lines :: (Monad m, IsStream t) => Fold m Char b -> t m Char -> t m b Source #
Fold each line of the stream using the supplied Fold
and stream the result.
>>>
Stream.toList $ lines Fold.toList (Stream.fromList "lines\nthis\nstring\n\n\n")
["lines","this","string","",""]
lines = S.splitOnSuffix (== '\n')
Pre-release
words :: (Monad m, IsStream t) => Fold m Char b -> t m Char -> t m b Source #
Fold each word of the stream using the supplied Fold
and stream the result.
>>>
Stream.toList $ words Fold.toList (Stream.fromList "fold these words")
["fold","these","words"]
words = S.wordsBy isSpace
Pre-release
unlines :: (MonadIO m, IsStream t) => Unfold m a Char -> t m a -> t m Char Source #
Unfold a stream to character streams using the supplied Unfold
and concat the results suffixing a newline character \n
to each stream.
unlines = Stream.interposeSuffix 'n' unlines = Stream.intercalateSuffix Unfold.fromList "n"
Pre-release
unwords :: (MonadIO m, IsStream t) => Unfold m a Char -> t m a -> t m Char Source #
Unfold the elements of a stream to character streams using the supplied
Unfold
and concat the results with a whitespace character infixed between
the streams.
unwords = Stream.interpose ' ' unwords = Stream.intercalate Unfold.fromList " "
Pre-release
StreamD UTF8 Encoding / Decoding transformations.
encodeUtf8D :: Monad m => Stream m Char -> Stream m Word8 Source #
See section "3.9 Unicode Encoding Forms" in https://www.unicode.org/versions/Unicode13.0.0/UnicodeStandard-13.0.pdf
decodeUtf8EitherD :: Monad m => Stream m Word8 -> Stream m (Either DecodeError Char) Source #
resumeDecodeUtf8EitherD :: Monad m => DecodeState -> CodePoint -> Stream m Word8 -> Stream m (Either DecodeError Char) Source #
Deprecations
decodeUtf8Lax :: (IsStream t, Monad m) => t m Word8 -> t m Char Source #
Deprecated: Please use decodeUtf8
instead
Same as decodeUtf8
encodeLatin1Lax :: (IsStream t, Monad m) => t m Char -> t m Word8 Source #
Deprecated: Please use encodeLatin1
instead
Same as encodeLatin1
encodeUtf8Lax :: (IsStream t, Monad m) => t m Char -> t m Word8 Source #
Deprecated: Please use encodeUtf8
instead
Same as encodeUtf8