generics-mrsop-1.0.0.1: Generic Programming with Mutually Recursive Sums of Products.

Safe HaskellSafe
LanguageHaskell2010

Generics.MRSOP.Base.Metadata

Contents

Description

Metadata maintenance; usefull for pretty-printing values.

Synopsis

Documentation

data DatatypeName Source #

Since we only handled fully saturated datatypes, a DatatypeName needs to remember what were the arguments applied to a type.

The type [Int] is represented by Name "[]" :: Name Int

Constructors

Name String 
DatatypeName :@: DatatypeName infixl 5 

data DatatypeInfo :: [[Atom kon]] -> * where Source #

Provides information about the declaration of a datatype.

Instances

Show (DatatypeInfo kon code) Source # 

Methods

showsPrec :: Int -> DatatypeInfo kon code -> ShowS #

show :: DatatypeInfo kon code -> String #

showList :: [DatatypeInfo kon code] -> ShowS #

type Fixity = Int Source #

Fixity information for infix constructors.

data ConstructorInfo :: [Atom kon] -> * where Source #

Constructor metadata.

Instances

Show (ConstructorInfo kon code) Source # 

Methods

showsPrec :: Int -> ConstructorInfo kon code -> ShowS #

show :: ConstructorInfo kon code -> String #

showList :: [ConstructorInfo kon code] -> ShowS #

Show (NP [Atom kon] (ConstructorInfo kon) code) Source # 

Methods

showsPrec :: Int -> NP [Atom kon] (ConstructorInfo kon) code -> ShowS #

show :: NP [Atom kon] (ConstructorInfo kon) code -> String #

showList :: [NP [Atom kon] (ConstructorInfo kon) code] -> ShowS #

data FieldInfo :: Atom kon -> * where Source #

Record fields metadata

Constructors

FieldInfo :: {..} -> FieldInfo k 

Fields

Instances

Show (FieldInfo kon atom) Source # 

Methods

showsPrec :: Int -> FieldInfo kon atom -> ShowS #

show :: FieldInfo kon atom -> String #

showList :: [FieldInfo kon atom] -> ShowS #

Show (NP (Atom kon) (FieldInfo kon) code) Source # 

Methods

showsPrec :: Int -> NP (Atom kon) (FieldInfo kon) code -> ShowS #

show :: NP (Atom kon) (FieldInfo kon) code -> String #

showList :: [NP (Atom kon) (FieldInfo kon) code] -> ShowS #

class Family ki fam codes => HasDatatypeInfo ki fam codes ix | fam -> codes ki where Source #

Given a Family, provides the DatatypeInfo for the type with index ix in family fam.

Minimal complete definition

datatypeInfo

Methods

datatypeInfo :: IsNat ix => Proxy fam -> Proxy ix -> DatatypeInfo (Lkup ix codes) Source #

Instances

datatypeInfoFor :: forall ki fam codes ix ty. (HasDatatypeInfo ki fam codes ix, ix ~ Idx ty fam, Lkup ix fam ~ ty, IsNat ix) => Proxy fam -> Proxy ty -> DatatypeInfo (Lkup ix codes) Source #

Sometimes it is more convenient to use a proxy of the type in the family instead of indexes.

Name Lookup

constrInfoLkup :: Constr sum c -> DatatypeInfo sum -> ConstructorInfo (Lkup c sum) Source #

This is essentially a list lookup, but needs significant type information to go through. Returns the name of the cth constructor of a sum-type.