Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Internal definition of types
Synopsis
- data RecreateEx where
- RecreateEx :: (Show e, KnownSymbol x) => Proxy x -> e -> RecreateEx
- RecreateExUnkStep :: Show e => e -> RecreateEx
- recreateErrUnknown :: Show e => e -> RecreateEx
- data EncodeEx where
- EncodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> EncodeEx
- asEncodeEx :: (Show a, KnownSymbol x) => Proxy x -> Either a b -> Either EncodeEx b
- encToRecrEx :: EncodeEx -> RecreateEx
- mergeEncodeEx :: KnownSymbol x => Proxy x -> EncodeEx -> Maybe EncodeEx -> EncodeEx
- emptyEncErr :: KnownSymbol x => Proxy x -> EncodeEx
- data UnexpectedDecodeEx where
- UnexpectedDecodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> UnexpectedDecodeEx
- mergeErrs :: err -> (err -> Maybe err -> err) -> Either err a -> Either err b -> Either err c
Documentation
>>>
:set -XOverloadedStrings -XMultiParamTypeClasses -XDataKinds -XAllowAmbiguousTypes
>>>
import qualified Data.Text as T
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.Common.Types.Exceptions showsPrec :: Int -> RecreateEx -> ShowS # show :: RecreateEx -> String # showList :: [RecreateEx] -> ShowS # | |
IsStringR str => Validate (Either RecreateEx) "r-Int-decimal" "r-Int-decimal" c str Source # | |
Defined in Data.TypedEncoding.Instances.Restriction.Misc validation :: Validation (Either RecreateEx) "r-Int-decimal" "r-Int-decimal" c str Source # | |
IsStringR str => Validate (Either RecreateEx) "r-Word8-decimal" "r-Word8-decimal" c str Source # | |
Defined in Data.TypedEncoding.Instances.Restriction.Misc validation :: Validation (Either RecreateEx) "r-Word8-decimal" "r-Word8-decimal" c str Source # | |
RecreateErr (Either RecreateEx) Source # | |
Defined in Data.TypedEncoding.Common.Class.Validate recoveryErr :: RecreateEx -> Either RecreateEx a Source # |
recreateErrUnknown :: Show e => e -> RecreateEx Source #
Represents errors in encoding @since 0.1.0.0
EncodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> EncodeEx |
Instances
Show EncodeEx Source # | |
(Ban s, Algorithm s "r-ban", IsStringR str) => Encode (Either EncodeEx) s "r-ban" c str Source # | |
Char8Find str => Encode (Either EncodeEx) "r-ASCII" "r-ASCII" c str Source # | |
Encode (Either EncodeEx) "r-ASCII" "r-ASCII" c Char Source # | |
Encode (Either EncodeEx) "r-ByteRep" "r-ByteRep" c String Source # | |
Encode (Either EncodeEx) "r-ByteRep" "r-ByteRep" c ByteString Source # | |
Encode (Either EncodeEx) "r-ByteRep" "r-ByteRep" c ByteString Source # | |
Encode (Either EncodeEx) "r-ByteRep" "r-ByteRep" c Char Source # | |
IsStringR str => Encode (Either EncodeEx) "r-Int-decimal" "r-Int-decimal" c str Source # | |
Encode (Either EncodeEx) "r-UNICODE.D76" "r-UNICODE.D76" c String Source # | |
Encode (Either EncodeEx) "r-UNICODE.D76" "r-UNICODE.D76" c Char Source # | |
Encode (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source # | |
Encode (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source # | UTF8 encodings are defined for ByteString only as that would not make much sense for Text
Following test uses
|
IsStringR str => Encode (Either EncodeEx) "r-Word8-decimal" "r-Word8-decimal" c str Source # | |
asEncodeEx :: (Show a, KnownSymbol x) => Proxy x -> Either a b -> Either EncodeEx b Source #
Since: 0.2.2.0
encToRecrEx :: EncodeEx -> RecreateEx Source #
Useful when manually recreating using recovery @since 0.2.2.0
mergeEncodeEx :: KnownSymbol x => Proxy x -> EncodeEx -> Maybe EncodeEx -> EncodeEx Source #
Since: 0.2.1.0
emptyEncErr :: KnownSymbol x => Proxy x -> EncodeEx Source #
Since: 0.2.1.0
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.
Since: 0.1.0.0
UnexpectedDecodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> UnexpectedDecodeEx |
Instances
Show UnexpectedDecodeEx Source # | |
Defined in Data.TypedEncoding.Common.Types.Exceptions showsPrec :: Int -> UnexpectedDecodeEx -> ShowS # show :: UnexpectedDecodeEx -> String # showList :: [UnexpectedDecodeEx] -> ShowS # | |
UnexpectedDecodeErr (Either UnexpectedDecodeEx) Source # | |