module Data.Machines.Encoding.Text ( decodeLatin1 , encodeUtf8, decodeUtf8 ) where import Data.ByteString (ByteString) import Data.Machine import Data.Text (Text) import qualified Data.Text.Encoding as TE {- | Convert a stream of ByteStrings to a stream of Text - by transorming the bytes from the Latin1 encoding. -} decodeLatin1 :: Process ByteString Text decodeLatin1 = auto TE.decodeLatin1 {-# INLINE decodeLatin1 #-} {- | Convert a stream of Text to a stream of ByteStrings - by transorming the symboles to the UTF-8 encoding. -} encodeUtf8 :: Process Text ByteString encodeUtf8 = auto TE.encodeUtf8 {-# LANGUAGE encodeUtf8 #-} {- | Convert a stream of ByteStrings to a stream of Text - by transorming the bytes from the UTF-8 encoding. -} decodeUtf8 :: Process ByteString Text decodeUtf8 = auto . Mealy $ runDecode . TE.streamDecodeUtf8 where runDecode :: TE.Decoding -> (Text, Mealy ByteString Text) runDecode (TE.Some r _ c) = (r, Mealy $ runDecode . c) {-# INLINE runDecode #-} {-# INLINE decodeUtf8 #-}