yoko-0.2: generic programming with disbanded constructors

Portabilitysee LANGUAGE pragmas (... GHC)
Stabilityexperimental
Maintainernicolas.frisby@gmail.com

Data.Yoko.InDT

Description

Various universes determined by a data constructor type's suitability to be embedded in a data type.

Synopsis

Documentation

data HasTagRepU tag c t whereSource

A type t inhabits HasTagRepU tag c if t is a DT and there exists a t constructor satisfying TagRepIs tag c.

Constructors

HasTagRepU :: DT t => Exists (DCOf t :&& TagRepIs tag c) (DCs t) -> HasTagRepU tag c t 

Instances

(DT t, (DCs t) ::: (Exists (:&& (DCOf t) (TagRepIs tag c)))) => t ::: (HasTagRepU tag c) 

hasTagRepU :: HasTagRepU tag c t -> RMI c -> tSource

Given HasTagRepU tag c t, a trivially-mediated c value can be embedded into t.

type HasTagRepImageU fn dc = HasTagRepU (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 ImageInDTU t fn dc whereSource

A constructor type dc inhabits ImageHasTagRepU t fn if

  1. fn can be mapped across the recursive occurrences in dc, and
  2. t has a constructor isomorphic to the fn-image of dc

Constructors

ImageInDTU :: (Generic dc, (Rep dc) ::: (Domain (CMap fn IdM))) => HasTagRepImageU (fn IdM) dc t -> ImageInDTU t fn dc 

Instances

(Generic dc, (Rep dc) ::: (Domain (CMap fn IdM)), t ::: (HasTagRepImageU (fn IdM) dc)) => dc ::: (ImageInDTU t fn) 

imageInDTU :: (forall t. fn IdM t) -> ImageInDTU t fn dc -> RMNI dc -> tSource

Given ImageInDTU 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))) => HasTagRepImageU (fn IdM) dc t -> ImageInDTDA t fn dc 

Instances

(Generic dc, (Rep dc) ::: (DomainA (CMap fn IdM)), t ::: (HasTagRepImageU (fn IdM) dc)) => dc ::: (ImageInDTDA t fn) 

imageInDTAU :: Functor (Idiom (fn IdM)) => (forall t. fn IdM t) -> ImageInDTDA t fn dc -> RMNI dc -> Idiom (fn IdM) tSource