| Portability | see LANGUAGE pragmas (... GHC) |
|---|---|
| Stability | experimental |
| Maintainer | nicolas.frisby@gmail.com |
Data.Yoko.InDT
Description
Various universes determined by a data constructor type's suitability to be embedded in a data type.
- data HasTagRepDCD tag c t where
- HasTagRepDCD :: DT t => Exists (DCOf t :&& TagRepIs tag c) (DCs t) -> HasTagRepDCD tag c t
- hasTagRepDCD :: HasTagRepDCD tag c t -> RMI c -> t
- type HasTagRepDCImageD fn dc = HasTagRepDCD (Tag dc) (CApp fn (Rep dc))
- data ImageInDTD t fn dc where
- ImageInDTD :: (Generic dc, (Rep dc) ::: (Domain (CMap fn IdM))) => HasTagRepDCImageD (fn IdM) dc t -> ImageInDTD t fn dc
- imageInDTD :: (forall t. fn IdM t) -> ImageInDTD t fn dc -> RMNI dc -> t
- data ImageInDTDA t fn dc where
- ImageInDTDA :: (Generic dc, (Rep dc) ::: (DomainA (CMap fn IdM))) => HasTagRepDCImageD (fn IdM) dc t -> ImageInDTDA t fn dc
- imageInDTAD :: Functor (Idiom (fn IdM)) => (forall t. fn IdM t) -> ImageInDTDA t fn dc -> RMNI dc -> Idiom (fn IdM) t
Documentation
data HasTagRepDCD tag c t whereSource
A type t inhabits HasTagRepDCD tag c if t is a DT and there exists a t
constructor satisfying .
TagRepIs tag c
Constructors
| HasTagRepDCD :: DT t => Exists (DCOf t :&& TagRepIs tag c) (DCs t) -> HasTagRepDCD tag c t |
hasTagRepDCD :: HasTagRepDCD tag c t -> RMI c -> tSource
Given HasTagRepDCD tag c t, a trivially-mediated c value can be embedded into
t.
type HasTagRepDCImageD fn dc = HasTagRepDCD (Tag dc) (CApp fn (Rep dc))Source
Often times, we're interested in the universe of types accomodating a data constructor's image under some type-function.
data ImageInDTD t fn dc whereSource
A constructor type dc inhabits ImageHasTagRepDCD t fn if
-
fncan be mapped across the recursive occurrences indc, and -
thas a constructor isomorphic to thefn-image ofdc
Constructors
| ImageInDTD :: (Generic dc, (Rep dc) ::: (Domain (CMap fn IdM))) => HasTagRepDCImageD (fn IdM) dc t -> ImageInDTD t fn dc |
imageInDTD :: (forall t. fn IdM t) -> ImageInDTD t fn dc -> RMNI dc -> tSource
Given ImageInDTD t fn dc, a trivially-mediated dc value can be
embedded into t.
data ImageInDTDA t fn dc whereSource
Same as ImageInDTD, but uses an implicitly applicative function.
Constructors
| ImageInDTDA :: (Generic dc, (Rep dc) ::: (DomainA (CMap fn IdM))) => HasTagRepDCImageD (fn IdM) dc t -> ImageInDTDA t fn dc |
imageInDTAD :: Functor (Idiom (fn IdM)) => (forall t. fn IdM t) -> ImageInDTDA t fn dc -> RMNI dc -> Idiom (fn IdM) tSource