typed-encoding-0.2.0.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding

Contents

Description

Overview

This library allows to specify and work with types like

-- Base 64 encoded bytes (could represent binary files)
Enc '["enc-B64"] ByteString

-- Base 64 encoded UTF8 bytes
Enc '["enc-B64", "r-UTF8"] ByteString

-- Text that contains only ASCII characters
Enc '["r-ASCII"] Text

or to do transformations to strings like

upper :: Text -> Enc '["do-UPPER"] Text
upper = ...

or define precise types to use with toEncString and fromEncString

date :: Enc '["r-date-%d%b%Y:%X %Z"] Text
date = toEncString ...

Primary focus of type-encodings is to provide type safe

  • encoding
  • decoding
  • recreation (verification of existing payload)
  • type conversions between encoded types

of string-like data (ByteString, Text) that is subject of some encoding or formatting restrictions.

as well as

  • toEncString
  • fromEncString

conversions.

Groups of annotations

typed-encoding uses type annotations grouped into semantic categories

"r-" restriction / predicate

  • encoding is a partial identity
  • recreation is a partial identity (matching encoding)
  • decoding is identity

Examples: "r-UTF8", "r-ASCII"

"do-" transformations

  • encoding applies transformation to the string (could be partial)
  • decoding - typically none
  • recreation - typically none but, if present, verifies the payload has expected data (e.g. only uppercase chars for "do-UPPER")

Examples: "do-UPPER", "do-lower", "do-reverse"

"enc-" data encoding that is not "r-"

  • encoding applies encoding transformation to the string (could be partial)
  • decoding reverses the transformation (can be used as pure function)
  • recreation verifies that the payload has correctly encoded data

Examples: "enc-B64"

Usage

To use this library import this module and one or more instance module.

Here is list of instance modules available in typed-encoding library itself

This list is not intended to be exhaustive, rather separate libraries can provide instances for other encodings and transformations.

To implement a new encoding import this module and

Examples

Examples of how to use this library are included in

Synopsis

Classes

Combinators

Types

