Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- class FlattenAs (y :: Symbol) (x :: Symbol) where
- class KnownSymbol x => FromEncString a f str x where
- fromEncStringF :: Enc '[x] () str -> f a
- class KnownSymbol x => ToEncString x str f a where
- toEncStringF :: a -> f (Enc '[x] () str)
- toEncString :: forall x str f a. ToEncString x str Identity a => a -> Enc '[x] () str
- fromEncString :: forall a str x. FromEncString a Identity str x => Enc '[x] () str -> a
- module Data.TypedEncoding.Internal.Class.Util
- module Data.TypedEncoding.Internal.Class.Encode
- module Data.TypedEncoding.Internal.Class.Decode
- module Data.TypedEncoding.Internal.Class.Recreate
- module Data.TypedEncoding.Internal.Class.Superset
- module Data.TypedEncoding.Internal.Class.Encoder
Documentation
class FlattenAs (y :: Symbol) (x :: Symbol) where Source #
Flatten is more permissive than Superset
instance FlattenAs "r-ASCII" "enc-B64" where -- OK
Now encoded data has form Enc '["r-ASCII"] c str
and there is no danger of it begin incorrectly decoded.
Nothing
Instances
FlattenAs "r-ASCII" "enc-B64" Source # | |
FlattenAs "r-ASCII" "enc-B64-nontext" Source # | allow to treat B64 encodings as ASCII forgetting about B64 encoding
|
class KnownSymbol x => FromEncString a f str x where Source #
Reverse of ToEncString
decodes encoded string back to a
fromEncStringF :: Enc '[x] () str -> f a Source #
Instances
(IsStringR str, UnexpectedDecodeErr f, Applicative f) => FromEncString Word8 (f :: Type -> Type) str "r-Word8-decimal" Source # | |
Defined in Data.TypedEncoding.Instances.ToEncString.Common fromEncStringF :: Enc ("r-Word8-decimal" ': []) () str -> f Word8 Source # | |
(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 |
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]
.
toEncStringF :: a -> f (Enc '[x] () str) Source #
Instances
IsString str => ToEncString "r-()" str Identity () Source # | |
Defined in Data.TypedEncoding.Instances.ToEncString.Common toEncStringF :: () -> Identity (Enc ("r-()" ': []) () str) Source # | |
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 | |
IsString str => ToEncString "r-Int-decimal" str Identity Int Source # | |
IsString str => ToEncString "r-Word8-decimal" str Identity Word8 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 #