multirec-0.7.8: Generic programming for families of recursive datatypes

Copyright(c) 2008--2010 Universiteit Utrecht
LicenseBSD3
Maintainergenerics@haskell.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Generics.MultiRec.Base

Contents

Description

This module is the base of the multirec library. It defines the view of a family of datatypes: All the datatypes of the family are represented as indexed functors that are built up from the structure types defined in this module. Furthermore, in order to use the library for a family, conversion functions have to be defined between the original datatypes and their representation. The type class that holds these conversion functions are also defined here.

Synopsis

Structure types

data I xi r ix Source #

Represents recursive positions. The first argument indicates which type to recurse on.

Constructors

I 

Fields

Instances

El phi xi => HEq phi (I xi) Source # 

Methods

heq :: (forall ix. phi ix -> r ix -> r ix -> Bool) -> phi ix -> I xi r ix -> I xi r ix -> Bool Source #

El phi xi => HFunctor phi (I xi) Source # 

Methods

hmapA :: Applicative a => (forall ix. phi ix -> r ix -> a (r' ix)) -> phi ix -> I xi r ix -> a (I xi r' ix) Source #

El phi xi => HReadPrec phi (I xi) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (I xi I0 ix) Source #

El phi xi => HShow phi (I xi) Source # 

Methods

hShowsPrecAlg :: Algebra' phi (I xi) [Int -> ShowS] Source #

(Constructor c, HReadPrec phi (I xi)) => HReadPrec phi (C c (I xi)) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (C c (I xi) I0 ix) Source #

ConNames (I a) Source # 

Methods

hconNames :: I a r ix -> [String] Source #

Fold (I xi) Source # 

Methods

alg :: Alg (I xi) r ix -> I xi r ix -> r ix Source #

Fold (I xi) Source # 

Methods

alg :: Alg (I xi) r -> I xi (K0 r) ix -> r Source #

CountAtoms (I xi) Source # 

Methods

countatoms :: I xi r ix -> Int Source #

Functor f => Fold ((:.:) f (I xi)) Source # 

Methods

alg :: Alg (f :.: I xi) r ix -> (f :.: I xi) r ix -> r ix Source #

Fold g => Fold ((:*:) (I xi) g) Source # 

Methods

alg :: Alg (I xi :*: g) r ix -> (I xi :*: g) r ix -> r ix Source #

Fold g => Fold ((:*:) (I xi) g) Source # 

Methods

alg :: Alg (I xi :*: g) r -> (I xi :*: g) (K0 r) ix -> r Source #

type Alg (I xi) r Source # 
type Alg (I xi) r = r -> r
type Comp (I xi) r ix Source # 
type Comp (I xi) r ix = r xi
type Alg (I xi) r ix Source # 
type Alg (I xi) r ix = r xi -> r ix
type Alg ((:*:) (I xi) g) r Source # 
type Alg ((:*:) (I xi) g) r = r -> Alg g r
type Alg ((:.:) f (I xi)) r ix Source # 
type Alg ((:.:) f (I xi)) r ix = f (r xi) -> r ix

data K a r ix Source #

Represents constant types that do not belong to the family.

Constructors

K 

Fields

Instances

Eq a => HEq phi (K a) Source #

For constant types, we make use of the standard equality function.

Methods

heq :: (forall ix. phi ix -> r ix -> r ix -> Bool) -> phi ix -> K a r ix -> K a r ix -> Bool Source #

HFunctor phi (K x) Source # 

Methods

hmapA :: Applicative a => (forall ix. phi ix -> r ix -> a (r' ix)) -> phi ix -> K x r ix -> a (K x r' ix) Source #

Read a => HReadPrec phi (K a) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (K a I0 ix) Source #

Show a => HShow phi (K a) Source #

For constant types, we make use of the standard show function.

Methods

hShowsPrecAlg :: Algebra' phi (K a) [Int -> ShowS] Source #

(Constructor c, HReadPrec phi (K a)) => HReadPrec phi (C c (K a)) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (C c (K a) I0 ix) Source #

ConNames (K x) Source # 

Methods

hconNames :: K x r ix -> [String] Source #

Fold (K a) Source # 

Methods

alg :: Alg (K a) r ix -> K a r ix -> r ix Source #

Fold (K a) Source # 

Methods

alg :: Alg (K a) r -> K a (K0 r) ix -> r Source #

CountAtoms (K a) Source # 

Methods

countatoms :: K a r ix -> Int Source #

Fold g => Fold ((:*:) (K a) g) Source # 

Methods

alg :: Alg (K a :*: g) r ix -> (K a :*: g) r ix -> r ix Source #

Fold g => Fold ((:*:) (K a) g) Source # 

Methods

alg :: Alg (K a :*: g) r -> (K a :*: g) (K0 r) ix -> r Source #

type Alg (K a) r Source # 
type Alg (K a) r = a -> r
type Comp (K a) r ix Source # 
type Comp (K a) r ix = a
type Alg (K a) r ix Source # 
type Alg (K a) r ix = a -> r ix
type Alg ((:*:) (K a) g) r Source # 
type Alg ((:*:) (K a) g) r = a -> Alg g r

data U r ix Source #

Represents constructors without fields.

Constructors

U 

Instances

ConNames U Source # 

Methods

hconNames :: U r ix -> [String] Source #

Fold U Source # 

Methods

alg :: Alg U r ix -> U r ix -> r ix Source #

Fold U Source # 

Methods

alg :: Alg U r -> U (K0 r) ix -> r Source #

HEq phi U Source # 

Methods

heq :: (forall ix. phi ix -> r ix -> r ix -> Bool) -> phi ix -> U r ix -> U r ix -> Bool Source #

HFunctor phi U Source # 

Methods

hmapA :: Applicative a => (forall ix. phi ix -> r ix -> a (r' ix)) -> phi ix -> U r ix -> a (U r' ix) Source #

HReadPrec phi U Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (U I0 ix) Source #

HShow phi U Source # 

Methods

hShowsPrecAlg :: Algebra' phi U [Int -> ShowS] Source #

Constructor c => HReadPrec phi (C c U) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (C c U I0 ix) Source #

type Alg U r Source # 
type Alg U r = r
type Alg U r ix Source # 
type Alg U r ix = r ix

data (f :+: g) r ix infixr 5 Source #

Represents sums (choices between constructors).

Constructors

L (f r ix) 
R (g r ix) 

Instances

(HEq phi f, HEq phi g) => HEq phi ((:+:) f g) Source # 

Methods

heq :: (forall ix. phi ix -> r ix -> r ix -> Bool) -> phi ix -> (f :+: g) r ix -> (f :+: g) r ix -> Bool Source #

(HFunctor phi f, HFunctor phi g) => HFunctor phi ((:+:) f g) Source # 

Methods

hmapA :: Applicative a => (forall ix. phi ix -> r ix -> a (r' ix)) -> phi ix -> (f :+: g) r ix -> a ((f :+: g) r' ix) Source #

(HReadPrec phi f, HReadPrec phi g) => HReadPrec phi ((:+:) f g) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec ((f :+: g) I0 ix) Source #

(HShow phi f, HShow phi g) => HShow phi ((:+:) f g) Source # 

Methods

hShowsPrecAlg :: Algebra' phi (f :+: g) [Int -> ShowS] Source #

(ConNames f, ConNames g) => ConNames ((:+:) f g) Source # 

Methods

hconNames :: (f :+: g) r ix -> [String] Source #

(Fold f, Fold g) => Fold ((:+:) f g) Source # 

Methods

alg :: Alg (f :+: g) r ix -> (f :+: g) r ix -> r ix Source #

(Fold f, Fold g) => Fold ((:+:) f g) Source # 

Methods

alg :: Alg (f :+: g) r -> (f :+: g) (K0 r) ix -> r Source #

type Alg ((:+:) f g) r Source # 
type Alg ((:+:) f g) r = (Alg f r, Alg g r)
type Alg ((:+:) f g) r ix Source # 
type Alg ((:+:) f g) r ix = (Alg f r ix, Alg g r ix)

data (f :*: g) r ix infixr 7 Source #

Represents products (sequences of fields of a constructor).

Constructors

(f r ix) :*: (g r ix) infixr 7 

Instances

(HEq phi f, HEq phi g) => HEq phi ((:*:) f g) Source # 

Methods

heq :: (forall ix. phi ix -> r ix -> r ix -> Bool) -> phi ix -> (f :*: g) r ix -> (f :*: g) r ix -> Bool Source #

(HFunctor phi f, HFunctor phi g) => HFunctor phi ((:*:) f g) Source # 

Methods

hmapA :: Applicative a => (forall ix. phi ix -> r ix -> a (r' ix)) -> phi ix -> (f :*: g) r ix -> a ((f :*: g) r' ix) Source #

(Constructor c, CountAtoms ((:*:) f g), HReadPrec phi f, HReadPrec phi g) => HReadPrec phi (C c ((:*:) f g)) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (C c (f :*: g) I0 ix) Source #

(HReadPrec phi f, HReadPrec phi g) => HReadPrec phi ((:*:) f g) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec ((f :*: g) I0 ix) Source #

(HShow phi f, HShow phi g) => HShow phi ((:*:) f g) Source # 

Methods

hShowsPrecAlg :: Algebra' phi (f :*: g) [Int -> ShowS] Source #

ConNames ((:*:) f g) Source # 

Methods

hconNames :: (f :*: g) r ix -> [String] Source #

Fold g => Fold ((:*:) (K a) g) Source # 

Methods

alg :: Alg (K a :*: g) r ix -> (K a :*: g) r ix -> r ix Source #

Fold g => Fold ((:*:) (I xi) g) Source # 

Methods

alg :: Alg (I xi :*: g) r ix -> (I xi :*: g) r ix -> r ix Source #

Fold g => Fold ((:*:) (K a) g) Source # 

Methods

alg :: Alg (K a :*: g) r -> (K a :*: g) (K0 r) ix -> r Source #

Fold g => Fold ((:*:) (I xi) g) Source # 

Methods

alg :: Alg (I xi :*: g) r -> (I xi :*: g) (K0 r) ix -> r Source #

(CountAtoms f, CountAtoms g) => CountAtoms ((:*:) f g) Source # 

Methods

countatoms :: (f :*: g) r ix -> Int Source #

type Alg ((:*:) (K a) g) r Source # 
type Alg ((:*:) (K a) g) r = a -> Alg g r
type Alg ((:*:) (I xi) g) r Source # 
type Alg ((:*:) (I xi) g) r = r -> Alg g r
type Alg ((:*:) f g) r ix Source # 
type Alg ((:*:) f g) r ix = Comp f r ix -> Alg g r ix

data (f :>: ix) r ix' where infix 6 Source #

Is used to indicate the type that a particular constructor injects to.

Constructors

Tag :: f r ix -> (f :>: ix) r ix 

Instances

HEq phi f => HEq phi ((:>:) f ix) Source # 

Methods

heq :: (forall ix0. phi ix0 -> r ix0 -> r ix0 -> Bool) -> phi ix -> (f :>: ix) r ix -> (f :>: ix) r ix -> Bool Source #

HFunctor phi f => HFunctor phi ((:>:) f ix) Source # 

Methods

hmapA :: Applicative a => (forall ix0. phi ix0 -> r ix0 -> a (r' ix0)) -> phi ix -> (f :>: ix) r ix -> a ((f :>: ix) r' ix) Source #

(HReadPrec phi f, EqS phi, El phi ix) => HReadPrec phi ((:>:) f ix) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec ((f :>: ix) I0 ix) Source #

HShow phi f => HShow phi ((:>:) f ix) Source # 

Methods

hShowsPrecAlg :: Algebra' phi (f :>: ix) [Int -> ShowS] Source #

ConNames f => ConNames ((:>:) f ix) Source # 

Methods

hconNames :: (f :>: ix) r ix -> [String] Source #

Fold f => Fold ((:>:) f xi) Source # 

Methods

alg :: Alg (f :>: xi) r ix -> (f :>: xi) r ix -> r ix Source #

Fold f => Fold ((:>:) f xi) Source # 

Methods

alg :: Alg (f :>: xi) r -> (f :>: xi) (K0 r) ix -> r Source #

type Alg ((:>:) f xi) r Source # 
type Alg ((:>:) f xi) r = Alg f r
type Alg ((:>:) f xi) r ix Source # 
type Alg ((:>:) f xi) r ix = Alg f r xi

unTag :: (f :>: ix) r ix -> f r ix Source #

Destructor for '(:>:)'.

data (f :.: g) r ix Source #

Represents composition with functors of kind * -> *.

Constructors

D 

Fields

  • unD :: f (g r ix)
     

Instances

(Eq1 f, HEq phi g) => HEq phi ((:.:) f g) Source # 

Methods

heq :: (forall ix. phi ix -> r ix -> r ix -> Bool) -> phi ix -> (f :.: g) r ix -> (f :.: g) r ix -> Bool Source #

(Traversable f, HFunctor phi g) => HFunctor phi ((:.:) f g) Source # 

Methods

hmapA :: Applicative a => (forall ix. phi ix -> r ix -> a (r' ix)) -> phi ix -> (f :.: g) r ix -> a ((f :.: g) r' ix) Source #

(Constructor c, HReadPrec phi ((:.:) f g)) => HReadPrec phi (C c ((:.:) f g)) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (C c (f :.: g) I0 ix) Source #

(Read1 f, HReadPrec phi g) => HReadPrec phi ((:.:) f g) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec ((f :.: g) I0 ix) Source #

(Show1 f, Traversable f, HShow phi g) => HShow phi ((:.:) f g) Source # 

Methods

hShowsPrecAlg :: Algebra' phi (f :.: g) [Int -> ShowS] Source #

ConNames ((:.:) f g) Source # 

Methods

hconNames :: (f :.: g) r ix -> [String] Source #

Functor f => Fold ((:.:) f (I xi)) Source # 

Methods

alg :: Alg (f :.: I xi) r ix -> (f :.: I xi) r ix -> r ix Source #

type Comp ((:.:) f g) r ix Source # 
type Comp ((:.:) f g) r ix = f (Comp g r ix)
type Alg ((:.:) f (I xi)) r ix Source # 
type Alg ((:.:) f (I xi)) r ix = f (r xi) -> r ix

data C c f r ix where Source #

Represents constructors.

Constructors

C :: f r ix -> C c f r ix 

Instances

(Constructor c, HEq phi f) => HEq phi (C c f) Source # 

Methods

heq :: (forall ix. phi ix -> r ix -> r ix -> Bool) -> phi ix -> C c f r ix -> C c f r ix -> Bool Source #

(Constructor c, HFunctor phi f) => HFunctor phi (C c f) Source # 

Methods

hmapA :: Applicative a => (forall ix. phi ix -> r ix -> a (r' ix)) -> phi ix -> C c f r ix -> a (C c f r' ix) Source #

(Constructor c, CountAtoms ((:*:) f g), HReadPrec phi f, HReadPrec phi g) => HReadPrec phi (C c ((:*:) f g)) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (C c (f :*: g) I0 ix) Source #

(Constructor c, HReadPrec phi ((:.:) f g)) => HReadPrec phi (C c ((:.:) f g)) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (C c (f :.: g) I0 ix) Source #

(Constructor c, HReadPrec phi (K a)) => HReadPrec phi (C c (K a)) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (C c (K a) I0 ix) Source #

(Constructor c, HReadPrec phi (I xi)) => HReadPrec phi (C c (I xi)) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (C c (I xi) I0 ix) Source #

Constructor c => HReadPrec phi (C c U) Source # 

Methods

hreader :: phi ix -> (forall ix1. phi ix1 -> ReadPrec (I0 ix1)) -> ReadPrec (C c U I0 ix) Source #

(Constructor c, HShow phi f) => HShow phi (C c f) Source # 

Methods

hShowsPrecAlg :: Algebra' phi (C c f) [Int -> ShowS] Source #

Constructor c => ConNames (C c f) Source # 

Methods

hconNames :: C c f r ix -> [String] Source #

Fold f => Fold (C c f) Source # 

Methods

alg :: Alg (C c f) r ix -> C c f r ix -> r ix Source #

Fold f => Fold (C c f) Source # 

Methods

alg :: Alg (C c f) r -> C c f (K0 r) ix -> r Source #

type Alg (C c f) r Source # 
type Alg (C c f) r = Alg f r
type Alg (C c f) r ix Source # 
type Alg (C c f) r ix = Alg f r ix

unC :: C c f r ix -> f r ix Source #

Destructor for C.

Constructor information

Unlifted variants

newtype I0 a Source #

Unlifted version of I.

Constructors

I0 

Fields

Instances

Functor I0 Source # 

Methods

fmap :: (a -> b) -> I0 a -> I0 b #

(<$) :: a -> I0 b -> I0 a #

Applicative I0 Source # 

Methods

pure :: a -> I0 a #

(<*>) :: I0 (a -> b) -> I0 a -> I0 b #

(*>) :: I0 a -> I0 b -> I0 b #

(<*) :: I0 a -> I0 b -> I0 a #

newtype K0 a b Source #

Unlifted version of K.

Constructors

K0 

Fields

Instances

Functor (K0 a) Source # 

Methods

fmap :: (a -> b) -> K0 a a -> K0 a b #

(<$) :: a -> K0 a b -> K0 a a #

Indexed families

type family PF (phi :: * -> *) :: (* -> *) -> * -> * Source #

Type family describing the pattern functor of a family.

class El phi ix where Source #

Class for the members of a family.

Minimal complete definition

proof

Methods

proof :: phi ix Source #

class Fam phi where Source #

Class that contains the shallow conversion functions for a family.

Minimal complete definition

from, to

Methods

from :: phi ix -> ix -> PF phi I0 ix Source #

to :: phi ix -> PF phi I0 ix -> ix Source #

index :: El phi ix => phi ix Source #

For backwards-compatibility: a synonym for proof.

Equality for indexed families

class EqS phi where Source #

Semi-decidable equality for types of a family.

Minimal complete definition

eqS

Methods

eqS :: phi ix -> phi ix' -> Maybe (ix :=: ix') Source #