yoko-0.9: Generic Programming with Disbanded Data Types

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

Data.YokoRaw

Contents

Description

This is the entire library, excluding the fancy builder of precise cases from Data.Yoko.SmartPreciseCase.

Synopsis

Representation

Sums

data Void Source

The empty sum. Used as an error type instead of a represention type, since data types with no constructors are uninteresting from a generic programming perspective -- there's just not much to be done generically.

newtype N a Source

The singleton sum.

Constructors

N a 

Instances

cxt a => Each_ cxt (N a) 
(Applicative (Idiom cnv), Generic dcA, ~ (FoundDC *) (Match * dcB) (WithMessage dcA b (FindDCs (Tag dcA) (DCs b))), MapRs cnv (ResultsInIncompatibleFields dcA dcB) dcA dcB (Rep dcA) (Rep dcB), DC dcB, ~ * (Codomain dcB) b, DT b) => HCompos cnv (N dcA) b 
Generic a => EachGeneric (N a) 
(~ (Maybe *) (Locate x sup) (Just * path), InjectAt path x sup) => Embed (N x) sup 
Partition_N (Elem x subL) x subL subR => Partition (N x) subL subR 
InjectAt (Here a) a (N a) 

data a :+: b Source

Sum union.

Constructors

L a 
R b 

Instances

(Each_ cxt a, Each_ cxt b) => Each_ cxt (:+: a b) 
(Applicative (Idiom cnv), HCompos cnv a t, HCompos cnv b t) => HCompos cnv (:+: a b) t 
InjectAt path a r => InjectAt (TurnRight path) a (:+: l r) 
InjectAt path a l => InjectAt (TurnLeft path) a (:+: l r) 
(Eq a, Eq b) => Eq (:+: a b) 
(Eq (:+: a b), Ord a, Ord b) => Ord (:+: a b) 
(Read a, Read b) => Read (:+: a b) 
(Show a, Show b) => Show (:+: a b) 
(EachGeneric a, EachGeneric b) => EachGeneric (:+: a b) 
(Embed l sup, Embed r sup) => Embed (:+: l r) sup 
(Partition a subL subR, Partition b subL subR) => Partition (:+: a b) subL subR 

Products

data U Source

The empty product.

Constructors

U 

Instances

Applicative (Idiom cnv) => MapRs cnv msg dc dc' U U 

data a :*: b Source

Product union.

Constructors

a :*: b 

Instances

(Applicative (Idiom cnv), MapRs cnv msg dc dc' a a', MapRs cnv msg dc dc' b b') => MapRs cnv msg dc dc' (:*: a b) (:*: a' b') 

Fields

newtype Rec a Source

A recursive occurrence.

Constructors

Rec a 

Instances

(Applicative (Idiom cnv), Convert cnv a b) => MapRs cnv msg dc dc' (Rec a) (Rec b) 

newtype Dep a Source

A non-recursive occurrence.

Constructors

Dep a 

Instances

Applicative (Idiom cnv) => MapRs cnv msg dc dc' (Dep a) (Dep a) 

newtype Par1 f a Source

Representation of unary type application. f is a genuine *->* type, not a representation. a is a representation.

Constructors

Par1 (f a) 

Instances

(Applicative (Idiom cnv), Traversable f, MapRs cnv msg dc dc' a a') => MapRs cnv msg dc dc' (Par1 f a) (Par1 f a') 

newtype Par2 f a b Source

Representation of binary type application. f is a genuine *->*->* type, not a representation. a and b are representations.

Constructors

Par2 (f a b) 

Instances

(Applicative (Idiom cnv), Bitraversable f, MapRs cnv msg dc dc' a a', MapRs cnv msg dc dc' b b') => MapRs cnv msg dc dc' (Par2 f a b) (Par2 f a' b') 

Conversions to and from fields-of-products structure

type family Rep a Source

A mapping to the structural representation of a fields type: just products of fields, no sums -- fields types have just one constructor.

class Generic a whereSource

Converts between a fields type and its product-of-fields structure.

Methods

rep :: a -> Rep aSource

obj :: Rep a -> aSource

Auxilliaries

unN :: N t -> tSource

foldN :: (b -> c) -> N b -> cSource

mapN :: (b1 -> b) -> N b1 -> N bSource

foldPlus :: (t1 -> t) -> (t2 -> t) -> :+: t1 t2 -> tSource

mapPlus :: (t -> b) -> (t1 -> b1) -> :+: t t1 -> :+: b b1Source

foldTimes :: (t3 -> t4 -> t) -> (t1 -> t3) -> (t2 -> t4) -> :*: t1 t2 -> tSource

mapTimes :: (t -> a) -> (t1 -> b) -> :*: t t1 -> :*: a bSource

unRec :: Rec t -> tSource

mapRec :: (t -> a) -> Rec t -> Rec aSource

unDep :: Dep t -> tSource

unPar1 :: Par1 t t1 -> t t1Source

