typed-encoding-0.1.0.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Internal.Class

Contents

Synopsis

Documentation

>>> :set -XScopedTypeVariables -XKindSignatures -XMultiParamTypeClasses -XDataKinds -XPolyKinds -XFlexibleInstances -XFlexibleContexts
>>> import Data.TypedEncoding.Internal.Types (unsafeSetPayload)

class EncodeF f instr outstr where Source #

Methods

encodeF :: instr -> f outstr Source #

Instances
(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 #

class EncodeFAll f (xs :: [k]) c str where Source #

Methods

encodeFAll :: Enc '[] c str -> f (Enc xs c str) Source #

Instances
Applicative f => EncodeFAll f ([] :: [k]) c str Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

encodeFAll :: Enc [] c str -> f (Enc [] c str) Source #

(Monad f, EncodeFAll f xs c str, EncodeF f (Enc xs c str) (Enc (x ': xs) c str)) => EncodeFAll f (x ': xs :: [k]) c str Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

encodeFAll :: Enc [] c str -> f (Enc (x ': xs) c str) Source #

encodeAll :: EncodeFAll Identity (xs :: [k]) c str => Enc '[] c str -> Enc xs c str Source #

class DecodeF f instr outstr where Source #

Methods

decodeF :: instr -> f outstr Source #

Instances
(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 #

class DecodeFAll f (xs :: [k]) c str where Source #

Methods

decodeFAll :: Enc xs c str -> f (Enc '[] c str) Source #

Instances
Applicative f => DecodeFAll f ([] :: [k]) c str Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

decodeFAll :: Enc [] c str -> f (Enc [] c str) Source #

(Monad f, DecodeFAll f xs c str, DecodeF f (Enc (x ': xs) c str) (Enc xs c str)) => DecodeFAll f (x ': xs :: [k]) c str Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

decodeFAll :: Enc (x ': xs) c str -> f (Enc [] c str) Source #

decodeAll :: DecodeFAll Identity (xs :: [k]) c str => Enc xs c str -> Enc '[] c str Source #

class RecreateF f instr outstr where Source #

Used to safely recover encoded data validating all encodingss

Methods

checkPrevF :: outstr -> f instr Source #

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 #

class Functor f => RecreateFAll f (xs :: [k]) c str where Source #

Minimal complete definition

checkFAll

Methods

checkFAll :: Enc xs c str -> f (Enc '[] c str) Source #

recreateFAll :: Enc '[] c str -> f (Enc xs c str) Source #

Instances
Applicative f => RecreateFAll f ([] :: [k]) c str Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

checkFAll :: Enc [] c str -> f (Enc [] c str) Source #

recreateFAll :: Enc [] c str -> f (Enc [] c str) Source #

(Monad f, RecreateFAll f xs c str, RecreateF f (Enc xs c str) (Enc (x ': xs) c str)) => RecreateFAll f (x ': xs :: [k]) c str Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

checkFAll :: Enc (x ': xs) c str -> f (Enc [] c str) Source #

recreateFAll :: Enc [] c str -> f (Enc (x ': xs) c str) Source #

recreateAll :: RecreateFAll Identity (xs :: [k]) c str => Enc '[] c str -> Enc xs c str Source #

type family Append (xs :: [k]) (ys :: [k]) :: [k] where ... Source #

TODO use singletons definition instead?

Equations

Append '[] xs = xs 
Append (y ': ys) xs = y ': Append ys xs 

encodeFPart :: forall f xs xsf c str. (Functor f, EncodeFAll f xs c str) => Proxy xs -> Enc xsf c str -> f (Enc (Append xs xsf) c str) Source #

encodePart :: EncodeFAll Identity (xs :: [k]) c str => Proxy xs -> Enc xsf c str -> Enc (Append xs xsf) c str Source #

decodeFPart :: forall f xs xsf c str. (Functor f, DecodeFAll f xs c str) => Proxy xs -> Enc (Append xs xsf) c str -> f (Enc xsf c str) Source #

Unsafe implementation guarded by safe type definition

decodePart :: DecodeFAll Identity (xs :: [k]) c str => Proxy xs -> Enc (Append xs xsf) c str -> Enc xsf c str Source #

class Subset (x :: k) (y :: k) where Source #

Minimal complete definition

Nothing

Methods

inject :: Proxy y -> Enc (x ': xs) c str -> Enc (y ': xs) c str Source #

Instances
Subset "r-ASCII" "r-UTF8" Source #

allow to treat ASCII encodings as UTF8 forgetting about B64 encoding

>>> let Right tstAscii = encodeFAll . toEncoding () $ "Hello World" :: Either EncodeEx (Enc '["r-ASCII"] () T.Text)
>>> displ (inject (Proxy :: Proxy "r-UTF8") tstAscii)
"MkEnc '[r-UTF8] () (Text Hello World)"
Instance details

Defined in Data.TypedEncoding.Instances.ASCII

Methods

inject :: Proxy "r-UTF8" -> Enc ("r-ASCII" ': xs) c str -> Enc ("r-UTF8" ': xs) c str Source #

class FlattenAs (x :: k) (y :: k) where Source #

Minimal complete definition

Nothing

Methods

flattenAs :: Proxy y -> Enc (x ': xs) c str -> Enc '[y] c str Source #

Instances
FlattenAs "enc-B64" "r-ASCII" Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

flattenAs :: Proxy "r-ASCII" -> Enc ("enc-B64" ': xs) c str -> Enc ("r-ASCII" ': []) c str Source #

FlattenAs "enc-B64-nontext" "r-ASCII" Source #

allow to treat B64 encodings as ASCII forgetting about B64 encoding

>>> let tstB64 = encodeAll . toEncoding () $ "Hello World" :: Enc '["enc-B64"] () B.ByteString
>>> displ (flattenAs (Proxy :: Proxy "r-ASCII") tstB64 :: Enc '["r-ASCII"] () B.ByteString)
"MkEnc '[r-ASCII] () (ByteString SGVsbG8gV29ybGQ=)"
Instance details

Defined in Data.TypedEncoding.Instances.Base64

Methods

flattenAs :: Proxy "r-ASCII" -> Enc ("enc-B64-nontext" ': xs) c str -> Enc ("r-ASCII" ': []) c str Source #

class HasA c a where Source #

Polymorphic data payloads used to encode/decode

Methods

has :: Proxy a -> c -> a Source #

Instances
HasA a () Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

has :: Proxy () -> a -> () Source #

HasA Config SizeLimit Source # 
Instance details

Defined in Examples.TypedEncoding.Overview

class UnexpectedDecodeErr f where Source #

With type safety in pace decoding errors should be unexpected this class can be used to provide extra info if decoding could fail

class RecreateErr f where Source #

Recovery errors are expected unless Recovery allows Identity instance

Methods

recoveryErr :: RecreateEx -> f a Source #

asRecreateErr :: (RecreateErr f, Applicative f, Show err, KnownSymbol x) => Proxy x -> Either err a -> f a Source #

Display

class Displ x where Source #

Human friendly version of Show

Methods

displ :: x -> String Source #

Instances
Displ String Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

displ :: String -> String Source #

Displ ByteString Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Displ ByteString Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Displ Text Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

displ :: Text -> String Source #

Displ Text Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

displ :: Text -> String Source #

(pxs ~ Proxy xs, Displ pxs, KnownSymbol x) => Displ (Proxy (x ': xs)) Source #
>>> displ (Proxy :: Proxy ["FIRST", "SECOND"])
"FIRST,SECOND"
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

displ :: Proxy (x ': xs) -> String Source #

Displ (Proxy ([] :: [k])) Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class

Methods

displ :: Proxy [] -> String Source #

(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 #

errorOnLeft :: Show err => Either err a -> a Source #