Copyright | (c) 2018 Composewell Technologies (c) Bjoern Hoehrmann 2008-2009 |
---|---|
License | BSD3 |
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
- decodeUtf8Lax :: (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
- decodeUtf8ArraysLenient :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char
- encodeLatin1 :: (IsStream t, Monad m) => t m Char -> t m Word8
- encodeLatin1Lax :: (IsStream t, Monad m) => t m Char -> t m Word8
- encodeUtf8 :: (Monad m, IsStream t) => t m Char -> t m Word8
- decodeUtf8D :: Monad m => Stream m Word8 -> Stream m Char
- encodeUtf8D :: Monad m => Stream m Char -> Stream m Word8
- decodeUtf8LenientD :: Monad m => Stream m Word8 -> Stream m Char
- 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
- decodeUtf8ArraysLenientD :: MonadIO m => Stream m (Array Word8) -> Stream m Char
- stripStart :: (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
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
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 incoming stream is truncated if an invalid codepoint is encountered.
Since: 0.7.0
decodeUtf8Lax :: (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
data DecodeError Source #
Instances
Show DecodeError Source # | |
Defined in Streamly.Internal.Data.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 #
Internal
resumeDecodeUtf8Either :: (Monad m, IsStream t) => DecodeState -> CodePoint -> t m Word8 -> t m (Either DecodeError Char) Source #
Internal
decodeUtf8ArraysLenient :: (MonadIO m, IsStream t) => t m (Array Word8) -> t m Char Source #
Internal
Elimination (Encoding)
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.7.0
encodeLatin1Lax :: (IsStream t, Monad m) => t m Char -> t m Word8 Source #
Like encodeLatin1
but silently truncates and maps input characters beyond
255 to (incorrect) chars in 0-255 range. No error or exception is thrown
when such truncation occurs.
Since: 0.7.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.
Since: 0.7.0
StreamD UTF8 Encoding / Decoding transformations.
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 #
Transformation
stripStart :: (Monad m, IsStream t) => t m Char -> t m Char Source #
Remove leading whitespace from a string.
stripStart = S.dropWhile isSpace
Internal
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.
>>>
S.toList $ lines FL.toList (S.fromList "lines\nthis\nstring\n\n\n")
["lines", "this", "string", "", ""]
lines = S.splitOnSuffix (== '\n')
Internal
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.
>>>
S.toList $ words FL.toList (S.fromList "fold these words")
["fold", "these", "words"]
words = S.wordsBy isSpace
Internal