typed-encoding-0.5.2.2: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding

Contents

Description

Overview

This library uses TypeLits symbols 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"] c Text
upper = ...

or to 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
  • validation (recreation) (verification of existing payload)
  • safe type conversions between encoded types
  • combinators for creating new encodings from existing encodings (e.g. by applying Boolean rules)

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
  • validation is a partial identity (matching encoding)
  • decoding is identity

Examples: "r-UTF8", "r-ASCII", upper alpha-numeric bound r-ban restrictions like "r-ban:999-999-9999"

"do-" transformations

(not provided in this library other than as Examples Examples.TypedEncoding.Instances.Do.Sample)

  • encoding applies transformation to the string (could be partial)
  • decoding - typically none
  • validation - 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 now be used as pure function)
  • validation verifies that the payload has correctly encoded data

Examples: "enc-B64"

Call Site Usage

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

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

... and needed conversions.

Conversion combinator module structure is similar to the one found in text and bytestring packages.

Conversion is typed-encoding are safe and reversible!

Please see comments in

for more information.

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

New encoding instance creation

To implement a new encoding import

Examples

Examples of how to use this library are included in

Synopsis

Enc and basic combinators

data Enc nms conf str Source #

Contains encoded data annotated by

  • nms list of Symbols with encoding names (encoding stack)
  • conf that can contain configuration / encoding information such as digest.
  • str the encoded data

Example:

Enc '["r-ASCII"] () ByteString

Since: 0.1.0.0

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

Defined in Data.TypedEncoding.Common.Types.Enc

Methods

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

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

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

Defined in Data.TypedEncoding.Common.Types.Enc

Methods

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

show :: Enc nms conf str -> String #

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

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

Defined in Data.TypedEncoding.Common.Types.Enc

Methods

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

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

Since: 0.1.0.0

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

Since: 0.1.0.0

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

Since: 0.1.0.0

Untyped versions of Enc

Encoding and basic combinators

data Encoding f (nm :: Symbol) (alg :: Symbol) conf str where Source #

Wraps the encoding function. Contains type level information about the encoding name and the algorithm used.

This type is used by programs implementing encoding instance. Such program needs to define a value of this type. It also implements Encode instance that simply returns that value.

Programs using encoding can access this type using encoding (from the Encode typeclass) but a better (and recommended) approach is to use its plural sibling Encodings defined below.

This type has 2 symbol type variables:

  • nm defines the encoding
  • alg defines algorithm

These two are related, currently this library only supports

  • Names nm containing ":" using format "alg:...", for example name "r-ban:999" has "r-ban" algorithm
  • Names without ":" require that nm ~ alg

Future version are likely to relax this, possibly introducing ability do define more than one algorithm for given encoding.

Using 2 variables allows us to define typeclass constraints that work with definitions like "r-ban" where "r-ban:" can be followed by arbitrary string literal.

This existential definition is intended for clarity. typed-encoding supports type level lists of encodings and each encoding should not know what encodings have already been applied.

