typed-encoding-0.4.0.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Examples.TypedEncoding.ToEncString

Contents

Description

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

Documentation

>>> :set -XMultiParamTypeClasses -XDataKinds -XPolyKinds -XFlexibleInstances -XTypeApplications -XOverloadedStrings
>>> import qualified Data.List as L

IpV4 example

data IpV4F a Source #

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.

Constructors

IpV4F 

Fields

Instances
Functor IpV4F Source # 
Instance details

Defined in Examples.TypedEncoding.ToEncString

Methods

fmap :: (a -> b) -> IpV4F a -> IpV4F b #

(<$) :: a -> IpV4F b -> IpV4F a #

Foldable IpV4F Source # 
Instance details

Defined in Examples.TypedEncoding.ToEncString

Methods

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 #

toList :: IpV4F a -> [a] #

null :: IpV4F a -> Bool #

length :: IpV4F a -> Int #

elem :: Eq a => a -> IpV4F a -> Bool #

maximum :: Ord a => IpV4F a -> a #

minimum :: Ord a => IpV4F a -> a #

sum :: Num a => IpV4F a -> a #

product :: Num a => IpV4F a -> a #

ToEncString Identity "r-IPv4" "r-IPv4" IpV4 Text Source #

In this example toEncString converts IpV4 to Enc '["r-IPv4"] Text.

This is done with help of existing "r-Word8-decimal" annotation defined in Data.TypedEncoding.Instances.Restriction.Misc

>>> toEncString @"r-IPv4" @IpV4 @T.Text tstIp
UnsafeMkEnc Proxy () "128.1.1.10"

Implementation is a classic map reduce where reduce is done with help of foldEncStr

>>> let fn a b = if b == "" then a else a <> "." <> b
>>> let reduce = EnT.foldEncStr @'["r-IPv4"] @'["r-Word8-decimal"] () fn
>>> displ . reduce . fmap toEncString $ tstIp
"Enc '[r-IPv4] () (String 128.1.1.10)"

Note lack of type safety here, the same code would work just fine if we added 5th field to IpV4F constructor.

Using something like a dependently typed

Vect 4 (Enc '["r-Word8-decimal"] () T.Text)

would have improved this situation. HList could be used for record types with heterogeneous fields.

Currently, 'type-encoding' library does not have these types in scope.

Instance details

Defined in Examples.TypedEncoding.ToEncString

Methods

toEncF :: IpV4 -> Identity (Enc ("r-IPv4" ': []) () Text) Source #

Show a => Show (IpV4F a) Source # 
Instance details

Defined in Examples.TypedEncoding.ToEncString

Methods

showsPrec :: Int -> IpV4F a -> ShowS #

show :: IpV4F a -> String #

showList :: [IpV4F a] -> ShowS #

Displ a => Displ (IpV4F a) Source #

Provides easy to read encoding information

Instance details

Defined in Examples.TypedEncoding.ToEncString

Methods

displ :: IpV4F a -> String Source #

(UnexpectedDecodeErr f, Applicative f) => FromEncString (f :: Type -> Type) "r-IPv4" "r-IPv4" IpV4 Text Source #
>>> let enc = toEncString @"r-IPv4" @IpV4 @T.Text tstIp
>>> fromEncString @"r-IPv4" @IpV4 enc
IpV4F {oct1 = 128, oct2 = 1, oct3 = 1, oct4 = 10}

To get IpV4 out of the string we need to reverse previous reduce. This is currently done using helper splitPayload combinator.

>>> EnT.splitPayload @ '["r-Word8-decimal"] (T.splitOn $ T.pack ".") $ enc
[UnsafeMkEnc Proxy () "128",UnsafeMkEnc Proxy () "1",UnsafeMkEnc Proxy () "1",UnsafeMkEnc Proxy () "10"]

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 splitPayload returned fixed size Vect 4.

Instance details

Defined in Examples.TypedEncoding.ToEncString

Methods

fromEncF :: Enc ("r-IPv4" ': []) () Text -> f IpV4 Source #

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.

Constructors

SimplifiedEmailF 

Fields

Instances
Functor SimplifiedEmailF Source # 
Instance details

Defined in Examples.TypedEncoding.ToEncString

Methods

fmap :: (a -> b) -> SimplifiedEmailF a -> SimplifiedEmailF b #

(<$) :: a -> SimplifiedEmailF b -> SimplifiedEmailF a #

Foldable SimplifiedEmailF Source # 
Instance details

Defined in Examples.TypedEncoding.ToEncString

Methods

fold :: Monoid m => SimplifiedEmailF m -> m #

foldMap :: Monoid m => (a -> m) -> SimplifiedEmailF a -> m #

foldr :: (a -> b -> b) -> b -> SimplifiedEmailF a -> b #

foldr' :: (a -> b -> b) -> b -> SimplifiedEmailF a -> b #

foldl :: (b -> a -> b) -> b -> SimplifiedEmailF a -> b #

foldl' :: (b -> a -> b) -> b -> SimplifiedEmailF a -> b #

foldr1 :: (a -> a -> a) -> SimplifiedEmailF a -> a #

foldl1 :: (a -> a -> a) -> SimplifiedEmailF a -> a #

toList :: SimplifiedEmailF a -> [a] #

null :: SimplifiedEmailF a -> Bool #

length :: SimplifiedEmailF a -> Int #

elem :: Eq a => a -> SimplifiedEmailF a -> Bool #

maximum :: Ord a => SimplifiedEmailF a -> a #

minimum :: Ord a => SimplifiedEmailF a -> a #

sum :: Num a => SimplifiedEmailF a -> a #

product :: Num a => SimplifiedEmailF a -> a #

Traversable SimplifiedEmailF Source # 
Instance details

Defined in Examples.TypedEncoding.ToEncString

Methods

traverse :: Applicative f => (a -> f b) -> SimplifiedEmailF a -> f (SimplifiedEmailF b) #

sequenceA :: Applicative f => SimplifiedEmailF (f a) -> f (SimplifiedEmailF a) #

mapM :: Monad m => (a -> m b) -> SimplifiedEmailF a -> m (SimplifiedEmailF b) #

sequence :: Monad m => SimplifiedEmailF (m a) -> m (SimplifiedEmailF a) #

Eq a => Eq (SimplifiedEmailF a) Source # 
Instance details

Defined in Examples.TypedEncoding.ToEncString

Show a => Show (SimplifiedEmailF a) Source # 
Instance details

Defined in Examples.TypedEncoding.ToEncString

Displ a => Displ (SimplifiedEmailF a) Source #

Provides easy to read encoding information

Instance details

Defined in Examples.TypedEncoding.ToEncString

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:

>>> check @'["enc-B64","r-ASCII"] @(Either RecreateEx) $ unchecked
Nothing
>>> check @'["enc-B64","r-UTF8"] @(Either RecreateEx) $ unchecked
Just (Right (UnsafeMkEnc 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 = [UnsafeMkCheckedEnc ["enc-B64"] () "U29tZSBBU0NJSSBUZXh0",UnsafeMkCheckedEnc ["r-ASCII"] () "Some ASCII Text",UnsafeMkCheckedEnc ["r-UTF8"] () "Some UTF8 Text",UnsafeMkCheckedEnc ["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
"UnsafeMkCheckedEnc [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 (UnsafeMkEnc Proxy () "U29tZSBBU0NJSSBUZXh0")

so we can apply the decoding on the selected piece

>>> fmap (toCheckedEnc . decodePart @'["enc-B64"]) . fromCheckedEnc @ '["enc-B64", "r-ASCII"] $ piece
Just (UnsafeMkCheckedEnc ["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 #