typed-encoding-0.2.2.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Internal.Class.Decode

Synopsis

Documentation

class DecodeF f instr outstr where Source #

Methods

decodeF :: instr -> f outstr Source #

Instances
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.Restriction.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.Restriction.UTF8

Methods

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

(IsStringR str, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("r-Int-decimal" ': xs) c str) (Enc xs c str :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Common

Methods

decodeF :: Enc ("r-Int-decimal" ': xs) c str -> f (Enc xs c str) Source #

(IsStringR str, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("r-Word8-decimal" ': xs) c str) (Enc xs c str :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Common

Methods

decodeF :: Enc ("r-Word8-decimal" ': xs) c str -> f (Enc xs c str) 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.Enc.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.Enc.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.Enc.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.Enc.Base64

Methods

decodeF :: Enc ("enc-B64" ': 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.Restriction.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.Restriction.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.Restriction.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.Restriction.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 String) (Enc xs c String :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

decodeF :: Enc ("r-ASCII" ': xs) c String -> f (Enc xs c String) 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.Restriction.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 :: [Symbol]) c str where Source #

Methods

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

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

Defined in Data.TypedEncoding.Internal.Class.Decode

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) c str Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class.Decode

Methods

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

decodeAll :: forall xs c str. DecodeFAll Identity (xs :: [Symbol]) c str => Enc xs c str -> Enc '[] 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 #

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

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

decodePart :: forall (xs :: [Symbol]) xsf c str. DecodeFAll Identity xs c str => Enc (Append xs xsf) c str -> Enc xsf c str Source #

class UnexpectedDecodeErr f where Source #

With type safety in place decoding errors should be unexpected. This class can be used to provide extra info if decoding could fail

asUnexpected :: forall x f err a. (KnownSymbol x, UnexpectedDecodeErr f, Applicative f, Show err) => Either err a -> f a Source #