| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Generics.SOP.Type.Metadata
Contents
Description
Type-level metadata
This module provides datatypes (to be used promoted) that can represent the metadata of Haskell datatypes on the type level.
We do not reuse the term-level metadata types, because these are GADTs that incorporate additional invariants. We could (at least in GHC 8) impose the same invariants on the type level as well, but some tests have revealed that the resulting type are rather inconvenient to work with.
So we use simple datatypes to represent the type-level metadata, even if this means that some invariants are not explicitly captured.
We establish a relation between the term- and type-level versions of the metadata by automatically computing the term-level version from the type-level version.
As we now have two versions of metadata (term-level and type-level) with very similar, yet slightly different datatype definitions, the names between the modules clash, and this module is recommended to be imported qualified when needed.
The interface exported by this module is still somewhat experimental.
Since: 0.3.0.0
Synopsis
- class DemoteDecidedStrictness (a :: DecidedStrictness) where- demoteDecidedStrictness :: proxy a -> DecidedStrictness
 
- class DemoteSourceStrictness (a :: SourceStrictness) where- demoteSourceStrictness :: proxy a -> SourceStrictness
 
- class DemoteSourceUnpackedness (a :: SourceUnpackedness) where- demoteSourceUnpackedness :: proxy a -> SourceUnpackedness
 
- class DemoteAssociativity (a :: Associativity) where- demoteAssociativity :: proxy a -> Associativity
 
- class DemoteFieldInfo (x :: FieldInfo) (a :: Type) where- demoteFieldInfo :: proxy x -> FieldInfo a
 
- class SListI xs => DemoteFieldInfos (fs :: [FieldInfo]) (xs :: [Type]) where- demoteFieldInfos :: proxy fs -> NP FieldInfo xs
 
- class DemoteStrictnessInfo (s :: StrictnessInfo) (x :: Type) where- demoteStrictnessInfo :: proxy s -> StrictnessInfo x
 
- class DemoteStrictnessInfos (ss :: [StrictnessInfo]) (xs :: [Type]) where- demoteStrictnessInfos :: proxy ss -> NP StrictnessInfo xs
 
- class DemoteStrictnessInfoss (sss :: [[StrictnessInfo]]) (xss :: [[Type]]) where- demoteStrictnessInfoss :: proxy sss -> NP (NP StrictnessInfo) xss
 
- class DemoteConstructorInfo (x :: ConstructorInfo) (xs :: [Type]) where- demoteConstructorInfo :: proxy x -> ConstructorInfo xs
 
- class DemoteConstructorInfos (cs :: [ConstructorInfo]) (xss :: [[Type]]) where- demoteConstructorInfos :: proxy cs -> NP ConstructorInfo xss
 
- class DemoteDatatypeInfo (x :: DatatypeInfo) (xss :: [[Type]]) where- demoteDatatypeInfo :: proxy x -> DatatypeInfo xss
 
