Safe Haskell | None |
---|---|
Language | Haskell2010 |
Metadata maintenance; usefull for pretty-printing values.
Synopsis
- type ModuleName = String
- type FamilyName = String
- type ConstructorName = String
- type FieldName = String
- data DatatypeName
- data DatatypeInfo :: [[Atom kon]] -> * where
- ADT :: ModuleName -> DatatypeName -> NP ConstructorInfo c -> DatatypeInfo c
- New :: ModuleName -> DatatypeName -> ConstructorInfo '[c] -> DatatypeInfo '['[c]]
- moduleName :: DatatypeInfo code -> ModuleName
- datatypeName :: DatatypeInfo code -> DatatypeName
- constructorInfo :: DatatypeInfo code -> NP ConstructorInfo code
- data Associativity
- type Fixity = Int
- data ConstructorInfo :: [Atom kon] -> * where
- Constructor :: ConstructorName -> ConstructorInfo xs
- Infix :: ConstructorName -> Associativity -> Fixity -> ConstructorInfo '[x, y]
- Record :: ConstructorName -> NP FieldInfo xs -> ConstructorInfo xs
- constructorName :: ConstructorInfo con -> ConstructorName
- data FieldInfo :: Atom kon -> * where
- class Family ki fam codes => HasDatatypeInfo ki fam codes | fam -> codes ki where
- datatypeInfo :: Proxy fam -> SNat ix -> DatatypeInfo (Lkup ix codes)
- 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)
- constrInfoLkup :: Constr sum c -> DatatypeInfo sum -> ConstructorInfo (Lkup c sum)
- constrInfoFor :: HasDatatypeInfo ki fam codes => Proxy fam -> SNat ix -> Constr (Lkup ix codes) c -> ConstructorInfo (Lkup c (Lkup ix codes))
Documentation
type ModuleName = String Source #
type FamilyName = String Source #
type ConstructorName = String Source #
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
Name String | |
DatatypeName :@: DatatypeName infixl 5 |
Instances
Eq DatatypeName Source # | |
Defined in Generics.MRSOP.Base.Metadata (==) :: DatatypeName -> DatatypeName -> Bool # (/=) :: DatatypeName -> DatatypeName -> Bool # | |
Show DatatypeName Source # | |
Defined in Generics.MRSOP.Base.Metadata showsPrec :: Int -> DatatypeName -> ShowS # show :: DatatypeName -> String # showList :: [DatatypeName] -> ShowS # |
data DatatypeInfo :: [[Atom kon]] -> * where Source #
Provides information about the declaration of a datatype.
ADT :: ModuleName -> DatatypeName -> NP ConstructorInfo c -> DatatypeInfo c | |
New :: ModuleName -> DatatypeName -> ConstructorInfo '[c] -> DatatypeInfo '['[c]] |
Instances
All (Compose Show (ConstructorInfo :: [Atom kon] -> Type)) code => Show (DatatypeInfo code) Source # | |
Defined in Generics.MRSOP.Base.Metadata 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.
Instances
Eq Associativity Source # | |
Defined in Generics.MRSOP.Base.Metadata (==) :: Associativity -> Associativity -> Bool # (/=) :: Associativity -> Associativity -> Bool # | |
Show Associativity Source # | |
Defined in Generics.MRSOP.Base.Metadata showsPrec :: Int -> Associativity -> ShowS # show :: Associativity -> String # showList :: [Associativity] -> ShowS # |
data ConstructorInfo :: [Atom kon] -> * where Source #
Constructor metadata.
Constructor :: ConstructorName -> ConstructorInfo xs | |
Infix :: ConstructorName -> Associativity -> Fixity -> ConstructorInfo '[x, y] | |
Record :: ConstructorName -> NP FieldInfo xs -> ConstructorInfo xs |
Instances
All (Compose Show (FieldInfo :: Atom kon -> Type)) code => Show (ConstructorInfo code) Source # | |
Defined in Generics.MRSOP.Base.Metadata showsPrec :: Int -> ConstructorInfo code -> ShowS # show :: ConstructorInfo code -> String # showList :: [ConstructorInfo code] -> ShowS # |
constructorName :: ConstructorInfo con -> ConstructorName Source #
Returns the name of a constructor
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
.
datatypeInfo :: Proxy fam -> SNat ix -> DatatypeInfo (Lkup ix codes) Source #
Instances
HasDatatypeInfo Singl FamRose CodesRose Source # | |
Defined in Generics.MRSOP.Examples.RoseTree datatypeInfo :: Proxy FamRose -> SNat ix -> DatatypeInfo (Lkup ix CodesRose) 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 c
th 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.