typed-encoding-0.4.2.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Common.Types.Validation

Description

Internal definition of types

Validation types for Enc

See also

Use of unsafeSetPayload currently recommended for recovering Enc from trusted input sources (if avoiding cost of Validation is important).

Synopsis

Documentation

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

Validation unwraps a layer of encoding and offers payload data down the encoding stack for further verification.

For "enc-" encodings this will typically be decoding step.

For "r-" encodings this will typically be encoding step.

Since: 0.3.0.0

Constructors

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

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

Type safe smart constructor adding the type family (AlgNm nm) restriction to UnsafeMkValidation slows down compilation, especially in tests.

Since: 0.3.0.0

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

Deprecated: Use runValidation''

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

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

Same as 'runValidation" but compiler figures out algorithm name

Using it can slowdown compilation

Since: 0.3.0.0

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

Wraps a list of Validation elements.

Similarly to Validation it can be used with a typeclass EncodeAll

Since: 0.3.0.0

Constructors

ZeroV :: Validations 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

ConsV :: Validation f nm alg conf str -> Validations f nms algs conf str -> Validations f (nm ': nms) (alg ': algs) conf str 

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

This basically puts payload in decoded state. More useful combinators are in Data.TypedEncoding.Combinators.Validate

Since: 0.3.0.0