Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Enc
and basic combinators- Existentially quantified and untyped versions of
Enc
Encoding
and basic combinators- List of encodings
- Similar to
Encoding
andEncodings
but cover Decoding and Validation UncheckedEnc
is an untyped version of Enc that represents not validated encoding- Laws / properties
- Classes
- Combinators
- Exceptions
- Other
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"] 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)
- 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
- 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
- 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"
"bool[Op]:" encodings
Encodings that are defined in terms of other encodings using boolean algebra.
(early, beta version)
Examples:
"boolOr:(r-ban:999-999-9999)(r-ban:(999) 999-9999)"
"@boolNot:(r-ASCII)"
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
- Data.TypedEncoding.Instances.Enc.Base64
- Data.TypedEncoding.Instances.Restriction.Misc (replaces
Common
from v0.2) - Data.TypedEncoding.Instances.Restriction.ASCII
- Data.TypedEncoding.Instances.Restriction.UTF8
- Data.TypedEncoding.Instances.Restriction.Bool (experimental / early alpha version, moved from
Combinators
toInstances
in v0.3) - Data.TypedEncoding.Instances.Restriction.BoundedAlphaNums (moved from
Combinators
toInstances
in v0.3) - Data.TypedEncoding.Instances.Do.Sample - This module is intended as example code and will be moved under
TypedEncoding
in the future
... and needed conversions.
Conversion combinator module structure is similar to one found in text and bytestring packages Please see comments in Data.TypedEncoding.Conv 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
- data Enc nms conf str
- toEncoding :: conf -> str -> Enc ('[] :: [Symbol]) conf str
- fromEncoding :: Enc '[] conf str -> str
- getPayload :: Enc enc conf str -> str
- module Data.TypedEncoding.Common.Types.SomeEnc
- module Data.TypedEncoding.Common.Types.CheckedEnc
- data Encoding f (nm :: Symbol) (alg :: Symbol) conf str where
- _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
- runEncoding' :: forall alg nm f xs conf str. Encoding f nm alg conf str -> Enc xs conf str -> f (Enc (nm ': xs) conf str)
- _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)
- data Encodings f (nms :: [Symbol]) (algs :: [Symbol]) conf str where
- runEncodings' :: forall algs nms f c str. Monad f => Encodings f nms algs c str -> Enc ('[] :: [Symbol]) c str -> f (Enc nms c str)
- _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)
- module Data.TypedEncoding.Common.Types.Decoding
- module Data.TypedEncoding.Common.Types.Validation
- module Data.TypedEncoding.Common.Types.UncheckedEnc
- 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
- _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
- 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
- _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
- module Data.TypedEncoding.Common.Class
- module Data.TypedEncoding.Combinators.Common
- module Data.TypedEncoding.Combinators.Encode
- module Data.TypedEncoding.Combinators.Decode
- module Data.TypedEncoding.Combinators.Validate
- module Data.TypedEncoding.Combinators.Unsafe
- module Data.TypedEncoding.Combinators.ToEncStr
- module Data.TypedEncoding.Combinators.Promotion
- module Data.TypedEncoding.Common.Types.Exceptions
- module Data.TypedEncoding.Common.Types.Common
Enc
and basic combinators
data Enc nms conf str Source #
Contains encoded data annotated by
nms
list ofSymbol
s 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 # | |
(Show conf, Show str) => Show (Enc nms conf str) Source # | |
(SymbolList xs, Show c, Displ str) => Displ (Enc xs c str) 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
Existentially quantified and 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 encodingalg
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.
Examples:
Encoding (Either EncodeEx) "r-ban:9" "r-ban" () String
encodes a single character <= 9'
Encoding Identity "enc-B64" "enc-B64" () ByteString
Represents a Byte 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
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:
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 exampleencodeF'
havealg
as first type variable in theforall
list. - functions without tick tend to assume
nm ~ alg
This particular function appears to not increase compilation time.
Since: 0.3.0.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 stands for TakeUntil ":" nm ~ alg
.
If rules on alg
are relaxed this will just return the default algorithm.
If that happens -XTypeApplications
annotations will be needed and _
methods will simply
use default algorithm name.
Since: 0.3.0.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
ZeroE :: Encodings 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 |
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"] 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"))
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 #