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

Safe HaskellNone
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
All (Compose Show (ConstructorInfo :: [Atom kon] -> Type)) code => Show (DatatypeInfo code) Source # 
Instance details

Defined in Generics.MRSOP.Base.Metadata

Methods

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

show :: DatatypeInfo code -> String #

showList :: [DatatypeInfo code] -> ShowS #

moduleName :: DatatypeInfo code -> ModuleName Source #

Returns the name of a module

datatypeName :: DatatypeInfo code -> DatatypeName Source #

Returns the name of a datatype

constructorInfo :: DatatypeInfo code -> NP ConstructorInfo code Source #

Returns information about the constructor fields

data Associativity Source #

Associativity information for infix constructors.

type Fixity = Int Source #

Fixity information for infix constructors.

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

Constructor metadata.

Instances
All (Compose Show (FieldInfo :: Atom kon -> Type)) code => Show (ConstructorInfo code) Source # 
Instance details

Defined in Generics.MRSOP.Base.Metadata

constructorName :: ConstructorInfo con -> ConstructorName Source #

Returns the name of a constructor

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

Record fields metadata

Constructors

FieldInfo 

Fields

Instances
Show (FieldInfo atom) Source # 
Instance details

Defined in Generics.MRSOP.Base.Metadata

Methods

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

show :: FieldInfo atom -> String #

showList :: [FieldInfo atom] -> ShowS #

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

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

Methods

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

datatypeInfoFor :: forall ki fam codes ix ty. (HasDatatypeInfo ki fam codes, 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.

constrInfoFor :: HasDatatypeInfo ki fam codes => Proxy fam -> SNat ix -> Constr (Lkup ix codes) c -> ConstructorInfo (Lkup c (Lkup ix codes)) Source #

Returns the constructor information for a given type in the family.