- type Fixity = Nat
- type FieldName = Symbol
- type ConstructorName = Symbol
- type ModuleName = Symbol
- type DatatypeName = Symbol
- data FieldInfo = FieldInfo FieldName
- data StrictnessInfo = StrictnessInfo SourceUnpackedness SourceStrictness DecidedStrictness
- data ConstructorInfo
- data DatatypeInfo
- data Associativity
Documentation
class DemoteDecidedStrictness (a :: DecidedStrictness) where Source #
Class for computing term-level decided strictness information from type-level decided strictness information.
Since: 0.4.0.0
Methods
demoteDecidedStrictness :: proxy a -> DecidedStrictness Source #
Given a proxy of some type-level source strictness information, return the corresponding term-level information.
Since: 0.4.0.0
Instances
| DemoteDecidedStrictness DecidedLazy Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteDecidedStrictness :: proxy DecidedLazy -> DecidedStrictness Source # | |
| DemoteDecidedStrictness DecidedStrict Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteDecidedStrictness :: proxy DecidedStrict -> DecidedStrictness Source # | |
| DemoteDecidedStrictness DecidedUnpack Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteDecidedStrictness :: proxy DecidedUnpack -> DecidedStrictness Source # | |
class DemoteSourceStrictness (a :: SourceStrictness) where Source #
Class for computing term-level source strictness information from type-level source strictness information.
Since: 0.4.0.0
Methods
demoteSourceStrictness :: proxy a -> SourceStrictness Source #
Given a proxy of some type-level source strictness information, return the corresponding term-level information.
Since: 0.4.0.0
Instances
| DemoteSourceStrictness SourceLazy Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteSourceStrictness :: proxy SourceLazy -> SourceStrictness Source # | |
| DemoteSourceStrictness SourceStrict Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteSourceStrictness :: proxy SourceStrict -> SourceStrictness Source # | |
| DemoteSourceStrictness NoSourceStrictness Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteSourceStrictness :: proxy NoSourceStrictness -> SourceStrictness Source # | |
class DemoteSourceUnpackedness (a :: SourceUnpackedness) where Source #
Class for computing term-level source unpackedness information from type-level source unpackedness information.
Since: 0.4.0.0
Methods
demoteSourceUnpackedness :: proxy a -> SourceUnpackedness Source #
Given a proxy of some type-level source unpackedness information, return the corresponding term-level information.
Since: 0.4.0.0
Instances
| DemoteSourceUnpackedness SourceUnpack Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteSourceUnpackedness :: proxy SourceUnpack -> SourceUnpackedness Source # | |
| DemoteSourceUnpackedness SourceNoUnpack Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteSourceUnpackedness :: proxy SourceNoUnpack -> SourceUnpackedness Source # | |
| DemoteSourceUnpackedness NoSourceUnpackedness Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteSourceUnpackedness :: proxy NoSourceUnpackedness -> SourceUnpackedness Source # | |
class DemoteAssociativity (a :: Associativity) where Source #
Class for computing term-level associativity information from type-level associativity information.
Since: 0.3.0.0
Methods
demoteAssociativity :: proxy a -> Associativity Source #
Given a proxy of some type-level associativity information, return the corresponding term-level information.
Since: 0.3.0.0
Instances
| DemoteAssociativity LeftAssociative Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteAssociativity :: proxy LeftAssociative -> Associativity Source # | |
| DemoteAssociativity RightAssociative Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteAssociativity :: proxy RightAssociative -> Associativity Source # | |
| DemoteAssociativity NotAssociative Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteAssociativity :: proxy NotAssociative -> Associativity Source # | |
class DemoteFieldInfo (x :: FieldInfo) (a :: Type) where Source #
Class for computing term-level field information from type-level field information.
Since: 0.3.0.0
Methods
demoteFieldInfo :: proxy x -> FieldInfo a Source #
Given a proxy of some type-level field information, return the corresponding term-level information.
Since: 0.3.0.0
Instances
| KnownSymbol s => DemoteFieldInfo (FieldInfo s) a Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteFieldInfo :: proxy (FieldInfo s) -> FieldInfo0 a Source # | |
class SListI xs => DemoteFieldInfos (fs :: [FieldInfo]) (xs :: [Type]) where Source #
Class for computing term-level field information from type-level field information.
Since: 0.3.0.0
Methods
demoteFieldInfos :: proxy fs -> NP FieldInfo xs Source #
Given a proxy of some type-level field information, return the corresponding term-level information as a product.
Since: 0.3.0.0
Instances
| DemoteFieldInfos ([] :: [FieldInfo]) ([] :: [Type]) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteFieldInfos :: proxy [] -> NP FieldInfo0 [] Source # | |
| (DemoteFieldInfo f x, DemoteFieldInfos fs xs) => DemoteFieldInfos (f ': fs) (x ': xs) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteFieldInfos :: proxy (f ': fs) -> NP FieldInfo (x ': xs) Source # | |
class DemoteStrictnessInfo (s :: StrictnessInfo) (x :: Type) where Source #
Methods
demoteStrictnessInfo :: proxy s -> StrictnessInfo x Source #
Instances
| (DemoteSourceUnpackedness su, DemoteSourceStrictness ss, DemoteDecidedStrictness ds) => DemoteStrictnessInfo (StrictnessInfo su ss ds) x Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteStrictnessInfo :: proxy (StrictnessInfo su ss ds) -> StrictnessInfo0 x Source # | |
class DemoteStrictnessInfos (ss :: [StrictnessInfo]) (xs :: [Type]) where Source #
Methods
demoteStrictnessInfos :: proxy ss -> NP StrictnessInfo xs Source #
Instances
| DemoteStrictnessInfos ([] :: [StrictnessInfo]) ([] :: [Type]) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteStrictnessInfos :: proxy [] -> NP StrictnessInfo0 [] Source # | |
| (DemoteStrictnessInfo s x, DemoteStrictnessInfos ss xs) => DemoteStrictnessInfos (s ': ss) (x ': xs) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteStrictnessInfos :: proxy (s ': ss) -> NP StrictnessInfo (x ': xs) Source # | |
class DemoteStrictnessInfoss (sss :: [[StrictnessInfo]]) (xss :: [[Type]]) where Source #
Methods
demoteStrictnessInfoss :: proxy sss -> NP (NP StrictnessInfo) xss Source #
Instances
| DemoteStrictnessInfoss ([] :: [[StrictnessInfo]]) ([] :: [[Type]]) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteStrictnessInfoss :: proxy [] -> NP (NP StrictnessInfo0) [] Source # | |
| (DemoteStrictnessInfos ss xs, DemoteStrictnessInfoss sss xss) => DemoteStrictnessInfoss (ss ': sss) (xs ': xss) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteStrictnessInfoss :: proxy (ss ': sss) -> NP (NP StrictnessInfo) (xs ': xss) Source # | |
class DemoteConstructorInfo (x :: ConstructorInfo) (xs :: [Type]) where Source #
Class for computing term-level constructor information from type-level constructor information.
Since: 0.3.0.0
Methods
demoteConstructorInfo :: proxy x -> ConstructorInfo xs Source #
Given a proxy of some type-level constructor information, return the corresponding term-level information.
Since: 0.3.0.0
Instances
| (KnownSymbol s, SListI xs) => DemoteConstructorInfo (Constructor s) xs Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteConstructorInfo :: proxy (Constructor s) -> ConstructorInfo xs Source # | |
| (KnownSymbol s, DemoteFieldInfos fs xs) => DemoteConstructorInfo (Record s fs) xs Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteConstructorInfo :: proxy (Record s fs) -> ConstructorInfo xs Source # | |
| (KnownSymbol s, DemoteAssociativity a, KnownNat f) => DemoteConstructorInfo (Infix s a f) (y ': (z ': ([] :: [Type]))) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteConstructorInfo :: proxy (Infix s a f) -> ConstructorInfo (y ': (z ': [])) Source # | |
class DemoteConstructorInfos (cs :: [ConstructorInfo]) (xss :: [[Type]]) where Source #
Class for computing term-level constructor information from type-level constructor information.
Since: 0.3.0.0
Methods
demoteConstructorInfos :: proxy cs -> NP ConstructorInfo xss Source #
Given a proxy of some type-level constructor information, return the corresponding term-level information as a product.
Since: 0.3.0.0
Instances
| DemoteConstructorInfos ([] :: [ConstructorInfo]) ([] :: [[Type]]) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteConstructorInfos :: proxy [] -> NP ConstructorInfo0 [] Source # | |
| (DemoteConstructorInfo c xs, DemoteConstructorInfos cs xss) => DemoteConstructorInfos (c ': cs) (xs ': xss) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteConstructorInfos :: proxy (c ': cs) -> NP ConstructorInfo (xs ': xss) Source # | |
class DemoteDatatypeInfo (x :: DatatypeInfo) (xss :: [[Type]]) where Source #
Class for computing term-level datatype information from type-level datatype information.
Since: 0.3.0.0
Methods
demoteDatatypeInfo :: proxy x -> DatatypeInfo xss Source #
Given a proxy of some type-level datatype information, return the corresponding term-level information.
Since: 0.3.0.0
Instances
| (KnownSymbol m, KnownSymbol d, DemoteConstructorInfo c (x ': ([] :: [Type]))) => DemoteDatatypeInfo (Newtype m d c) ((x ': ([] :: [Type])) ': ([] :: [[Type]])) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteDatatypeInfo :: proxy (Newtype m d c) -> DatatypeInfo ((x ': []) ': []) Source # | |
| (KnownSymbol m, KnownSymbol d, DemoteConstructorInfos cs xss, DemoteStrictnessInfoss sss xss) => DemoteDatatypeInfo (ADT m d cs sss) xss Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteDatatypeInfo :: proxy (ADT m d cs sss) -> DatatypeInfo xss Source # | |
type ConstructorName = Symbol Source #
The name of a data constructor.
type ModuleName = Symbol Source #
The name of a module.
type DatatypeName = Symbol Source #
The name of a datatype.
Metadata for a single record field (to be used promoted).
Since: 0.3.0.0
Instances
| DemoteFieldInfos ([] :: [FieldInfo]) ([] :: [Type]) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteFieldInfos :: proxy [] -> NP FieldInfo0 [] Source # | |
| (DemoteFieldInfo f x, DemoteFieldInfos fs xs) => DemoteFieldInfos (f ': fs) (x ': xs) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteFieldInfos :: proxy (f ': fs) -> NP FieldInfo (x ': xs) Source # | |
data StrictnessInfo Source #
Strictness information for a single field (to be used promoted).
Since: 0.4.0.0
Instances
| DemoteStrictnessInfos ([] :: [StrictnessInfo]) ([] :: [Type]) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteStrictnessInfos :: proxy [] -> NP StrictnessInfo0 [] Source # | |
| DemoteStrictnessInfoss ([] :: [[StrictnessInfo]]) ([] :: [[Type]]) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteStrictnessInfoss :: proxy [] -> NP (NP StrictnessInfo0) [] Source # | |
| (DemoteStrictnessInfo s x, DemoteStrictnessInfos ss xs) => DemoteStrictnessInfos (s ': ss) (x ': xs) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteStrictnessInfos :: proxy (s ': ss) -> NP StrictnessInfo (x ': xs) Source # | |
| (DemoteStrictnessInfos ss xs, DemoteStrictnessInfoss sss xss) => DemoteStrictnessInfoss (ss ': sss) (xs ': xss) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteStrictnessInfoss :: proxy (ss ': sss) -> NP (NP StrictnessInfo) (xs ': xss) Source # | |
data ConstructorInfo Source #
Metadata for a single constructors (to be used promoted).
Since: 0.3.0.0
Constructors
| Constructor ConstructorName | Normal constructor | 
| Infix ConstructorName Associativity Fixity | Infix constructor | 
| Record ConstructorName [FieldInfo] | Record constructor | 
Instances
| DemoteConstructorInfos ([] :: [ConstructorInfo]) ([] :: [[Type]]) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteConstructorInfos :: proxy [] -> NP ConstructorInfo0 [] Source # | |
| (DemoteConstructorInfo c xs, DemoteConstructorInfos cs xss) => DemoteConstructorInfos (c ': cs) (xs ': xss) Source # | |
| Defined in Generics.SOP.Type.Metadata Methods demoteConstructorInfos :: proxy (c ': cs) -> NP ConstructorInfo (xs ': xss) Source # | |
data DatatypeInfo Source #
Metadata for a datatype (to be used promoted).
A type of kind DatatypeInfo
The constructor indicates whether the datatype has been declared using newtype
 or not.
Since: 0.3.0.0
Constructors
| ADT ModuleName DatatypeName [ConstructorInfo] [[StrictnessInfo]] | Standard algebraic datatype | 
| Newtype ModuleName DatatypeName ConstructorInfo | Newtype | 
re-exports
data Associativity #
Datatype to represent the associativity of a constructor
Constructors
| LeftAssociative | |
| RightAssociative | |
| NotAssociative |