Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- class DecodeF f instr outstr where
- decodeF :: instr -> f outstr
- class DecodeFAll f (xs :: [Symbol]) c str where
- decodeFAll :: Enc xs c str -> f (Enc '[] c str)
- decodeAll :: forall xs c str. DecodeFAll Identity (xs :: [Symbol]) c str => Enc xs c str -> Enc '[] c str
- 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)
- 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)
- decodePart_ :: DecodeFAll Identity (xs :: [Symbol]) c str => Proxy xs -> Enc (Append xs xsf) c str -> Enc xsf c str
- decodePart :: forall (xs :: [Symbol]) xsf c str. DecodeFAll Identity xs c str => Enc (Append xs xsf) c str -> Enc xsf c str
- class UnexpectedDecodeErr f where
- unexpectedDecodeErr :: UnexpectedDecodeEx -> f a
- asUnexpected_ :: (KnownSymbol x, UnexpectedDecodeErr f, Applicative f, Show err) => Proxy x -> Either err a -> f a
- asUnexpected :: forall x f err a. (KnownSymbol x, UnexpectedDecodeErr f, Applicative f, Show err) => Either err a -> f a
Documentation
class DecodeF f instr outstr where Source #
Instances
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-UTF8" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # | |
Defined in Data.TypedEncoding.Instances.Restriction.UTF8 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 # | |
Defined in Data.TypedEncoding.Instances.Restriction.UTF8 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 # | |
(IsStringR str, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("r-Word8-decimal" ': xs) c str) (Enc xs c str :: Type) Source # | |
(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c Text) (Enc xs c Text :: Type) Source # | |
(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c Text) (Enc xs c Text :: Type) Source # | |
(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # | |
Defined in Data.TypedEncoding.Instances.Enc.Base64 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. |
Defined in Data.TypedEncoding.Instances.Enc.Base64 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 # | |
Defined in Data.TypedEncoding.Instances.Restriction.ASCII 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 # | |
Defined in Data.TypedEncoding.Instances.Restriction.ASCII 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 # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c Text) (Enc xs c Text :: Type) Source # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c String) (Enc xs c String :: Type) Source # | |
Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-ASCII" ': xs) c Char) (Enc xs c Char :: Type) Source # | |
(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("my-sign" ': xs) c Text) (Enc xs c Text :: Type) Source # | Decoding allows effectful Implementation simply uses |
class DecodeFAll f (xs :: [Symbol]) c str where Source #
decodeFAll :: Enc xs c str -> f (Enc '[] c str) Source #
Instances
Applicative f => DecodeFAll f ([] :: [Symbol]) c str Source # | |
Defined in Data.TypedEncoding.Internal.Class.Decode 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 # | |
Defined in Data.TypedEncoding.Internal.Class.Decode 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
unexpectedDecodeErr :: UnexpectedDecodeEx -> f a Source #
Instances
UnexpectedDecodeErr Identity Source # | |
Defined in Data.TypedEncoding.Internal.Class.Decode | |
UnexpectedDecodeErr (Either UnexpectedDecodeEx) Source # | |
asUnexpected_ :: (KnownSymbol x, UnexpectedDecodeErr f, Applicative f, Show err) => Proxy x -> Either err a -> f a Source #
asUnexpected :: forall x f err a. (KnownSymbol x, UnexpectedDecodeErr f, Applicative f, Show err) => Either err a -> f a Source #