unPar2 :: Par2 t t1 t2 -> t t1 t2Source

type family DistMaybePlus a b :: Maybe *Source

We avoid empty sums with a type-level Maybe. DistMaybePlus performs sum union on lifted sums, only introducing :+: when both arguments are Justs.

Reflection

Fields types

type family Tag dc :: DigitSource

Tag returns a simulated type-level string that is the name of the constructor that the dc fields type represents.

type family Codomain dc Source

Codomain is the data type that contains the constructor that the fields type dc represents. It can also be applied to sums of fields types, in which case it just uses the left-most.

class (Generic dc, DT (Codomain dc)) => DC dc whereSource

Any fields type can be further represented as a product-of-fields and can be injected back into the original data type.

Methods

rejoin :: dc -> Codomain dcSource

Disbanded data types

type family DCs t Source

The DCs of a data type is sum of all of its fields types.

class Each IsDCOf (DCs t) => DT t whereSource

DT disbands a data type if all of its fields types have DC instances.

Methods

disband :: t -> DCs tSource

Building fields type consumers

one :: (dc -> a) -> N dc -> aSource

one extends a function that consumes a fields type to a function that consumes a disbanded data type containing just that fields type.

(|||) :: Codomain sumL ~ Codomain sumR => (sumL -> a) -> (sumR -> a) -> (sumL :+: sumR) -> aSource

Combines two functions that consume disbanded data types into a function that consumes their union. All fields types must be from the same data type.

(||.) :: ~ * (Codomain sumL) (Codomain dc) => (sumL -> a) -> (dc -> a) -> :+: sumL (N dc) -> aSource

f ||. g = f ||| one g

(.||) :: ~ * (Codomain sumR) (Codomain dc) => (dc -> a) -> (sumR -> a) -> :+: (N dc) sumR -> aSource

f .|| g = one f ||| g

(.|.) :: ~ * (Codomain dc) (Codomain dc1) => (dc -> a) -> (dc1 -> a) -> :+: (N dc) (N dc1) -> aSource

f .|. g = one f ||| one g

Operations on disbanded data types

disbanded :: Embed (N dc) (DCs (Codomain dc)) => dc -> DCs (Codomain dc)Source

disbanded injects a fields type into its disbanded range

band :: forall t. Each (ConDCOf t) (DCs t) => DCs t -> tSource

bands a disbanded data type back into its normal data type.

Since Disbanded is a type family, the range of band determines the t type variable.

class (Codomain dc ~ t, DC dc) => ConDCOf t dc Source

Instances

(~ * (Codomain dc) t, DC dc) => ConDCOf t dc 

precise_case :: (Codomain dcs ~ t, Codomain (DCs t) ~ t, DT t, Partition (DCs t) dcs (DCs t :-: dcs)) => ((DCs t :-: dcs) -> a) -> t -> (dcs -> a) -> aSource

precise_case is an exactly-typed case: the second argument is the discriminant, the first argument is the default case, and the third argument approximates a list of alternatives.

 precise_case default x $
   ((C0_ ...) -> ...) .||
   ((C1_ ...) -> ...) .|.
   ((C2_ ...) -> ...)

In this example, C0_, C1_, and C2_ are fields types. The other fields types for the same data type are handled with the default function.

Operations on sums of fields types

type family sum :-: sum2 Source

class Embed sub sup Source

Instances

(~ (Maybe *) (Locate x sup) (Just * path), InjectAt path x sup) => Embed (N x) sup 
(Embed l sup, Embed r sup) => Embed (:+: l r) sup 

class Partition sup subL subR Source

Instances

Partition_N (Elem x subL) x subL subR => Partition (N x) subL subR 
(Partition a subL subR, Partition b subL subR) => Partition (:+: a b) subL subR 

embed :: (Codomain sub ~ Codomain sup, Embed sub sup) => sub -> supSource

inject :: Embed (N dc) sum => dc -> sumSource

injects a fields type into a sum of fields types.

partition :: (Codomain sum ~ Codomain sub, Partition sum sub (sum :-: sub)) => sum -> Either sub (sum :-: sub)Source

partitions a sum of fields type into a specified sum of fields types and the remaining sum.

project :: (Codomain sum ~ Codomain dc, Partition sum (N dc) (sum :-: N dc)) => sum -> Either dc (sum :-: N dc)Source

projects a single fields type out of a disbanded data type.

Forgetting yoko's extra structure

reps :: EachGeneric sum => sum -> EachRep sumSource

reps maps a disbanded data type to its sum-of-products representation.

class EachGeneric sum Source

Instances

type family EachRep sum Source

ig_from :: (DT t, EachGeneric (DCs t)) => t -> EachRep (DCs t)Source

ig_from x = 'reps $ disband' x is a convenience. It approximates the instant-generics view, less the CEq annotations.

type Equal a b = IsEQ (SpineCompare a b)Source

Convenient synonym. type Equal a b = IsEQ (SpineCompare a b)

Bundled Template Haskell