Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Internal definition of types
Synopsis
- data UnexpectedDecodeEx where
- UnexpectedDecodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> UnexpectedDecodeEx
- data EncodeEx where
- EncodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> EncodeEx
- data RecreateEx where
- RecreateEx :: (Show e, KnownSymbol x) => Proxy x -> e -> RecreateEx
- RecreateExUnkStep :: Show e => e -> RecreateEx
- recreateErrUnknown :: Show e => e -> RecreateEx
- implEncodeF_ :: (Show err, KnownSymbol x) => Proxy x -> (str -> Either err str) -> Enc enc1 conf str -> Either EncodeEx (Enc enc2 conf str)
- implEncodeF :: forall x enc1 enc2 err conf str. (Show err, KnownSymbol x) => (str -> Either err str) -> Enc enc1 conf str -> Either EncodeEx (Enc enc2 conf str)
- implEncodeF_' :: (Show err, KnownSymbol x) => Proxy x -> (conf -> str -> Either err str) -> Enc enc1 conf str -> Either EncodeEx (Enc enc2 conf str)
- module Data.TypedEncoding.Internal.Types.Enc
- module Data.TypedEncoding.Internal.Types.CheckedEnc
- module Data.TypedEncoding.Internal.Types.UncheckedEnc
- module Data.TypedEncoding.Internal.Types.Common
Documentation
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.
UnexpectedDecodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> UnexpectedDecodeEx |
Instances
Show UnexpectedDecodeEx Source # | |
Defined in Data.TypedEncoding.Internal.Types showsPrec :: Int -> UnexpectedDecodeEx -> ShowS # show :: UnexpectedDecodeEx -> String # showList :: [UnexpectedDecodeEx] -> ShowS # | |
UnexpectedDecodeErr (Either UnexpectedDecodeEx) Source # | |
Represents errors in encoding
EncodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> EncodeEx |
Instances
Show EncodeEx Source # | |
EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source # | |
Defined in Data.TypedEncoding.Instances.Restriction.UTF8 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
Following test uses \(b :: B.ByteString) -> verEncoding b (fmap (fromEncoding . decodeAll . proxiedId (Proxy :: Proxy (Enc '["r-UTF8"] _ _))) . (encodeFAll :: _ -> Either EncodeEx _). toEncoding () $ b) |
Defined in Data.TypedEncoding.Instances.Restriction.UTF8 encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-UTF8" ': xs) c ByteString) Source # | |
(IsStringR str, IsString str) => EncodeF (Either EncodeEx) (Enc xs c str) (Enc ("r-Word8-decimal" ': xs) c str :: Type) Source # | |
EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-ASCII" ': xs) c ByteString :: Type) Source # | |
Defined in Data.TypedEncoding.Instances.Restriction.ASCII 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 # | |
Defined in Data.TypedEncoding.Instances.Restriction.ASCII 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 # | |
EncodeF (Either EncodeEx) (Enc xs c Text) (Enc ("r-ASCII" ': xs) c Text :: Type) Source # | |
EncodeF (Either EncodeEx) (Enc xs c Char) (Enc ("r-ASCII" ': xs) c Char :: Type) Source # | |
data RecreateEx where Source #
Represents errors in recovery (recreation of encoded types).
RecreateEx :: (Show e, KnownSymbol x) => Proxy x -> e -> RecreateEx | |
RecreateExUnkStep :: Show e => e -> RecreateEx |
Instances
Show RecreateEx Source # | |
Defined in Data.TypedEncoding.Internal.Types showsPrec :: Int -> RecreateEx -> ShowS # show :: RecreateEx -> String # showList :: [RecreateEx] -> ShowS # | |
RecreateErr (Either RecreateEx) Source # | |
Defined in Data.TypedEncoding.Internal.Class.Recreate recoveryErr :: RecreateEx -> Either RecreateEx a Source # |
recreateErrUnknown :: Show e => e -> RecreateEx Source #
implEncodeF_ :: (Show err, KnownSymbol x) => Proxy x -> (str -> Either err str) -> Enc enc1 conf str -> Either EncodeEx (Enc enc2 conf str) Source #
implEncodeF :: forall x enc1 enc2 err conf str. (Show err, KnownSymbol x) => (str -> Either err str) -> Enc enc1 conf str -> Either EncodeEx (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 #