Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Common combinators used across encodings.
Since: 0.2.1.0
Synopsis
- decFR :: (IsR s ~ True, Applicative f) => Enc (s ': xs) c str -> f (Enc xs c str)
- recWithEncR :: forall (s :: Symbol) xs c str. IsR s ~ True => (Enc xs c str -> Either EncodeEx (Enc (s ': xs) c str)) -> Enc xs c str -> Either RecreateEx (Enc (s ': xs) c str)
- unsafeRecWithEncR :: forall (s :: Symbol) xs c str. (Enc xs c str -> Either EncodeEx (Enc (s ': xs) c str)) -> Enc xs c str -> Either RecreateEx (Enc (s ': xs) c str)
- type family IsR (s :: Symbol) :: Bool where ...
- type family IsROrEmpty (s :: Symbol) :: Bool where ...
Documentation
>>>
:set -XOverloadedStrings -XMultiParamTypeClasses -XDataKinds -XTypeApplications
decFR :: (IsR s ~ True, Applicative f) => Enc (s ': xs) c str -> f (Enc xs c str) Source #
Universal decode for all "r-" types
recWithEncR :: forall (s :: Symbol) xs c str. IsR s ~ True => (Enc xs c str -> Either EncodeEx (Enc (s ': xs) c str)) -> Enc xs c str -> Either RecreateEx (Enc (s ': xs) c str) Source #
Manual recreate step combinator converting "r-"
encode function to a recreate step.
For "r-" encoding recreate and encode are the same other than the exception type used.
The convention in typed-encoding
is to implement encode and convert it to recreate.
unsafeRecWithEncR :: forall (s :: Symbol) xs c str. (Enc xs c str -> Either EncodeEx (Enc (s ': xs) c str)) -> Enc xs c str -> Either RecreateEx (Enc (s ': xs) c str) Source #
type family IsR (s :: Symbol) :: Bool where ... Source #
>>>
:kind! IsR "r-UPPER"
... ... 'True
>>>
:kind! IsR "do-UPPER"
... = (TypeError ...
type family IsROrEmpty (s :: Symbol) :: Bool where ... Source #
IsROrEmpty "" = True | |
IsROrEmpty x = IsR x |