data Enc enc conf str 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, IsString 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 ("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 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 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 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 #

(HasA SizeLimit c, Applicative f) => EncodeF (f :: Type -> Type) (Enc xs c ByteString) (Enc ("do-size-limit" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.Sample

Methods

encodeF :: Enc xs c ByteString -> f (Enc ("do-size-limit" ': xs) c ByteString) Source #

(HasA SizeLimit c, Applicative f) => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-size-limit" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-size-limit" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-reverse" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-reverse" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-reverse" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-reverse" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-Title" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-Title" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-Title" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-Title" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-lower" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-lower" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-lower" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-lower" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-UPPER" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-UPPER" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("do-UPPER" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Do.Sample

Methods

encodeF :: Enc xs c Text -> f (Enc ("do-UPPER" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("enc-B64" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Enc.Base64

Methods

encodeF :: Enc xs c Text -> f (Enc ("enc-B64" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("enc-B64" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Enc.Base64

Methods

encodeF :: Enc xs c Text -> f (Enc ("enc-B64" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c ByteString) (Enc ("enc-B64" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Enc.Base64

Methods

encodeF :: Enc xs c ByteString -> f (Enc ("enc-B64" ': xs) c ByteString) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c ByteString) (Enc ("enc-B64" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Enc.Base64

Methods

encodeF :: Enc xs c ByteString -> f (Enc ("enc-B64" ': xs) c ByteString) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("my-sign" ': xs) c Text :: Type) Source #

Because encoding function is pure we can create instance of EncodeF that is polymorphic in effect f. This is done using implTranP combinator.

Instance details

Defined in Examples.TypedEncoding.DiySignEncoding

Methods

encodeF :: Enc xs c Text -> f (Enc ("my-sign" ': xs) c Text) 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 #

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, IsString 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 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 #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.UTF8

Methods

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

>>> encodeFAll . toEncoding () $ "\xc3\xb1" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Right (MkEnc Proxy () "\195\177")
>>> encodeFAll . toEncoding () $ "\xc3\x28" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Left (EncodeEx "r-UTF8" (Cannot decode byte '\xc3': Data.Text.Internal.Encoding.decodeUtf8: Invalid UTF-8 stream))

Following test uses verEncoding helper that checks that bytes are encoded as Right iff they are valid UTF8 bytes

\(b :: B.ByteString) -> verEncoding b (fmap (fromEncoding . decodeAll . proxiedId (Proxy :: Proxy (Enc '["r-UTF8"] _ _))) . (encodeFAll :: _ -> Either EncodeEx _). toEncoding () $ b)
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.UTF8

Methods

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 # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Common

Methods

encodeF :: Enc xs c str -> Either EncodeEx (Enc ("r-Word8-decimal" ': xs) c str) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-ASCII" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

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 # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

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 # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

encodeF :: Enc xs c Text -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c Text) (Enc ("r-ASCII" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

encodeF :: Enc xs c Text -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c Char) (Enc ("r-ASCII" ': xs) c Char :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

encodeF :: Enc xs c Char -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Char) Source #

(Eq conf, Eq str) => Eq (Enc enc conf str) Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Types.Enc

Methods

(==) :: Enc enc conf str -> Enc enc conf str -> Bool #

(/=) :: Enc enc conf str -> Enc enc conf str -> Bool #

(Show conf, Show str) => Show (Enc enc conf str) Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Types.Enc

Methods

showsPrec :: Int -> Enc enc conf str -> ShowS #

show :: Enc enc conf str -> String #

showList :: [Enc enc conf str] -> ShowS #

(SymbolList xs, Show c, Displ str) => Displ (Enc xs c str) Source #
>>> let disptest = unsafeSetPayload () "hello" :: Enc '["TEST"] () T.Text
>>> displ disptest
"MkEnc '[TEST] () (Text hello)"
Instance details

Defined in Data.TypedEncoding.Internal.Types.Enc

Methods

displ :: Enc xs c str -> String Source #

data CheckedEnc conf str Source #

Represents some validated encoded string.

CheckedEnc is untyped version of Enc. CheckedEnc contains verified encoded data, encoding is visible at the value level only.

Instances
(Eq conf, Eq str) => Eq (CheckedEnc conf str) Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Types.CheckedEnc

Methods

(==) :: CheckedEnc conf str -> CheckedEnc conf str -> Bool #

(/=) :: CheckedEnc conf str -> CheckedEnc conf str -> Bool #

(Show conf, Show str) => Show (CheckedEnc conf str) Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Types.CheckedEnc

Methods

showsPrec :: Int -> CheckedEnc conf str -> ShowS #

show :: CheckedEnc conf str -> String #

showList :: [CheckedEnc conf str] -> ShowS #

(Show c, Displ str) => Displ (CheckedEnc c str) Source #
>>> displ $ unsafeCheckedEnc ["TEST"] () ("hello" :: T.Text)
"MkCheckedEnc [TEST] () (Text hello)"
Instance details

Defined in Data.TypedEncoding.Internal.Types.CheckedEnc

Methods

displ :: CheckedEnc c str -> String Source #

data EncodeEx where Source #

Represents errors in encoding

Constructors

EncodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> EncodeEx 
Instances
Show EncodeEx Source # 
Instance details

Defined in Data.TypedEncoding.Internal.Types

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.UTF8

Methods

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

>>> encodeFAll . toEncoding () $ "\xc3\xb1" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Right (MkEnc Proxy () "\195\177")
>>> encodeFAll . toEncoding () $ "\xc3\x28" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Left (EncodeEx "r-UTF8" (Cannot decode byte '\xc3': Data.Text.Internal.Encoding.decodeUtf8: Invalid UTF-8 stream))

Following test uses verEncoding helper that checks that bytes are encoded as Right iff they are valid UTF8 bytes

\(b :: B.ByteString) -> verEncoding b (fmap (fromEncoding . decodeAll . proxiedId (Proxy :: Proxy (Enc '["r-UTF8"] _ _))) . (encodeFAll :: _ -> Either EncodeEx _). toEncoding () $ b)
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.UTF8

Methods

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 # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Common

Methods

encodeF :: Enc xs c str -> Either EncodeEx (Enc ("r-Word8-decimal" ': xs) c str) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-ASCII" ': xs) c ByteString :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

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 # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

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 # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

encodeF :: Enc xs c Text -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c Text) (Enc ("r-ASCII" ': xs) c Text :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

encodeF :: Enc xs c Text -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Text) Source #

EncodeF (Either EncodeEx) (Enc xs c Char) (Enc ("r-ASCII" ': xs) c Char :: Type) Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

encodeF :: Enc xs c Char -> Either EncodeEx (Enc ("r-ASCII" ': xs) c Char) Source #

data RecreateEx where Source #

Represents errors in recovery (recreation of encoded types).

Constructors

RecreateEx :: (Show e, KnownSymbol x) => Proxy x -> e -> RecreateEx 
RecreateExUnkStep :: Show e => e -> RecreateEx 

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.

Constructors

UnexpectedDecodeEx :: (Show a, KnownSymbol x) => Proxy x -> a -> UnexpectedDecodeEx 

type EncAnn = String Source #

Represents value level (single) annotation.

Existentially quantified version of Enc and basic combinators

Types and combinators for not verfied encoding

Basic Enc Combinators

getPayload :: Enc enc conf str -> str Source #

unsafeSetPayload :: conf -> str -> Enc enc conf str Source #

fromEncoding :: Enc '[] conf str -> str Source #

toEncoding :: conf -> str -> Enc '[] conf str Source #

Basic CheckedEnc Combinators

unsafeCheckedEnc :: [EncAnn] -> c -> s -> CheckedEnc c s Source #

toCheckedEnc :: forall xs c str. SymbolList xs => Enc xs c str -> CheckedEnc c str Source #

fromCheckedEnc :: forall xs c str. SymbolList xs => CheckedEnc c str -> Maybe (Enc xs c str) Source #

Other Basic Combinators