product-profunctors-0.9.0.0: product-profunctors

Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Product.Internal.Adaptor

Contents

Synopsis

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.

data Select Source #

A flag denoting a type-level field accessor.

Constructors

Fst 
Snd 

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 #

Equations

Unzip z (f a) = Unzip' z f (Project z a) 
Unzip z a = a 

type family Unzip' (z :: Select) (a :: k) :: k where ... Source #

A hack to enable kind-polymorphic recursion.

Equations

Unzip' z a = Unzip z a 

class TypePair a Source #

A type p a b can be seen as a type-level pair '(a, b).

Associated Types

type Project (z :: Select) a Source #

This type synonym extracts a component, a or b, of that pair p a b.

Instances

TypePair * (p a b) Source # 

Associated Types

type Project (p a b) (z :: Select) (a :: p a b) :: * Source #

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 ))

Instances

type GUnzip z (K1 * i c) Source # 
type GUnzip z (K1 * i c) = K1 * i (Project * z c)
type GUnzip z ((:*:) * f g) Source # 
type GUnzip z ((:*:) * f g) = (:*:) * (GUnzip z f) (GUnzip z g)
type GUnzip z (M1 * i c f) Source # 
type GUnzip z (M1 * i c f) = M1 * i c (GUnzip z f)

class Profunctor p => GAdaptor p f | f -> p where Source #

Adaptors over generic representations of types.

Minimal complete definition

gAdaptor

Methods

gAdaptor :: f a -> p (GUnzip Fst f a) (GUnzip Snd f a) Source #

Instances

Profunctor p => GAdaptor p (K1 * i (p a b)) Source # 

Methods

gAdaptor :: K1 * i (p a b) a -> p (GUnzip Fst (K1 * i (p a b)) a) (GUnzip Snd (K1 * i (p a b)) a) Source #

(ProductProfunctor p, GAdaptor p f, GAdaptor p g) => GAdaptor p ((:*:) * f g) Source # 

Methods

gAdaptor :: (* :*: f) g a -> p (GUnzip Fst ((* :*: f) g) a) (GUnzip Snd ((* :*: f) g) a) Source #

GAdaptor p f => GAdaptor p (M1 * i c f) Source # 

Methods

gAdaptor :: M1 * i c f a -> p (GUnzip Fst (M1 * i c f) a) (GUnzip Snd (M1 * i c f) a) Source #