| Portability | see LANGUAGE pragmas (... GHC) |
|---|---|
| Stability | experimental |
| Maintainer | nicolas.frisby@gmail.com |
| Safe Haskell | None |
Data.Yoko.HCompos
Description
The generic homomorphism or "heterogenous compos".
See the paper "A Pattern for Almost Homomorphic Functions" at http://www.ittc.ku.edu/~nfrisby/frisby-2012-wgp.pdf, presented at the Workshop on Generic Programming 2012.
- type family Idiom cnv :: * -> *
- class Applicative (Idiom cnv) => Convert0 cnv a b where
- class Applicative (Idiom cnv) => HCompos0 cnv a t where
- data FoundDC k l
- = NoCorrespondingConstructorFor_In_ k k
- | Match l
- type family WithMessage dcA b dcB :: FoundDC k l
- type family FindDCs s dcBs :: Maybe (* -> * -> *)
- data ResultsInIncompatibleFields dcA dcB = ResultsInIncompatibleFields
- class Applicative (Idiom cnv) => MapRs0 cnv msg dc dc' prod prod' where
Documentation
class Applicative (Idiom cnv) => Convert0 cnv a b whereSource
Use the conversion cnv to convert from a to b.
Instances
| (Applicative i, ~ * a x, ~ * b y) => Convert0 (a -> i b) x y |
class Applicative (Idiom cnv) => HCompos0 cnv a t whereSource
The generic version of convert; operates on disbanded data types.
Instances
| (Generic * dcA, ~ (FoundDC * (* -> * -> *)) (Match * (* -> * -> *) (N * dcB)) (WithMessage * (* -> * -> *) dcA b (FindDCs (Tag * dcA) (DCs * b))), MapRs0 * * * * cnv (ResultsInIncompatibleFields * dcA dcB) dcA dcB (Rep * dcA) (Rep * dcB), DC * dcB, ~ * (Codomain * dcB) b, DT * b) => HCompos0 * * cnv (N * dcA) b | |
| (HCompos0 * * cnv a t, HCompos0 * * cnv b t) => HCompos0 * * cnv (:+: a b) t |
Constructors
| NoCorrespondingConstructorFor_In_ k k | |
| Match l |
type family WithMessage dcA b dcB :: FoundDC k lSource
type family FindDCs s dcBs :: Maybe (* -> * -> *)Source
FindDCs dcA dcBs returns a type-level Maybe. Just dcB is a fields
type dcB where .
Tag dcA ~ dcB
data ResultsInIncompatibleFields dcA dcB Source
Constructors
| ResultsInIncompatibleFields |
class Applicative (Idiom cnv) => MapRs0 cnv msg dc dc' prod prod' whereSource
Same as compos semantics, but with a generalized type and just for
converting between product representations.
Instances
| Applicative (Idiom cnv) => MapRs0 k k1 * * cnv msg dc dc' U U | |
| Applicative (Idiom cnv) => MapRs0 k k1 * * cnv msg dc dc' (T0 Dep a) (T0 Dep a) | |
| Convert0 cnv a b => MapRs0 k k1 * * cnv msg dc dc' (T0 (Rec lbl) a) (T0 (Rec lbl') b) | |
| (MapRs0 k k1 * * cnv msg dc dc' a a', MapRs0 k k1 * * cnv msg dc dc' b b') => MapRs0 k k1 * * cnv msg dc dc' (:*: a b) (:*: a' b') | |
| (Traversable f, MapRs0 k k1 * * cnv msg dc dc' a a') => MapRs0 k k1 * * cnv msg dc dc' (T1 Dep f a) (T1 Dep f a') | |
| MapRs0 k k1 * * cnv msg dc dc' a a' => MapRs0 k k1 * * cnv msg dc dc' (C k2 dcA a) (C k3 dcB a') | |
| (Bitraversable f, MapRs0 k k1 * * cnv msg dc dc' a a', MapRs0 k k1 * * cnv msg dc dc' b b') => MapRs0 k k1 * * cnv msg dc dc' (T2 Dep f a b) (T2 Dep f a' b') |