typed-encoding-0.2.0.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Internal.Class

Synopsis

Documentation

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

Minimal complete definition

Nothing

Methods

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

Instances
FlattenAs "r-ASCII" "enc-B64" Source # 
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)
"MkEnc '[r-ASCII] () (ByteString SGVsbG8gV29ybGQ=)"
Instance details

Defined in Data.TypedEncoding.Instances.Enc.Base64

Methods

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

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

subsets are useful for restriction encodings like r-UFT8 but not for other encodings.

Minimal complete definition

Nothing

Methods

inject :: Enc (x ': xs) c str -> Enc (y ': xs) c str Source #

Instances
Superset "r-UTF8" "r-ASCII" Source #

allow to treat ASCII encodings as UTF8 forgetting about B64 encoding

>>> let Right tstAscii = encodeFAll . toEncoding () $ "Hello World" :: Either EncodeEx (Enc '["r-ASCII"] () T.Text)
>>> displ (inject @ "r-UTF8" tstAscii)
"MkEnc '[r-UTF8] () (Text Hello World)"
Instance details

Defined in Data.TypedEncoding.Instances.Restriction.ASCII

Methods

inject :: Enc ("r-ASCII" ': xs) c str -> Enc ("r-UTF8" ': xs) c str Source #

class KnownSymbol x => FromEncString a f str x where Source #

Reverse of ToEncString decodes encoded string back to a

Methods

fromEncStringF :: Enc '[x] () str -> f a Source #

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

Defined in Data.TypedEncoding.Instances.ToEncString.Common

Methods

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

(UnexpectedDecodeErr f, Applicative f) => FromEncString IpV4 (f :: Type -> Type) Text "r-IPv4" Source #
>>> let enc = toEncString @"r-IPv4" @T.Text tstIp
>>> fromEncString @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
[MkEnc Proxy () "128",MkEnc Proxy () "1",MkEnc Proxy () "1",MkEnc 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

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

class KnownSymbol x => ToEncString x str f a where Source #

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

Encodes a as Enc '[xs].

Methods

toEncStringF :: a -> f (Enc '[x] () str) Source #

Instances
IsString str => ToEncString "r-()" str Identity () Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ToEncString.Common

Methods

toEncStringF :: () -> Identity (Enc ("r-()" ': []) () str) Source #

ToEncString "r-IPv4" Text Identity IpV4 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.Common

>>> toEncString @"r-IPv4" @T.Text tstIp
MkEnc 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
"MkEnc '[r-IPv4] () 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

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

IsString str => ToEncString "r-Int-decimal" str Identity Int Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ToEncString.Common

Methods

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

IsString str => ToEncString "r-Word8-decimal" str Identity Word8 Source # 
Instance details

Defined in Data.TypedEncoding.Instances.ToEncString.Common

Methods

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

toEncString :: forall x str f a. ToEncString x str Identity a => a -> Enc '[x] () str Source #

fromEncString :: forall a str x. FromEncString a Identity str x => Enc '[x] () str -> a Source #