Safe Haskell | None |
---|---|
Language | Haskell2010 |
Contains type save equivalents of the following functions defined in encoding:
encodeStrictByteStringExplicit
encodeLazyByteStringExplicit
encString
decodeStrictByteStringExplicit
decodeLazyByteStringExplicit
decodeStringExplicit
Warnings
These conversions are provides AS-IS and assume that encoding functions behave in a way consistent with typed-encoding type definitions.
For example, typed-encoding effectively guarantees that decode function will never fail
and it is safe to use Identity
instance of the UnexpectedDecodeErr
class.
In encoding v0.8.5, the decoding can fail after the encoding succeeded:
>>>
Encoding.encodeStringExplicit EncCP932.CP932 "\DEL"
Right "\DEL">>>
Encoding.decodeStringExplicit EncCP932.CP932 "\DEL"
Left (IllegalCharacter 127)
Here are some other peculiarities:
cp1257 is a single bit encoding and one could expect this to fail, but it succeeds:
>>>
Encoding.encodeStringExplicit (Encoding.encodingFromString "cp1257") "\x100"
Right "\194"
Decoding can also be surprising:
>>>
Encoding.decodeStringExplicit EncASCII.ASCII "\236\239"
Right "\236\239"
here is UTF8 decoding
>>>
Encoding.decodeStringExplicit EncUTF8.UTF8 "\192\NUL"
Right "\NUL">>>
Encoding.encodeStringExplicit EncUTF8.UTF8 "\NUL"
Right "\NUL"
This package does not try to fix these issues, only provides a wrapper that annotates encodings as symbols.
Synopsis
- type family IsDynEnc (s :: Symbol) :: Bool where ...
- type DynEnc s = (KnownSymbol s, IsDynEnc s ~ True)
- encodeStrictByteStringExplicit :: forall s xs c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Enc xs c String -> Either EncodeEx (Enc (s ': xs) c ByteString)
- encodeLazyByteStringExplicit :: forall s xs c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Enc xs c String -> Either EncodeEx (Enc (s ': xs) c ByteString)
- encodeStringExplicit :: forall s xs c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Enc xs c String -> Either EncodeEx (Enc (s ': xs) c String)
- encString :: forall s xs c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Encoding (Either EncodeEx) s "enc-pkg/encoding" c String
- decodeStrictByteStringExplicit :: forall s xs f c. (UnexpectedDecodeErr f, Monad f, DynEnc s, Algorithm s "enc-pkg/encoding") => Enc (s ': xs) c ByteString -> f (Enc xs c String)
- decodeLazyByteStringExplicit :: forall s xs f c. (UnexpectedDecodeErr f, Monad f, DynEnc s, Algorithm s "enc-pkg/encoding") => Enc (s ': xs) c ByteString -> f (Enc xs c String)
- decodeStringExplicit :: forall s xs f c. (UnexpectedDecodeErr f, Monad f, DynEnc s, Algorithm s "enc-pkg/encoding") => Enc (s ': xs) c String -> f (Enc xs c String)
- decString :: forall s xs f c. (UnexpectedDecodeErr f, Monad f, DynEnc s, Algorithm s "enc-pkg/encoding") => Decoding f s "enc-pkg/encoding" c String
- getDynEncoding :: forall s xs c str. DynEnc s => Enc (s ': xs) c str -> DynEncoding
- exferDynEncoding :: (KnownSymbol s, DynEnc s) => Proxy s -> Either String DynEncoding
Documentation
>>>
:set -XOverloadedStrings -XDataKinds -XTypeApplications -XFlexibleContexts
>>>
import Data.Functor.Identity
>>>
import qualified Data.TypedEncoding as Usage
>>>
import Data.Encoding.ASCII as EncASCII
>>>
import Data.Encoding.UTF8 as EncUTF8
>>>
import Data.Encoding.CP932 as EncCP932
Conversion To ByteString
encodeStrictByteStringExplicit :: forall s xs c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Enc xs c String -> Either EncodeEx (Enc (s ': xs) c ByteString) Source #
encodeStrictByteStringExplicit
creates values of types like
Enc '["enc-pkg/encoding:cyrillic"] () ByteString
>>>
fmap Typed.displ . encodeStrictByteStringExplicit @"enc-pkg/encoding:cyrillic" . Typed.toEncoding () $ "а на животе кнопка"
Right "Enc '[enc-pkg/encoding:cyrillic] () (ByteString \208 \221\208 \214\216\210\222\226\213 \218\221\222\223\218\208)"
>>>
fmap Typed.displ . encodeStrictByteStringExplicit @"enc-pkg/encoding:koi8_r" . Typed.toEncoding () $ "а на животе кнопка"
Right "Enc '[enc-pkg/encoding:koi8_r] () (ByteString \193 \206\193 \214\201\215\207\212\197 \203\206\207\208\203\193)"
>>>
"а на животе кнопка"
"\1072 \1085\1072 \1078\1080\1074\1086\1090\1077 \1082\1085\1086\1087\1082\1072"
>>>
"Статья"
"\1057\1090\1072\1090\1100\1103"
>>>
fmap Typed.displ . encodeStrictByteStringExplicit @"enc-pkg/encoding:cyrillic" . Typed.toEncoding () $ "Статья"
Right "Enc '[enc-pkg/encoding:cyrillic] () (ByteString \193\226\208\226\236\239)"
>>>
encodeStrictByteStringExplicit @"enc-pkg/encoding:ascii" . Typed.toEncoding () $ "Статья"
Left (EncodeEx "enc-pkg/encoding:ascii" (HasNoRepresentation '\1057'))
>>>
fmap Typed.displ . encodeStrictByteStringExplicit @"enc-pkg/encoding:ascii" . Typed.toEncoding () $ "story"
Right "Enc '[enc-pkg/encoding:ascii] () (ByteString story)"
encodeLazyByteStringExplicit :: forall s xs c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Enc xs c String -> Either EncodeEx (Enc (s ': xs) c ByteString) Source #
Converts String
to some Enc '["enc-pkg/encoding:..."] () BL.ByteString
type
by actually encoding characters in the String into correct byte layout.
Conversion to encoded String
encodeStringExplicit :: forall s xs c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Enc xs c String -> Either EncodeEx (Enc (s ': xs) c String) Source #
Converts String
to some Enc '["enc-pkg/encoding:..."] () String
type
by actually encoding characters in the String into a certain byte layout.
The resulting payload has all Characters representing bytes, that is < '\255'
encString :: forall s xs c. (DynEnc s, Algorithm s "enc-pkg/encoding") => Encoding (Either EncodeEx) s "enc-pkg/encoding" c String Source #
Conversion From ByteString
decodeStrictByteStringExplicit :: forall s xs f c. (UnexpectedDecodeErr f, Monad f, DynEnc s, Algorithm s "enc-pkg/encoding") => Enc (s ': xs) c ByteString -> f (Enc xs c String) Source #
>>>
fmap Typed.displ $ decodeStrictByteStringExplicit @"enc-pkg/encoding:cyrillic" @'[] @Identity (Typed.unsafeSetPayload () "\193\226\208\226\236\239")
Identity "Enc '[] () (String \1057\1090\1072\1090\1100\1103)"
decodeLazyByteStringExplicit :: forall s xs f c. (UnexpectedDecodeErr f, Monad f, DynEnc s, Algorithm s "enc-pkg/encoding") => Enc (s ': xs) c ByteString -> f (Enc xs c String) Source #
Conversion From encoded String
decodeStringExplicit :: forall s xs f c. (UnexpectedDecodeErr f, Monad f, DynEnc s, Algorithm s "enc-pkg/encoding") => Enc (s ': xs) c String -> f (Enc xs c String) Source #
decString :: forall s xs f c. (UnexpectedDecodeErr f, Monad f, DynEnc s, Algorithm s "enc-pkg/encoding") => Decoding f s "enc-pkg/encoding" c String Source #
Helpers
getDynEncoding :: forall s xs c str. DynEnc s => Enc (s ': xs) c str -> DynEncoding Source #
Provides type safety over existence of DynEncoding
Implementation
exferDynEncoding :: (KnownSymbol s, DynEnc s) => Proxy s -> Either String DynEncoding Source #