| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Data.TypedEncoding.Instances.Support.Helpers
Contents
Description
Support for mostly creating instances ToEncString and FromEncString conversions
Synopsis
- foldEnc :: forall (xs2 :: [Symbol]) (xs1 :: [Symbol]) f c s1 s2. (Foldable f, Functor f) => c -> (s1 -> s2 -> s2) -> s2 -> f (Enc xs1 c s1) -> Enc xs2 c s2
- foldEncStr :: forall (xs2 :: [Symbol]) (xs1 :: [Symbol]) f c s1 s2. (Foldable f, Functor f, IsString s2) => c -> (s1 -> s2 -> s2) -> f (Enc xs1 c s1) -> Enc xs2 c s2
- foldCheckedEnc :: forall (xs2 :: [Symbol]) f c s1 s2. (Foldable f, Functor f) => c -> ([EncAnn] -> s1 -> s2 -> s2) -> s2 -> f (CheckedEnc c s1) -> Enc xs2 c s2
- foldCheckedEncStr :: forall (xs2 :: [Symbol]) f c s1 s2. (Foldable f, Functor f, IsString s2) => c -> ([EncAnn] -> s1 -> s2 -> s2) -> f (CheckedEnc c s1) -> Enc xs2 c s2
- splitPayload :: forall (xs2 :: [Symbol]) (xs1 :: [Symbol]) c s1 s2. (s1 -> [s2]) -> Enc xs1 c s1 -> [Enc xs2 c s2]
- splitSomePayload :: forall c s1 s2. ([EncAnn] -> s1 -> [([EncAnn], s2)]) -> CheckedEnc c s1 -> [CheckedEnc c s2]
- verifyWithRead :: forall a str. (IsStringR str, Read a, Show a) => String -> str -> Either String str
- verifyDynEnc :: forall s str err1 err2 enc a. (KnownSymbol s, Show err1, Show err2) => Proxy s -> (Proxy s -> Either err1 enc) -> (enc -> str -> Either err2 a) -> str -> Either EncodeEx str
Documentation
>>>:set -XTypeApplications>>>import qualified Data.Text as T>>>import Data.Word
Composite encodings from Foldable Functor types
foldEnc :: forall (xs2 :: [Symbol]) (xs1 :: [Symbol]) f c s1 s2. (Foldable f, Functor f) => c -> (s1 -> s2 -> s2) -> s2 -> f (Enc xs1 c s1) -> Enc xs2 c s2 Source #
allows to fold payload in Enc to create another Enc, assumes homogeneous input encodings.
 This yields not a type safe code, better implementation code should use fixed size
 dependently typed Vect n or some HList like foldable.
Since: 0.2.0.0
foldEncStr :: forall (xs2 :: [Symbol]) (xs1 :: [Symbol]) f c s1 s2. (Foldable f, Functor f, IsString s2) => c -> (s1 -> s2 -> s2) -> f (Enc xs1 c s1) -> Enc xs2 c s2 Source #
Similar to foldEnc, assumes that destination payload has IsString instance and uses "" as base case. 
Since: 0.2.0.0
foldCheckedEnc :: forall (xs2 :: [Symbol]) f c s1 s2. (Foldable f, Functor f) => c -> ([EncAnn] -> s1 -> s2 -> s2) -> s2 -> f (CheckedEnc c s1) -> Enc xs2 c s2 Source #
Similar to foldEnc, works with untyped CheckedEnc
Since: 0.2.0.0
foldCheckedEncStr :: forall (xs2 :: [Symbol]) f c s1 s2. (Foldable f, Functor f, IsString s2) => c -> ([EncAnn] -> s1 -> s2 -> s2) -> f (CheckedEnc c s1) -> Enc xs2 c s2 Source #
Similar to foldEncStr, works with untyped CheckedEnc
Since: 0.2.0.0
Composite encoding: Recreate and Encode helpers
splitPayload :: forall (xs2 :: [Symbol]) (xs1 :: [Symbol]) c s1 s2. (s1 -> [s2]) -> Enc xs1 c s1 -> [Enc xs2 c s2] Source #
Splits composite payload into homogenious chunks
Since: 0.2.0.0
splitSomePayload :: forall c s1 s2. ([EncAnn] -> s1 -> [([EncAnn], s2)]) -> CheckedEnc c s1 -> [CheckedEnc c s2] Source #
Untyped version of splitPayload
Since: 0.2.0.0
Utility combinators
verifyWithRead :: forall a str. (IsStringR str, Read a, Show a) => String -> str -> Either String str Source #
sometimes show . read is not identity, eg. Word8:
>>>read "256" :: Word80
>>>verifyWithRead @Word8 "Word8-decimal" (T.pack "256")Left "Payload does not satisfy format Word8-decimal: 256"
>>>verifyWithRead @Word8 "Word8-decimal" (T.pack "123")Right "123"
Since: 0.2.0.0
Arguments
| :: (KnownSymbol s, Show err1, Show err2) | |
| => Proxy s | proxy defining encoding annotation | 
| -> (Proxy s -> Either err1 enc) | finds encoding marker  | 
| -> (enc -> str -> Either err2 a) | decoder based on  | 
| -> str | input | 
| -> Either EncodeEx str | 
Convenience function for checking if str decodes without error
 using enc encoding markers and decoders that can pick decoder based
 on that marker
Since: 0.3.0.0