typed-encoding-0.2.2.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Internal.Class.Recreate

Synopsis

Documentation

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 ByteString :: Type) (Enc ("r-UTF8" ': xs) c ByteString) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.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.Restriction.UTF8

Methods

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

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

Defined in Data.TypedEncoding.Instances.Restriction.Common

Methods

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

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

Defined in Data.TypedEncoding.Instances.Restriction.Common

Methods

checkPrevF :: Enc ("r-Word8-decimal" ': xs) c str -> f (Enc xs c str) 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.Enc.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.Enc.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.Enc.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.Enc.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.Enc.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.Enc.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 Text :: Type) (Enc ("do-UPPER" ': xs) c Text) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.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 ByteString :: Type) (Enc ("r-ASCII" ': xs) c ByteString) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.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.Restriction.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.Restriction.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.Restriction.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 String :: Type) (Enc ("r-ASCII" ': xs) c String) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

checkPrevF :: Enc ("r-ASCII" ': xs) c String -> f (Enc xs c String) 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 :: [Symbol]) 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 ([] :: [Symbol]) c str Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Class.Recreate

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

Defined in Data.TypedEncoding.Internal.Class.Recreate

Methods

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

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

recreateAll :: forall xs c str. RecreateFAll Identity xs c str => Enc '[] c str -> Enc xs c str Source #

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

Useful for partially manual recreation

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

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

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

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 #

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