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

Safe HaskellNone
LanguageHaskell2010

Generics.SOP.Metadata

Contents

Description

Metadata about what a datatype looks like

In generics-sop, the metadata is completely independent of the main universe. Many generic functions will use this metadata, but other don't, and yet others might need completely different metadata.

This module defines a datatype to represent standard metadata, i.e., names of the datatype, its constructors, and possibly its record selectors. Metadata descriptions are in general GADTs indexed by the code of the datatype they're associated with, so matching on the metadata will reveal information about the shape of the datatype.

Synopsis

Documentation

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

Metadata for a datatype.

A value of type DatatypeInfo c contains the information about a datatype that is not contained in Code c. 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.

moduleName :: DatatypeInfo xss -> ModuleName Source #

The module name where a datatype is defined.

Since: 0.2.3.0

datatypeName :: DatatypeInfo xss -> DatatypeName Source #

The name of a datatype (or newtype).

Since: 0.2.3.0

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

The constructor info for a datatype (or newtype).

Since: 0.2.3.0

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

Metadata for a single constructors.

This is indexed by the product structure of the constructor components.

constructorName :: ConstructorInfo xs -> ConstructorName Source #

The name of a constructor.

Since: 0.2.3.0

data FieldInfo :: * -> * where Source #

For records, this functor maps the component to its selector name.

Constructors

FieldInfo :: FieldName -> FieldInfo a 

Instances

Functor FieldInfo Source # 

Methods

fmap :: (a -> b) -> FieldInfo a -> FieldInfo b #

(<$) :: a -> FieldInfo b -> FieldInfo a #

Eq (FieldInfo a) Source # 

Methods

(==) :: FieldInfo a -> FieldInfo a -> Bool #

(/=) :: FieldInfo a -> FieldInfo a -> Bool #

Ord (FieldInfo a) Source # 
Show (FieldInfo a) Source # 

fieldName :: FieldInfo a -> FieldName Source #

The name of a field.

Since: 0.2.3.0

type DatatypeName = String Source #

The name of a datatype.

type ModuleName = String Source #

The name of a module.

type ConstructorName = String Source #

The name of a data constructor.

type FieldName = String Source #

The name of a field / record selector.

type Fixity = Int Source #

The fixity of an infix constructor.

re-exports

data Associativity :: * #

Datatype to represent the associativity of a constructor

Instances

Bounded Associativity 
Enum Associativity 
Eq Associativity 
Data Associativity 

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 
Read Associativity 
Show Associativity 
Ix Associativity 
Generic Associativity 

Associated Types

type Rep Associativity :: * -> * #

SingI Associativity LeftAssociative 

Methods

sing :: Sing LeftAssociative a

SingI Associativity RightAssociative 

Methods

sing :: Sing RightAssociative a

SingI Associativity NotAssociative 

Methods

sing :: Sing NotAssociative a

SingKind Associativity (KProxy Associativity) 

Associated Types

type DemoteRep (KProxy Associativity) (kparam :: KProxy (KProxy Associativity)) :: *

Methods

fromSing :: Sing (KProxy Associativity) a -> DemoteRep (KProxy Associativity) kparam

type Rep Associativity 
type Rep Associativity = D1 (MetaData "Associativity" "GHC.Generics" "base" False) ((:+:) (C1 (MetaCons "LeftAssociative" PrefixI False) U1) ((:+:) (C1 (MetaCons "RightAssociative" PrefixI False) U1) (C1 (MetaCons "NotAssociative" PrefixI False) U1)))
data Sing Associativity 
type DemoteRep Associativity (KProxy Associativity)