typed-encoding-0.1.0.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Examples.TypedEncoding.DiySignEncoding

Contents

Description

Simple DIY encoding example that "signs" Text with its length.

Documentation includes discussion of error handling options.

My current thinking:

Stronger type level information about encoding provides type safety over decoding process. Decoding cannot fail unless somehow underlying data has been corrupted.

Such integrity of data should be enforced at boundaries (JSON instances, DB retrievals, etc). This can be accomplished using provided RecreateF typeclass.

This still is user decision, the errors during decoding process are considered unexpected UnexpectedDecodeErr. In particular user can decide to use unsafe operations with the encoded type. See Unsafe.

Synopsis

Documentation

>>> :set -XOverloadedStrings -XMultiParamTypeClasses -XDataKinds
>>> import Test.QuickCheck.Instances.Text()

encodeSign :: Text -> Text Source #

encoding function, typically should be module private

decodeSign :: Text -> Either String Text Source #

dual purpose decoding and recovery function.

This typically should be module private.

>>> decodeSign "3:abc"
Right "abc"
>>> decodeSign "4:abc"
Left "Corrupted Signature"

helloSigned :: Enc '["my-sign"] () Text Source #

Encoded hello world example.

>>> helloSigned
MkEnc Proxy () "11:Hello World"
>>> fromEncoding . decodeAll $ helloSigned
"Hello World"

propEncDec :: Text -> Bool Source #

property checks that Text values are exected to decode without error after encoding.

\t -> propEncDec

hacker :: Either RecreateEx (Enc '["my-sign"] () Text) Source #

Hacker example The data was transmitted over a network and got corrupted.

>>> let payload = getPayload $ helloSigned :: T.Text
>>> let newpay = payload <> " corruption"
>>> recreateFAll . toEncoding () $ newpay :: Either RecreateEx (Enc '["my-sign"] () T.Text)
Left (RecreateEx "my-sign" ("Corrupted Signature"))
>>> recreateFAll . toEncoding () $ payload :: Either RecreateEx (Enc '["my-sign"] () T.Text)
Right (MkEnc Proxy () "11:Hello World")

prxyMySign :: Proxy "my-sign" Source #

Orphan instances

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("my-sign" ': xs) c Text) Source #

Recreation allows effectful f to check for tampering with data. Implementation simply uses implCheckPrevF combinator on the recovery function.

Instance details

Methods

checkPrevF :: Enc ("my-sign" ': xs) c Text -> f (Enc xs c Text) Source #

(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("my-sign" ': xs) c Text) (Enc xs c Text :: Type) Source #

Decoding allows effectful f to allow for troubleshooting and unsafe payload changes.

Implementation simply uses implDecodeF combinator on the asUnexpected composed with decoding function. UnexpectedDecodeErr has Identity instance allowing for decoding that assumes errors are not possible. For debugging purposes or when unsafe changes to "my-sign" Error UnexpectedDecodeEx instance can be used.

Instance details

Methods

decodeF :: Enc ("my-sign" ': xs) c Text -> f (Enc xs c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("my-sign" ': xs) c Text :: Type) Source #

Because encoding function is pure we can create instance of EncodeF that is polymorphic in effect f. This is done using implTranP combinator.

Instance details

Methods

encodeF :: Enc xs c Text -> f (Enc ("my-sign" ': xs) c Text) Source #