typed-encoding-0.1.0.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Internal.Types

Description

Internal definition of types

Synopsis

Documentation

data Enc enc conf str where Source #

Constructors

MkEnc :: Proxy enc -> conf -> str -> Enc enc conf str

constructor is to be treated as Unsafe to Encode and Decode instance implementations particular encoding instances may expose smart constructors for limited data types

Instances
(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("do-UPPER" ': xs) c Text) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

checkPrevF :: Enc ("do-UPPER" ': xs) c Text -> f (Enc xs c Text) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("enc-B64" ': xs) c Text) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

checkPrevF :: Enc ("enc-B64" ': xs) c Text -> f (Enc xs c Text) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("enc-B64" ': xs) c Text) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

checkPrevF :: Enc ("enc-B64" ': xs) c Text -> f (Enc xs c Text) Source #

Applicative f => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("enc-B64-len" ': xs) c ByteString) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

checkPrevF :: Enc ("enc-B64-len" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("enc-B64" ': xs) c ByteString) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

checkPrevF :: Enc ("enc-B64" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

Applicative f => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("enc-B64-len" ': xs) c ByteString) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

checkPrevF :: Enc ("enc-B64-len" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("enc-B64" ': xs) c ByteString) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

checkPrevF :: Enc ("enc-B64" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-UTF8" ': xs) c ByteString) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.UTF8

Methods

checkPrevF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-UTF8" ': xs) c ByteString) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.UTF8

Methods

checkPrevF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-ASCII" ': xs) c ByteString) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

checkPrevF :: Enc ("r-ASCII" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-ASCII" ': xs) c ByteString) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

checkPrevF :: Enc ("r-ASCII" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("r-ASCII" ': xs) c Text) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

checkPrevF :: Enc ("r-ASCII" ': xs) c Text -> f (Enc xs c Text) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("r-ASCII" ': xs) c Text) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

checkPrevF :: Enc ("r-ASCII" ': xs) c Text -> f (Enc xs c Text) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("my-sign" ': xs) c Text) Source #

Recreation allows effectful f to check for tampering with data. Implementation simply uses implCheckPrevF combinator on the recovery function.

Instance details

Defined in Examples.TypedEncoding.DiySignEncoding

Methods

checkPrevF :: Enc ("my-sign" ': xs) c Text -> f (Enc xs c Text) Source #

(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c Text) (Enc xs c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

decodeF :: Enc ("enc-B64" ': xs) c Text -> f (Enc xs c Text) Source #

(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c Text) (Enc xs c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

decodeF :: Enc ("enc-B64" ': xs) c Text -> f (Enc xs c Text) Source #

(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

decodeF :: Enc ("enc-B64" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source #

Effectful instance for corruption detection. This protocol is used, for example, in emails. It is a well known encoding and hackers will have no problem making undetectable changes, but error handling at this stage could verify that email was corrupted.

Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

decodeF :: Enc ("enc-B64" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-UTF8" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.UTF8

Methods

decodeF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-UTF8" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.UTF8

Methods

decodeF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

decodeF :: Enc ("r-ASCII" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

decodeF :: Enc ("r-ASCII" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c Text) (Enc xs c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

decodeF :: Enc ("r-ASCII" ': xs) c Text -> f (Enc xs c Text) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c Text) (Enc xs c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

decodeF :: Enc ("r-ASCII" ': xs) c Text -> f (Enc xs c Text) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c Char) (Enc xs c Char :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

decodeF :: Enc ("r-ASCII" ': xs) c Char -> f (Enc xs c Char) Source #

(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("my-sign" ': xs) c Text) (Enc xs c Text :: Type) Source #

Decoding allows effectful f to allow for troubleshooting and unsafe payload changes.

Implementation simply uses implDecodeF combinator on the asUnexpected composed with decoding function. UnexpectedDecodeErr has Identity instance allowing for decoding that assumes errors are not possible. For debugging purposes or when unsafe changes to "my-sign" Error UnexpectedDecodeEx instance can be used.

Instance details

Defined in Examples.TypedEncoding.DiySignEncoding

Methods

decodeF :: Enc ("my-sign" ': xs) c Text -> f (Enc xs c Text) Source #

(HasA c SizeLimit, Applicative f) => EncodeF (f :: Type -> Type) (Enc xs c ByteString) (Enc ("do-size-limit" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

encodeF :: Enc xs c ByteString -> f (Enc ("do-size-limit" ': xs) c ByteString) Source #

(HasA c SizeLimit, Applicative f) => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-size-limit" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-size-limit" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-reverse" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-reverse" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-reverse" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-reverse" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-Title" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-Title" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-Title" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-Title" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-lower" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-lower" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-lower" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-lower" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-UPPER" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-UPPER" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-UPPER" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Encode.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-UPPER" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("enc-B64" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

encodeF :: Enc xs c Text -> f (Enc ("enc-B64" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("enc-B64" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

encodeF :: Enc xs c Text -> f (Enc ("enc-B64" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c ByteString) (Enc ("enc-B64" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

encodeF :: Enc xs c ByteString -> f (Enc ("enc-B64" ': xs) c ByteString) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c ByteString) (Enc ("enc-B64" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

encodeF :: Enc xs c ByteString -> f (Enc ("enc-B64" ': xs) c ByteString) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("my-sign" ': xs) c Text :: Type) Source #

Because encoding function is pure we can create instance of EncodeF that is polymorphic in effect f. This is done using implTranP combinator.

Instance details

Defined in Examples.TypedEncoding.DiySignEncoding

Methods

encodeF :: Enc xs c Text -> f (Enc ("my-sign" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.UTF8

Methods

encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-UTF8" ': xs) c ByteString) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source #

UTF8 encodings are defined for ByteString only as that would not make much sense for Text

>>> encodeFAll . toEncoding () $ "\xc3\xb1" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Right (MkEnc Proxy () "\195\177")
>>> encodeFAll . toEncoding () $ "\xc3\x28" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Left (EncodeEx "r-UTF8" (Cannot decode byte '\xc3': Data.Text.Internal.Encoding.decodeUtf8: Invalid UTF-8 stream))

Following test uses verEncoding helper that checks that bytes are encoded as Right iff they are valid UTF8 bytes

\(b :: B.ByteString) -> verEncoding b (fmap (fromEncoding . decodeAll . proxiedId (Proxy :: Proxy (Enc '["r-UTF8"] _ _))) . (encodeFAll :: _ -> Either EncodeEx _). toEncoding () $ b)
Instance details

Defined in Data.TypedEncoding.Instances.UTF8

Methods

encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-UTF8" ': xs) c ByteString) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-ASCII" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-ASCII" ': xs) c ByteString) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-ASCII" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-ASCII" ': xs) c ByteString) Source #

EncodeF (Either EncodeEx) (Enc xs c Text) (Enc ("r-ASCII" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

encodeF :: Enc xs c Text -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c Text) (Enc ("r-ASCII" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

encodeF :: Enc xs c Text -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c Char) (Enc ("r-ASCII" ': xs) c Char :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

encodeF :: Enc xs c Char -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Char) Source #

(Eq conf, Eq str) => Eq (Enc enc conf str) Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Types

Methods

(==) :: Enc enc conf str -> Enc enc conf str -> Bool #

(/=) :: Enc enc conf str -> Enc enc conf str -> Bool #

(Show conf, Show str) => Show (Enc enc conf str) Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Types

Methods

showsPrec :: Int -> Enc enc conf str -> ShowS #

show :: Enc enc conf str -> String #

showList :: [Enc enc conf str] -> ShowS #

(Displ (Proxy xs), Show c, Displ str) => Displ (Enc xs c str) Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

displ :: Enc xs c str -> String Source #

toEncoding :: conf -> str -> Enc '[] conf str Source #

fromEncoding :: Enc '[] conf str -> str Source #

implTranF :: Functor f => (str -> f str) -> Enc enc1 conf str -> f (Enc enc2 conf str) Source #

implEncodeF :: (Show err, KnownSymbol x) => Proxy x -> (str -> Either err str) -> Enc enc1 conf str -> Either EncodeEx (Enc enc2 conf str) Source #

implDecodeF :: Functor f => (str -> f str) -> Enc enc1 conf str -> f (Enc enc2 conf str) Source #

implCheckPrevF :: Functor f => (str -> f str) -> Enc enc1 conf str -> f (Enc enc2 conf str) Source #

implTranF' :: Functor f => (conf -> str -> f str) -> Enc enc1 conf str -> f (Enc enc2 conf str) Source #

implEncodeF' :: (Show err, KnownSymbol x) => Proxy x -> (conf -> str -> Either err str) -> Enc enc1 conf str -> Either EncodeEx (Enc enc2 conf str) Source #

implDecodeF' :: Functor f => (conf -> str -> f str) -> Enc enc1 conf str -> f (Enc enc2 conf str) Source #

implTranP :: Applicative f => (str -> str) -> Enc enc1 conf str -> f (Enc enc2 conf str) Source #

implEncodeP :: Applicative f => (str -> str) -> Enc enc1 conf str -> f (Enc enc2 conf str) Source #

implTranP' :: Applicative f => (conf -> str -> str) -> Enc enc1 conf str -> f (Enc enc2 conf str) Source #

implEncodeP' :: Applicative f => (conf -> str -> str) -> Enc enc1 conf str -> f (Enc enc2 conf str) Source #

getPayload :: Enc enc conf str -> str Source #

unsafeSetPayload :: conf -> str -> Enc enc conf str Source #

withUnsafeCoerce :: (s1 -> s2) -> Enc e1 c s1 -> Enc e2 c s2 Source #

unsafeChangePayload :: (s1 -> s2) -> Enc e c s1 -> Enc e c s2 Source #

data RecreateEx where Source #

Represents errors in recovery (recreation of encoded types).

Constructors

RecreateEx :: (Show e, KnownSymbol x) => Proxy x -> e -> RecreateEx 

data EncodeEx where Source #

Represents errors in encoding

Constructors

EncodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> EncodeEx 
Instances
Show EncodeEx Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Types

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.UTF8

Methods

encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-UTF8" ': xs) c ByteString) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source #

UTF8 encodings are defined for ByteString only as that would not make much sense for Text

>>> encodeFAll . toEncoding () $ "\xc3\xb1" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Right (MkEnc Proxy () "\195\177")
>>> encodeFAll . toEncoding () $ "\xc3\x28" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Left (EncodeEx "r-UTF8" (Cannot decode byte '\xc3': Data.Text.Internal.Encoding.decodeUtf8: Invalid UTF-8 stream))

Following test uses verEncoding helper that checks that bytes are encoded as Right iff they are valid UTF8 bytes

\(b :: B.ByteString) -> verEncoding b (fmap (fromEncoding . decodeAll . proxiedId (Proxy :: Proxy (Enc '["r-UTF8"] _ _))) . (encodeFAll :: _ -> Either EncodeEx _). toEncoding () $ b)
Instance details

Defined in Data.TypedEncoding.Instances.UTF8

Methods

encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-UTF8" ': xs) c ByteString) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-ASCII" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-ASCII" ': xs) c ByteString) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-ASCII" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-ASCII" ': xs) c ByteString) Source #

EncodeF (Either EncodeEx) (Enc xs c Text) (Enc ("r-ASCII" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

encodeF :: Enc xs c Text -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c Text) (Enc ("r-ASCII" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

encodeF :: Enc xs c Text -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c Char) (Enc ("r-ASCII" ': xs) c Char :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

encodeF :: Enc xs c Char -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Char) Source #

data UnexpectedDecodeEx where Source #

Type safety over encodings makes decoding process safe. However failures are still possible due to bugs or unsafe payload modifications. UnexpectedDecodeEx represents such errors.

Constructors

UnexpectedDecodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> UnexpectedDecodeEx