Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module shows use of ToEncString
and FromEncString
and demonstrates composite encoding.
Show
and Read
classes use a very permissive String type. This often results in
read errors. type-encoding approach provides type safety over decoding process.
This module includes a simplified email example. This is a non-homogeneous case, email parts do not have the same encoding.
Examples here could be made more type safe with use of dependently typed
concepts like Vect
, HList
or variant equivalents of these types.
Current version of typed-encoding does not have dependencies on such types.
These examples use CheckedEnc
when untyped version of Enc
is needed.
Alternatively, an existentially quantified SomeEnc
type could have been used.
Both are isomorphic.
Synopsis
- type IpV4 = IpV4F Word8
- data IpV4F a = IpV4F {}
- tstIp :: IpV4
- type PartHeader = [String]
- type EmailHeader = String
- data SimplifiedEmailF a = SimplifiedEmailF {
- emailHeader :: EmailHeader
- parts :: [a]
- type SimplifiedEmail = SimplifiedEmailF (PartHeader, ByteString)
- type SimplifiedEmailEncB = SimplifiedEmailF (CheckedEnc () ByteString)
- tstEmail :: SimplifiedEmail
- recreateEncoding :: SimplifiedEmail -> Either RecreateEx SimplifiedEmailEncB
- decodeB64ForTextOnly :: SimplifiedEmailEncB -> SimplifiedEmailEncB
- runAlternatives' :: Alternative f => (f b -> b) -> [a -> f b] -> a -> b
- runAlternatives :: Alternative f => (a -> f b -> b) -> [a -> f b] -> a -> b
- alternatives :: Alternative f => [a -> f b] -> a -> f b
Documentation
>>>
:set -XMultiParamTypeClasses -XDataKinds -XPolyKinds -XFlexibleInstances -XTypeApplications -XOverloadedStrings
>>>
import qualified Data.List as L
IpV4 example
In this example all data fields have the same type. This simplifies encoding work as all fields will be encoded the same way. We use IP address since all fields are single byte size.
Instances
Functor IpV4F Source # | |
Foldable IpV4F Source # | |
Defined in Examples.TypedEncoding.ToEncString fold :: Monoid m => IpV4F m -> m # foldMap :: Monoid m => (a -> m) -> IpV4F a -> m # foldr :: (a -> b -> b) -> b -> IpV4F a -> b # foldr' :: (a -> b -> b) -> b -> IpV4F a -> b # foldl :: (b -> a -> b) -> b -> IpV4F a -> b # foldl' :: (b -> a -> b) -> b -> IpV4F a -> b # foldr1 :: (a -> a -> a) -> IpV4F a -> a # foldl1 :: (a -> a -> a) -> IpV4F a -> a # elem :: Eq a => a -> IpV4F a -> Bool # maximum :: Ord a => IpV4F a -> a # minimum :: Ord a => IpV4F a -> a # | |
ToEncString "r-IPv4" Text Identity IpV4 Source # | In this example This is done with help of existing
Implementation is a classic map reduce where reduce is done with help of
Note lack of type safety here, the same code would work just fine if we added
5th field to Using something like a dependently typed Vect 4 (Enc '["r-Word8-decimal"] () T.Text) would have improved this situation.
Currently, 'type-encoding' library does not have these types in scope. |
Defined in Examples.TypedEncoding.ToEncString | |
Show a => Show (IpV4F a) Source # | |
Displ a => Displ (IpV4F a) Source # | Provides easy to read encoding information |
(UnexpectedDecodeErr f, Applicative f) => FromEncString IpV4 (f :: Type -> Type) Text "r-IPv4" Source # |
To get
The conversion of a list to IpV4F needs handle errors but these errors are considered unexpected. Note, again, the error condition exposed by this implementation could have been avoided
if |
Defined in Examples.TypedEncoding.ToEncString |
Simplified email example
type PartHeader = [String] Source #
Simplified Part header
type EmailHeader = String Source #
Simplified Email header
data SimplifiedEmailF a Source #
This section shows a type safe processing of emails.
SimplifiedEmailF
is an over-simplified email type, it has parts that can be either
- binary and have to be Base 64 encoded or
- are text that have either UTF8 or ASCII character set
The text parts can be optionally can be Base 64 encoded but do not have to be.
For simplicity, the layout of simplified headers is assumed the same as encoding annotations in this library.
SimplifiedEmailF | |
|
Instances
type SimplifiedEmail = SimplifiedEmailF (PartHeader, ByteString) Source #
type SimplifiedEmailEncB = SimplifiedEmailF (CheckedEnc () ByteString) Source #
tstEmail :: SimplifiedEmail Source #
tstEmail
contains some simple data to play with
recreateEncoding :: SimplifiedEmail -> Either RecreateEx SimplifiedEmailEncB Source #
This example encodes fields in SimplifiedEmailF
into an untyped version of Enc
which
stores verified encoded data and encoding information is stored at the value level:
CheckedEnc () B.ByteString
.
Part of email are first converted to UncheckedEnc
(that stores encoding information at the value level as well).
UncheckedEnc
that can easily represent parts of the email
>>>
let part = parts tstEmail L.!! 2
>>>
part
(["enc-B64","r-UTF8"],"U29tZSBVVEY4IFRleHQ=")>>>
let unchecked = toUncheckedEnc (fst part) () (snd part)
>>>
unchecked
MkUncheckedEnc ["enc-B64","r-UTF8"] () "U29tZSBVVEY4IFRleHQ="
We can play Alternative
(<|>
) game (we acually use Maybe
) with final option being a RecreateEx
error:
>>>
verifyUncheckedEnc' @'["enc-B64","r-ASCII"] $ unchecked
Nothing>>>
verifyUncheckedEnc' @'["enc-B64","r-UTF8"] $ unchecked
Just (Right (MkEnc Proxy () "U29tZSBVVEY4IFRleHQ="))
Since the data is heterogeneous (each piece has a different encoding annotation), we need wrap the result in another plain ADT: CheckedEnc
.
CheckedEnc
is similar to UncheckedEnc
with the difference that the only (safe) way to get values of this type is
from properly encoded Enc
values.
Using unsafeCheckedEnc
would break type safety here.
It is important to handle all cases during encoding so decoding errors become impossible.
Again, use of dependently typed variant types that could enumerate all possible encodings would made this code nicer.
decodeB64ForTextOnly :: SimplifiedEmailEncB -> SimplifiedEmailEncB Source #
Example decodes parts of email that are base 64 encoded text and nothing else.
This provides a type safety assurance that we do not decode certain parts of email (like trying to decode base 64 on a plain text part).
>>>
decodeB64ForTextOnly <$> recreateEncoding tstEmail
Right (SimplifiedEmailF {emailHeader = "Some Header", parts = [MkCheckedEnc ["enc-B64"] () "U29tZSBBU0NJSSBUZXh0",MkCheckedEnc ["r-ASCII"] () "Some ASCII Text",MkCheckedEnc ["r-UTF8"] () "Some UTF8 Text",MkCheckedEnc ["r-ASCII"] () "Some ASCII plain text"]})
Combinator fromCheckedEnc @'["enc-B64", "r-UTF8"]
acts as a selector and picks only the
["enc-B64", "r-UTF8"]
values from our Traversable
type.
We play the (<|>
) game on all the selectors we want picking and decoding right pieces only.
Imagine this is one of the pieces:
>>>
let piece = unsafeCheckedEnc ["enc-B64","r-ASCII"] () ("U29tZSBBU0NJSSBUZXh0" :: B.ByteString)
>>>
displ piece
"MkCheckedEnc [enc-B64,r-ASCII] () (ByteString U29tZSBBU0NJSSBUZXh0)"
This code will not pick it up:
>>>
fromCheckedEnc @ '["enc-B64", "r-UTF8"] $ piece
Nothing
But this one will:
>>>
fromCheckedEnc @ '["enc-B64", "r-ASCII"] $ piece
Just (MkEnc Proxy () "U29tZSBBU0NJSSBUZXh0")
so we can apply the decoding on the selected piece
>>>
fmap (toCheckedEnc . decodePart @'["enc-B64"]) . fromCheckedEnc @ '["enc-B64", "r-ASCII"] $ piece
Just (MkCheckedEnc ["r-ASCII"] () "Some ASCII Text")
Helpers
runAlternatives' :: Alternative f => (f b -> b) -> [a -> f b] -> a -> b Source #
runAlternatives :: Alternative f => (a -> f b -> b) -> [a -> f b] -> a -> b Source #
alternatives :: Alternative f => [a -> f b] -> a -> f b Source #