Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- genericAdaptor :: GAdaptable p a b c => a -> p b c
- type Adaptor p a = a -> p (Unzip 'Fst a) (Unzip 'Snd a)
- type GAdaptable p a b c = (Generic a, Generic b, Generic c, GUnzip 'Fst (Rep a) ~ Rep b, GUnzip 'Snd (Rep a) ~ Rep c, GAdaptor p (Rep a))
- data Select
- class Unzippable (a :: k)
- type family Unzip (z :: Select) (a :: k) :: k where ...
- type family Unzip' (z :: Select) (a :: k) :: k where ...
- class TypePair a where
- type family GUnzip (z :: Select) (f :: * -> *) :: * -> *
- class Profunctor p => GAdaptor p f | f -> p where
Exported
genericAdaptor :: GAdaptable p a b c => a -> p b c Source #
Generic adaptor.
genericAdaptor
::ProductProfunctor
p =>Adaptor
p (Foo (p a a') (p b b') (p c c'))genericAdaptor
::ProductProfunctor
p => Foo (p a a') (p b b') (p c c') -> p (Foo a b c) (Foo a' b' c')
type Adaptor p a = a -> p (Unzip 'Fst a) (Unzip 'Snd a) Source #
A type synonym to shorten the signature of an adaptor.
Adaptor
p (Foo (p a a') (p b b') (p c c'))
~
Foo (p a a') (p b b') (p c c') -> p (Foo a b c) (Foo a' b' c')
Implementation
type GAdaptable p a b c = (Generic a, Generic b, Generic c, GUnzip 'Fst (Rep a) ~ Rep b, GUnzip 'Snd (Rep a) ~ Rep c, GAdaptor p (Rep a)) Source #
A constraint synonym on generic types for which an adaptor can be defined generically.
class Unzippable (a :: k) Source #
A type like
T = Foo (p a a') (p b b') (p c c')
can be unzipped to
Unzip 'Fst T = Foo a b c Unzip 'Snd T = Foo a' b' c'
This defines the type family Unzip
with versions of GHC older than 8.0.1.
For 8.0.1 and newer versions, Unzip
is an independent type family
and Unzippable
is just an empty class for backwards compatibility.
type family Unzip' (z :: Select) (a :: k) :: k where ... Source #
A hack to enable kind-polymorphic recursion.
A type p a b
can be seen as a type-level pair '(a, b)
.
type family GUnzip (z :: Select) (f :: * -> *) :: * -> * Source #
Unzips the types of fields of a record.
T = (M1 _ _ (K1 _ (p c1 c2))) :*: (M1 _ _ (K1 _ (p d1 d2))) GUnzip 'Fst T = (M1 _ _ (K1 _ c1 )) :*: (M1 _ _ (K1 _ d1 )) GUnzip 'Snd T = (M1 _ _ (K1 _ c2 )) :*: (M1 _ _ (K1 _ d2 ))
class Profunctor p => GAdaptor p f | f -> p where Source #
Adaptors over generic representations of types.