generics-sop-0.5.1.0: Generic Programming using True Sums of Products

Safe HaskellNone
LanguageHaskell2010

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

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

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

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

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

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 # 
Instance details

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 # 
Instance details

Defined in Generics.SOP.Type.Metadata

Methods

demoteFieldInfos :: proxy [] -> NP FieldInfo0 [] Source #

(DemoteFieldInfo f x, DemoteFieldInfos fs xs) => DemoteFieldInfos (f ': fs) (x ': xs) Source # 
Instance details

Defined in Generics.SOP.Type.Metadata

Methods

demoteFieldInfos :: proxy (f ': fs) -> NP FieldInfo (x ': xs) Source #

class DemoteStrictnessInfos (ss :: [StrictnessInfo]) (xs :: [Type]) where Source #

Instances
DemoteStrictnessInfos ([] :: [StrictnessInfo]) ([] :: [Type]) Source # 
Instance details

Defined in Generics.SOP.Type.Metadata

(DemoteStrictnessInfo s x, DemoteStrictnessInfos ss xs) => DemoteStrictnessInfos (s ': ss) (x ': xs) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Generics.SOP.Type.Metadata

(KnownSymbol s, DemoteFieldInfos fs xs) => DemoteConstructorInfo (Record s fs) xs Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Generics.SOP.Type.Metadata

(DemoteConstructorInfo c xs, DemoteConstructorInfos cs xss) => DemoteConstructorInfos (c ': cs) (xs ': xss) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Generics.SOP.Type.Metadata

Methods

demoteDatatypeInfo :: proxy (ADT m d cs sss) -> DatatypeInfo xss Source #

type Fixity = Nat Source #

The fixity of an infix constructor.

type FieldName = Symbol Source #

The name of a field / record selector.

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.

data FieldInfo Source #

Metadata for a single record field (to be used promoted).

Since: 0.3.0.0

Constructors

FieldInfo FieldName 
Instances
DemoteFieldInfos ([] :: [FieldInfo]) ([] :: [Type]) Source # 
Instance details

Defined in Generics.SOP.Type.Metadata

Methods

demoteFieldInfos :: proxy [] -> NP FieldInfo0 [] Source #

(DemoteFieldInfo f x, DemoteFieldInfos fs xs) => DemoteFieldInfos (f ': fs) (x ': xs) Source # 
Instance details

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 # 
Instance details

Defined in Generics.SOP.Type.Metadata

DemoteStrictnessInfoss ([] :: [[StrictnessInfo]]) ([] :: [[Type]]) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Generics.SOP.Type.Metadata

(DemoteConstructorInfo c xs, DemoteConstructorInfos cs xss) => DemoteConstructorInfos (c ': cs) (xs ': xss) Source # 
Instance details

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 contains meta-information about a datatype that is not contained in its code. This information consists primarily of the names of the datatype, its constructors, and possibly its record selectors.

The constructor indicates whether the datatype has been declared using newtype or not.

Since: 0.3.0.0

re-exports

data Associativity #

Datatype to represent the associativity of a constructor

Instances
Bounded Associativity

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Enum Associativity

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Data Associativity

Since: base-4.9.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Associativity -> c Associativity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Associativity #

toConstr :: Associativity -> Constr #

dataTypeOf :: Associativity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Associativity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Associativity) #

gmapT :: (forall b. Data b => b -> b) -> Associativity -> Associativity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Associativity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Associativity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Associativity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Associativity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Associativity -> m Associativity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Associativity -> m Associativity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Associativity -> m Associativity #

Ord Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Read Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Ix Associativity

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type #

SingKind Associativity

Since: base-4.0.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Associativity :: Type

Methods

fromSing :: Sing a -> DemoteRep Associativity

HasDatatypeInfo Associativity Source # 
Instance details

Defined in Generics.SOP.Instances

Generic Associativity Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Associativity :: [[Type]] Source #

SingI LeftAssociative

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing LeftAssociative

SingI RightAssociative

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing RightAssociative

SingI NotAssociative

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing NotAssociative

type Rep Associativity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

type Rep Associativity = D1 (MetaData "Associativity" "GHC.Generics" "base" False) (C1 (MetaCons "LeftAssociative" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RightAssociative" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NotAssociative" PrefixI False) (U1 :: Type -> Type)))
data Sing (a :: Associativity) 
Instance details

Defined in GHC.Generics

data Sing (a :: Associativity) where
type DemoteRep Associativity 
Instance details

Defined in GHC.Generics

type DemoteRep Associativity = Associativity
type DatatypeInfoOf Associativity Source # 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf Associativity = ADT "GHC.Generics" "Associativity" (Constructor "LeftAssociative" ': (Constructor "RightAssociative" ': (Constructor "NotAssociative" ': ([] :: [ConstructorInfo])))) (([] :: [StrictnessInfo]) ': (([] :: [StrictnessInfo]) ': (([] :: [StrictnessInfo]) ': ([] :: [[StrictnessInfo]]))))
type Code Associativity Source # 
Instance details

Defined in Generics.SOP.Instances

type Code Associativity = ([] :: [Type]) ': (([] :: [Type]) ': (([] :: [Type]) ': ([] :: [[Type]])))