typed-encoding-0.5.2.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Common.Types.Decoding

Description

Decoding types for Enc

This module is re-exported in Data.TypedEncoding and it is best not to import it directly.

Synopsis

Documentation

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

Similar to Encoding

Wraps the decoding function.

Can be used with Decode type class.

Examples.TypedEncoding.Instances.DiySignEncoding contains an implementation example.

Examples.TypedEncoding.Overview shows decoding usage examples.

Since: 0.3.0.0

Constructors

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

Consider this constructor as private or use it with care

Using that constructor: UnsafeMkDecoding :: Proxy nm -> (forall (xs :: [Symbol]) . Enc (nm ': xs) conf str -> f (Enc xs conf str)) -> Decoding f nm (AlgNm nm) conf str

would make compilation much slower

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

Deprecated: Use _mkDecoding

Type safe smart constructor (See also _mkEncoding)

Since: 0.3.0.0

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

Type safe smart constructor (See also _mkEncoding)

This function follows the naming convention of using "_" when the typechecker figures out alg @since 0.5.0.0

runDecoding :: forall nm f xs conf str. Decoding f nm nm conf str -> Enc (nm ': xs) conf str -> f (Enc xs conf str) Source #

This function assumes mn ~ alg, making its type different from previous (before v.0.5) versions.

Since: 0.5.0.0

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

Since: 0.3.0.0

_runDecoding :: forall nm f xs conf str alg. AlgNm nm ~ alg => Decoding f nm alg conf str -> Enc (nm ': xs) conf str -> f (Enc xs conf str) Source #

Same as 'runDecoding" but compiler figures out algorithm name

Using it can slowdown compilation

Since: 0.3.0.0

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

Wraps a list of Decoding elements.

Similarly to Encodings can be used with a typeclass DecodeAll

Since: 0.3.0.0

Constructors

ZeroD :: Decodings f '[] '[] conf str

constructor is to be treated as Unsafe to Encode and Decode instance implementations particular encoding instances may expose smart constructors for limited data types

ConsD :: Decoding f nm alg conf str -> Decodings f nms algs conf str -> Decodings f (nm ': nms) (alg ': algs) conf str 

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

This function assumes nms ~ algs, making its type different from previous (before v.0.5) versions.

Since: 0.5.0.0

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

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

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

Since: 0.3.0.0