typed-encoding-0.5.1.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Common.Class

Synopsis

Documentation

class FlattenAs (y :: Symbol) (x :: Symbol) where Source #

Flatten is more permissive IsSuperset instance FlattenAs "r-ASCII" "enc-B64" where

Now encoded data has form Enc '["r-ASCII"] c str and there is no danger of it begin incorrectly decoded.

Since: 0.1.0.0

Minimal complete definition

Nothing

Methods

flattenAs :: Enc (x ': xs) c str -> Enc '[y] c str Source #

Instances
FlattenAs "r-ASCII" "enc-B64" Source #

Since: 0.1.0.0

Instance details

Defined in Data.TypedEncoding.Instances.Enc.Base64

Methods

flattenAs :: Enc ("enc-B64" ': xs) c str -> Enc ("r-ASCII" ': []) c str Source #

FlattenAs "r-ASCII" "enc-B64-nontext" Source #

allow to treat B64 encodings as ASCII forgetting about B64 encoding

>>> let tstB64 = encodeAll . toEncoding () $ "Hello World" :: Enc '["enc-B64"] () B.ByteString
>>> displ (flattenAs tstB64 :: Enc '["r-ASCII"] () B.ByteString)
"Enc '[r-ASCII] () (ByteString SGVsbG8gV29ybGQ=)"

Since: 0.1.0.0

Instance details

Defined in Data.TypedEncoding.Instances.Enc.Base64

Methods

flattenAs :: Enc ("enc-B64-nontext" ': xs) c str -> Enc ("r-ASCII" ': []) c str Source #

FlattenAs "r-B64" "enc-B64" Source #

Since: 0.5.1.0

Instance details

Defined in Data.TypedEncoding.Instances.Enc.Base64

Methods

flattenAs :: Enc ("enc-B64" ': xs) c str -> Enc ("r-B64" ': []) c str Source #

class (KnownSymbol nm, KnownSymbol ann) => FromEncString f nm ann a str where Source #

Reverse of ToEncString decodes encoded string back to a

Since: 0.2.0.0

Methods

fromEncF :: Enc '[nm] () str -> f a Source #

Instances
(IsStringR str, UnexpectedDecodeErr f, Applicative f) => FromEncString (f :: Type -> Type) "r-Word8-decimal" "r-Word8-decimal" Word8 str Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Misc

Methods

fromEncF :: Enc ("r-Word8-decimal" ': []) () str -> f Word8 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 #

class (KnownSymbol nm, KnownSymbol ann) => ToEncString f nm ann a str where Source #

Generalized Java toString or a type safe version of Haskell's Show.

Encodes a as Enc '[xs] specifying algorithm alg and using effect f

Since: 0.2.0.0

Methods

toEncF :: a -> f (Enc '[nm] () str) Source #

Instances
(IsString str, Applicative f) => ToEncString f "r-Int-decimal" "r-Int-decimal" Int str Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Misc

Methods

toEncF :: Int -> f (Enc ("r-Int-decimal" ': []) () str) Source #

(IsString str, Applicative f) => ToEncString f "r-Word8-decimal" "r-Word8-decimal" Word8 str Source # 
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.Misc

Methods

toEncF :: Word8 -> f (Enc ("r-Word8-decimal" ': []) () str) Source #

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 foldEnc

>>> let fn a b = if b == "" then a else a <> "." <> b
>>> let reduce = EnT.foldEnc @'["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 #