However, this construction is mostly equivalent to storing a simple one level encoding function Enc ('[]:: [Symbol]) conf str -> f (Enc '[nm] conf str) (see _mkEncoding1 and runEncoding1' below).

Examples:

Encoding (Either EncodeEx) "r-ban:9" "r-ban" () String

encodes a single character <= 9'

Encoding Identity "enc-B64" "enc-B64" () ByteString

Represents a Base 64 encoder that can operate on any stack of previous encodings. (encoding name and algorithm name are "enc-B64", there is no additional configuration () needed and it runs in the Identity Functor.

Similar boilerplate for Decoding and Validation is specified in separate modules.

Since: 0.3.0.0

Constructors

UnsafeMkEncoding :: Proxy nm -> (forall (xs :: [Symbol]). Enc xs conf str -> f (Enc (nm ': xs) conf str)) -> Encoding f nm alg conf str

Consider this constructor as private or use it with care

Defining constructor like this: MkEncoding :: Proxy nm -> (forall (xs :: [Symbol]) . Enc xs conf str -> f (Enc (nm ': xs) conf str)) -> Encoding f nm (AlgNm nm) conf str

would make compilation much slower

_mkEncoding :: forall f (nm :: Symbol) conf str. (forall (xs :: [Symbol]). Enc xs conf str -> f (Enc (nm ': xs) conf str)) -> Encoding f nm (AlgNm nm) conf str Source #

Type safe smart constructor

Adding the type family (AlgNm nm) mapping to Encoding constructor slows down the compilation. Using smart constructor does not have that issue.

This approach also provides more future flexibility with possibility of future overloads relaxing current limitations on alg names.

Notice underscore _ convention, it indicates a use of Algorithm AlgNm: compiler figures out alg value. These can be slower to compile when used.

Here are other conventions that relate to the existence of alg

  • functions ending with: ', for example encodeF' have alg as first type variable in the forall list.
  • functions without tick tend to assume nm ~ alg

This particular function appears to not increase compilation time.

Since: 0.3.0.0

_mkEncoding1 :: forall f (nm :: Symbol) conf str. Functor f => (Enc ('[] :: [Symbol]) conf str -> f (Enc '[nm] conf str)) -> Encoding f nm (AlgNm nm) conf str Source #

Defines encoding by only specifying a simple one level encoding function. This typically is not used in constructing encodings as there are more convenient combinators for doing this (e.g. in Data.TypedEncoding.Instances.Support). It is here for completeness to show that the Encoding definition is a bit overdone.

Since: 0.5.2.0

runEncoding' :: forall alg nm f xs conf str. Encoding f nm alg conf str -> Enc xs conf str -> f (Enc (nm ': xs) conf str) Source #

Since: 0.3.0.0

_runEncoding :: forall nm f xs conf str alg. Algorithm nm alg => Encoding f nm alg conf str -> Enc xs conf str -> f (Enc (nm ': xs) conf str) Source #

Same as runEncoding' but compiler figures out algorithm name

Using it can slowdown compilation

This combinator has Algorithm nm alg constraint (which currently stands for TakeUntil ":" nm ~ alg.

runEncoding functions are typically not used directly, runEncodings functions defined below or encodeAll functions are used instead.

In the following example (and other examples) we use displ convenience function that provides String display of the encoding. The "r-ban:111" allows only strings with 3 characters satisfying alphanumeric bound of '1'

>>> fmap displ (_runEncoding encFBan $ toEncoding () "000" :: Either EncodeEx (Enc '["r-ban:111"] () T.Text))
Right "Enc '[r-ban:111] () (Text 000)"

Since: 0.3.0.0

runEncoding1' :: forall alg nm f conf str. Encoding f nm alg conf str -> Enc ('[] :: [Symbol]) conf str -> f (Enc '[nm] conf str) Source #

Version of runEncoding' function specialized to empty encoding

Since: 0.5.2.0

List of encodings

data Encodings f (nms :: [Symbol]) (algs :: [Symbol]) conf str where Source #

HList like construction that defines a list of Encoding elements.

This type is used by programs using / manipulating encodings.

Can be easily accessed with EncodeAll constraint using encodings. But could also be used by creating Encodings list by hand.

Since: 0.3.0.0

Constructors

ZeroE :: Encodings f '[] '[] conf str 
ConsE :: Encoding f nm alg conf str -> Encodings f nms algs conf str -> Encodings f (nm ': nms) (alg ': algs) conf str 

runEncodings' :: forall algs nms f c str. Monad f => Encodings f nms algs c str -> Enc ('[] :: [Symbol]) c str -> f (Enc nms c str) Source #

Runs encodings, requires -XTypeApplication annotation specifying the algorithm(s)

>>> runEncodings' @'["r-ban"] (encFBan -:- ZeroE) . toEncoding () $ "000" :: Either EncodeEx (Enc '["r-ban:111"] () T.Text)
Right (UnsafeMkEnc Proxy () "000")

Polymorphic access to encodings is provided by EncodeAll typeclass so we can simply write:

>>> runEncodings' @'["r-ban"] encodings . toEncoding () $ "22" :: Either EncodeEx (Enc '["r-ban:111"] () T.Text)
Left (EncodeEx "r-ban:111" ("Input list has wrong size expecting 3 but length \"22\" == 2"))

This library also offers backward compatible equivalents encodeFAll to runEncodings functions (see Data.TypedEncoding.Combinators.Encode) which are basically equivalent to something like runEncoding' encoding

>>> encodeFAll' @'["r-ban"] . toEncoding () $ "111" :: Either EncodeEx (Enc '["r-ban:111"] () T.Text)
Right (UnsafeMkEnc Proxy () "111")
>>> fmap displ . encodeFAll' @'["r-ban"] @'["r-ban:111"] @(Either EncodeEx) @() @T.Text . toEncoding () $ "111"
Right "Enc '[r-ban:111] () (Text 111)"

Since: 0.3.0.0

_runEncodings :: forall nms f c str algs. (Monad f, algs ~ AlgNmMap nms) => Encodings f nms algs c str -> Enc ('[] :: [Symbol]) c str -> f (Enc nms c str) Source #

At a possibly some compilation cost, have compiler figure out algorithm names.

>>> _runEncodings encodings . toEncoding () $ ("Hello World") :: Identity (Enc '["enc-B64","enc-B64"] () B.ByteString)
Identity (UnsafeMkEnc Proxy () "U0dWc2JHOGdWMjl5YkdRPQ==")
>>> _runEncodings encodings . toEncoding () $ ("22") :: Either EncodeEx (Enc '["r-ban:111"] () T.Text)
Left (EncodeEx "r-ban:111" ("Input list has wrong size expecting 3 but length \"22\" == 2"))

(see also _runEncoding) @since 0.3.0.0

Similar to Encoding and Encodings but cover Decoding and Validation

UncheckedEnc is an untyped version of Enc that represents not validated encoding

Laws / properties

propSafeDecoding' :: forall alg nm c str. (Eq c, Eq str) => Encoding (Either EncodeEx) nm alg c str -> Decoding (Either UnexpectedDecodeEx) nm alg c str -> c -> str -> Bool Source #

Main property that encodings are expected to enforce.

Decoding is safe and can use Identity instance of UnexpectedDecodeErr.

Errors are handled during the encoding phase.

_propSafeDecoding :: forall nm c str alg. (Algorithm nm alg, Eq c, Eq str) => Encoding (Either EncodeEx) nm alg c str -> Decoding (Either UnexpectedDecodeEx) nm alg c str -> c -> str -> Bool Source #

propSafeValidatedDecoding' :: forall alg nm c str. (Eq c, Eq str) => Validation (Either RecreateEx) nm alg c str -> Decoding (Either UnexpectedDecodeEx) nm alg c str -> c -> str -> Bool Source #

Similar to propSafeDecoding' but Validation based. Validation acts as Decoding recovering original payload value. Recovering with validation keeps the encoded value and that value is supposed to decode without error.

Expects input of encoded values

_propSafeValidatedDecoding :: forall nm c str alg. (Algorithm nm alg, Eq c, Eq str) => Validation (Either RecreateEx) nm alg c str -> Decoding (Either UnexpectedDecodeEx) nm alg c str -> c -> str -> Bool Source #

Encoding Classes

class Encode f nm alg conf str where Source #

Allows for polymorphic access to encoding, for example

>>> displ (runIdentity . _runEncoding encoding $ toEncoding () "Hello" :: Enc '["enc-B64"] () B.ByteString)
"Enc '[enc-B64] () (ByteString SGVsbG8=)"

Using 2 Symbol type variables (nm and alg) creates what seems like redundant typing in statically defined instances such as "r-ASCII", however it provides future flexibility to constrain nm in some interesting way, different than AlgNm nm ~ alg.

It also seems to be easier to understand as type variables used in the definition of Encoding match with what is on the typeclass.

alg is expected to be very statically defined and is needed to support more open instances such as "r-ban".

Since: 0.3.0.0

Methods

encoding :: Encoding f nm alg conf str Source #

Instances
Applicative f => Encode f "enc-B64" "enc-B64" c Text Source #

This instance will likely be removed in future versions (performance concerns) (Moved from Data.TypedEncoding.Instances.Enc.Base64)

Instance details

Defined in Data.TypedEncoding.Instances.Enc.Warn.Base64

Methods

encoding :: Encoding f "enc-B64" "enc-B64" c Text Source #

Applicative f => Encode f "enc-B64" "enc-B64" c ByteString Source #

Since: 0.3.0.0

Instance details

Defined in Data.TypedEncoding.Instances.Enc.Base64

Methods

encoding :: Encoding f "enc-B64" "enc-B64" c ByteString Source #

Applicative f => Encode f "enc-B64" "enc-B64" c ByteString Source #

Since: 0.3.0.0

Instance details

Defined in Data.TypedEncoding.Instances.Enc.Base64

Methods

encoding :: Encoding f "enc-B64" "enc-B64" c ByteString Source #

Applicative f => Encode f "my-sign" "my-sign" c Text Source #

Because encoding function is pure we can create instance of Encode that is polymorphic in effect f.

This is done using implTranP combinator.

Instance details

Defined in Examples.TypedEncoding.Instances.DiySignEncoding

Methods

encoding :: Encoding f "my-sign" "my-sign" c Text Source #

(HasA SizeLimit c, Applicative f) => Encode f "do-size-limit" "do-size-limit" c ByteString Source # 
Instance details

Defined in Examples.TypedEncoding.Instances.Do.Sample

Methods

encoding :: Encoding f "do-size-limit" "do-size-limit" c ByteString Source #

(HasA SizeLimit c, Applicative f) => Encode f "do-size-limit" "do-size-limit" c Text Source #

Since: 0.3.0.0

Instance details

Defined in Examples.TypedEncoding.Instances.Do.Sample

Methods

encoding :: Encoding f "do-size-limit" "do-size-limit" c Text Source #

Applicative f => Encode f "do-reverse" "do-reverse" c Text Source # 
Instance details

Defined in Examples.TypedEncoding.Instances.Do.Sample

Methods

encoding :: Encoding f "do-reverse" "do-reverse" c Text Source #

Applicative f => Encode f "do-reverse" "do-reverse" c Text Source #

Since: 0.3.0.0

Instance details

Defined in Examples.TypedEncoding.Instances.Do.Sample

Methods

encoding :: Encoding f "do-reverse" "do-reverse" c Text Source #

Applicative f => Encode f "do-Title" "do-Title" c Text Source # 
Instance details

Defined in Examples.TypedEncoding.Instances.Do.Sample

Methods

encoding :: Encoding f "do-Title" "do-Title" c Text Source #

Applicative f => Encode f "do-Title" "do-Title" c Text Source #

Since: 0.3.0.0

Instance details

Defined in Examples.TypedEncoding.Instances.Do.Sample

Methods

encoding :: Encoding f "do-Title" "do-Title" c Text Source #

Applicative f => Encode f "do-lower" "do-lower" c Text Source # 
Instance details

Defined in Examples.TypedEncoding.Instances.Do.Sample

Methods

encoding :: Encoding f "do-lower" "do-lower" c Text Source #

Applicative f => Encode f "do-lower" "do-lower" c Text Source #

Since: 0.3.0.0

Instance details

Defined in Examples.TypedEncoding.Instances.Do.Sample

Methods

encoding :: Encoding f "do-lower" "do-lower" c Text Source #

Applicative f => Encode f "do-UPPER" "do-UPPER" c Text Source # 
Instance details

Defined in Examples.TypedEncoding.Instances.Do.Sample

Methods

encoding :: Encoding f "do-UPPER" "do-UPPER" c Text Source #

Applicative f => Encode f "do-UPPER" "do-UPPER" c Text Source #

Since: 0.3.0.0

Instance details

Defined in Examples.TypedEncoding.Instances.Do.Sample

Methods

encoding :: Encoding f "do-UPPER" "do-UPPER" c Text Source #

(Ban s, Algorithm s "r-ban", IsStringR str) => Encode (Either EncodeEx) s "r-ban" c str Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.BoundedAlphaNums

Methods

encoding :: Encoding (Either EncodeEx) s "r-ban" c str Source #

Char8Find str => Encode (Either EncodeEx) "r-ASCII" "r-ASCII" c str Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

encoding :: Encoding (Either EncodeEx) "r-ASCII" "r-ASCII" c str Source #

Encode (Either EncodeEx) "r-ASCII" "r-ASCII" c Char Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

encoding :: Encoding (Either EncodeEx) "r-ASCII" "r-ASCII" c Char Source #

Encode (Either EncodeEx) "r-B64" "r-B64" c String Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Base64

Methods

encoding :: Encoding (Either EncodeEx) "r-B64" "r-B64" c String Source #

Encode (Either EncodeEx) "r-B64" "r-B64" c Text Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Base64

Methods

encoding :: Encoding (Either EncodeEx) "r-B64" "r-B64" c Text Source #

Encode (Either EncodeEx) "r-B64" "r-B64" c Text Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Base64

Methods

encoding :: Encoding (Either EncodeEx) "r-B64" "r-B64" c Text Source #

Encode (Either EncodeEx) "r-B64" "r-B64" c ByteString Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Base64

Methods

encoding :: Encoding (Either EncodeEx) "r-B64" "r-B64" c ByteString Source #

Encode (Either EncodeEx) "r-B64" "r-B64" c ByteString Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Base64

Methods

encoding :: Encoding (Either EncodeEx) "r-B64" "r-B64" c ByteString Source #

Encode (Either EncodeEx) "r-ByteRep" "r-ByteRep" c String Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ByteRep

Methods

encoding :: Encoding (Either EncodeEx) "r-ByteRep" "r-ByteRep" c String Source #

Encode (Either EncodeEx) "r-ByteRep" "r-ByteRep" c ByteString Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ByteRep

Methods

encoding :: Encoding (Either EncodeEx) "r-ByteRep" "r-ByteRep" c ByteString Source #

Encode (Either EncodeEx) "r-ByteRep" "r-ByteRep" c ByteString Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ByteRep

Methods

encoding :: Encoding (Either EncodeEx) "r-ByteRep" "r-ByteRep" c ByteString Source #

Encode (Either EncodeEx) "r-ByteRep" "r-ByteRep" c Char Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ByteRep

Methods

encoding :: Encoding (Either EncodeEx) "r-ByteRep" "r-ByteRep" c Char Source #

IsStringR str => Encode (Either EncodeEx) "r-Int-decimal" "r-Int-decimal" c str Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Misc

Methods

encoding :: Encoding (Either EncodeEx) "r-Int-decimal" "r-Int-decimal" c str Source #

Encode (Either EncodeEx) "r-UNICODE.D76" "r-UNICODE.D76" c String Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.D76

Methods

encoding :: Encoding (Either EncodeEx) "r-UNICODE.D76" "r-UNICODE.D76" c String Source #

Encode (Either EncodeEx) "r-UNICODE.D76" "r-UNICODE.D76" c Char Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.D76

Methods

encoding :: Encoding (Either EncodeEx) "r-UNICODE.D76" "r-UNICODE.D76" c Char Source #

Encode (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.UTF8

Methods

encoding :: Encoding (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

>>> _runEncodings encodings . toEncoding () $ "\xc3\xb1" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Right (UnsafeMkEnc Proxy () "\195\177")
>>> _runEncodings encodings . toEncoding () $ "\xc3\x28" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Left (EncodeEx "r-UTF8" (Cannot decode byte '\xc3': ...

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

>>> :{
quickCheck $ \(b :: B.ByteString) -> verEncoding b $ fmap (
         fromEncoding 
         . decodeAll @'["r-UTF8"]
         ) . encodeFAll @'["r-UTF8"] @(Either EncodeEx)
         . toEncoding () $ b
:}
+++ OK, passed 100 tests.
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.UTF8

Methods

encoding :: Encoding (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source #

IsStringR str => Encode (Either EncodeEx) "r-Word8-decimal" "r-Word8-decimal" c str Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Misc

Methods

encoding :: Encoding (Either EncodeEx) "r-Word8-decimal" "r-Word8-decimal" c str Source #

class EncodeAll f nms algs conf str where Source #

Allows for polymorphic access to Encodings

For example

>>> displ (runIdentity . _runEncodings encodings $ toEncoding () "Hello" :: (Enc '["enc-B64", "enc-B64"] () B.ByteString))
"Enc '[enc-B64,enc-B64] () (ByteString U0dWc2JHOD0=)"

You can also use convenience functions like encodeAll

Since: 0.3.0.0

Methods

encodings :: Encodings f nms algs conf str Source #

Instances
EncodeAll f ([] :: [Symbol]) ([] :: [Symbol]) conf str Source # 
Instance details

Defined in Data.TypedEncoding.Common.Class.Encode

Methods

encodings :: Encodings f [] [] conf str Source #

(EncodeAll f nms algs conf str, Encode f nm alg conf str) => EncodeAll f (nm ': nms) (alg ': algs) conf str Source # 
Instance details

Defined in Data.TypedEncoding.Common.Class.Encode

Methods

encodings :: Encodings f (nm ': nms) (alg ': algs) conf str Source #

Decoding, Validation and Other Classes

Combinators

Exceptions

Other