generics-sop-0.5.0.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

type Fixity = Int Source #

The fixity of an infix constructor.

type FieldName = String Source #

The name of a field / record selector.

type ConstructorName = String Source #

The name of a data constructor.

type ModuleName = String Source #

The name of a module.

type DatatypeName = String Source #

The name of a datatype.

data FieldInfo :: Type -> Type where Source #

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

Constructors

FieldInfo :: FieldName -> FieldInfo a 
Instances
Functor FieldInfo Source # 
Instance details

Defined in Generics.SOP.Metadata

Methods

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

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

Eq (FieldInfo a) Source # 
Instance details

Defined in Generics.SOP.Metadata

Methods

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

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

Ord (FieldInfo a) Source # 
Instance details

Defined in Generics.SOP.Metadata

Show (FieldInfo a) Source # 
Instance details

Defined in Generics.SOP.Metadata

data StrictnessInfo :: Type -> Type where Source #

Metadata for strictness information of a field.

Indexed by the type of the field.

Since: 0.4.0.0

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

Metadata for a single constructor.

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

data DatatypeInfo :: [[Type]] -> Type 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

constructorName :: ConstructorInfo xs -> ConstructorName Source #

The name of a constructor.

Since: 0.2.3.0

fieldName :: FieldInfo a -> FieldName Source #

The name of a field.

Since: 0.2.3.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]])))

data DecidedStrictness #

The strictness that GHC infers for a field during compilation. Whereas there are nine different combinations of SourceUnpackedness and SourceStrictness, the strictness that GHC decides will ultimately be one of lazy, strict, or unpacked. What GHC decides is affected both by what the user writes in the source code and by GHC flags. As an example, consider this data type:

data E = ExampleConstructor {-# UNPACK #-} !Int !Int Int

Since: base-4.9.0.0

Instances
Bounded DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Enum DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Data DecidedStrictness

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) -> DecidedStrictness -> c DecidedStrictness #

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

toConstr :: DecidedStrictness -> Constr #

dataTypeOf :: DecidedStrictness -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Read DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ix DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type #

SingKind DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep DecidedStrictness :: Type

Methods

fromSing :: Sing a -> DemoteRep DecidedStrictness

HasDatatypeInfo DecidedStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

Generic DecidedStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

SingI DecidedLazy

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing DecidedLazy

SingI DecidedStrict

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing DecidedStrict

SingI DecidedUnpack

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing DecidedUnpack

type Rep DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep DecidedStrictness = D1 (MetaData "DecidedStrictness" "GHC.Generics" "base" False) (C1 (MetaCons "DecidedLazy" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DecidedStrict" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DecidedUnpack" PrefixI False) (U1 :: Type -> Type)))
data Sing (a :: DecidedStrictness) 
Instance details

Defined in GHC.Generics

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

Defined in GHC.Generics

type DatatypeInfoOf DecidedStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf DecidedStrictness = ADT "GHC.Generics" "DecidedStrictness" (Constructor "DecidedLazy" ': (Constructor "DecidedStrict" ': (Constructor "DecidedUnpack" ': ([] :: [ConstructorInfo])))) (([] :: [StrictnessInfo]) ': (([] :: [StrictnessInfo]) ': (([] :: [StrictnessInfo]) ': ([] :: [[StrictnessInfo]]))))
type Code DecidedStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

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

data SourceStrictness #

The strictness of a field as the user wrote it in the source code. For example, in the following data type:

data E = ExampleConstructor Int ~Int !Int

The fields of ExampleConstructor have NoSourceStrictness, SourceLazy, and SourceStrict, respectively.

Since: base-4.9.0.0

Instances
Bounded SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Enum SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Data SourceStrictness

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) -> SourceStrictness -> c SourceStrictness #

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

toConstr :: SourceStrictness -> Constr #

dataTypeOf :: SourceStrictness -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Read SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ix SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type #

SingKind SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep SourceStrictness :: Type

Methods

fromSing :: Sing a -> DemoteRep SourceStrictness

HasDatatypeInfo SourceStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

Generic SourceStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

SingI SourceLazy

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing SourceLazy

SingI SourceStrict

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing SourceStrict

SingI NoSourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing NoSourceStrictness

type Rep SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep SourceStrictness = D1 (MetaData "SourceStrictness" "GHC.Generics" "base" False) (C1 (MetaCons "NoSourceStrictness" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SourceLazy" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SourceStrict" PrefixI False) (U1 :: Type -> Type)))
data Sing (a :: SourceStrictness) 
Instance details

Defined in GHC.Generics

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

Defined in GHC.Generics

type DatatypeInfoOf SourceStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf SourceStrictness = ADT "GHC.Generics" "SourceStrictness" (Constructor "NoSourceStrictness" ': (Constructor "SourceLazy" ': (Constructor "SourceStrict" ': ([] :: [ConstructorInfo])))) (([] :: [StrictnessInfo]) ': (([] :: [StrictnessInfo]) ': (([] :: [StrictnessInfo]) ': ([] :: [[StrictnessInfo]]))))
type Code SourceStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

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

data SourceUnpackedness #

The unpackedness of a field as the user wrote it in the source code. For example, in the following data type:

data E = ExampleConstructor     Int
           {-# NOUNPACK #-} Int
           {-#   UNPACK #-} Int

The fields of ExampleConstructor have NoSourceUnpackedness, SourceNoUnpack, and SourceUnpack, respectively.

Since: base-4.9.0.0

Instances
Bounded SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Enum SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Data SourceUnpackedness

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) -> SourceUnpackedness -> c SourceUnpackedness #

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

toConstr :: SourceUnpackedness -> Constr #

dataTypeOf :: SourceUnpackedness -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Read SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ix SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

SingKind SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep SourceUnpackedness :: Type

Methods

fromSing :: Sing a -> DemoteRep SourceUnpackedness

HasDatatypeInfo SourceUnpackedness Source # 
Instance details

Defined in Generics.SOP.Instances

Generic SourceUnpackedness Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

SingI SourceUnpack

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing SourceUnpack

SingI SourceNoUnpack

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing SourceNoUnpack

SingI NoSourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing NoSourceUnpackedness

type Rep SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep SourceUnpackedness = D1 (MetaData "SourceUnpackedness" "GHC.Generics" "base" False) (C1 (MetaCons "NoSourceUnpackedness" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SourceNoUnpack" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SourceUnpack" PrefixI False) (U1 :: Type -> Type)))
data Sing (a :: SourceUnpackedness) 
Instance details

Defined in GHC.Generics

type DemoteRep SourceUnpackedness 
Instance details

Defined in GHC.Generics

type DatatypeInfoOf SourceUnpackedness Source # 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf SourceUnpackedness = ADT "GHC.Generics" "SourceUnpackedness" (Constructor "NoSourceUnpackedness" ': (Constructor "SourceNoUnpack" ': (Constructor "SourceUnpack" ': ([] :: [ConstructorInfo])))) (([] :: [StrictnessInfo]) ': (([] :: [StrictnessInfo]) ': (([] :: [StrictnessInfo]) ': ([] :: [[StrictnessInfo]]))))
type Code SourceUnpackedness Source # 
Instance details

Defined in Generics.SOP.Instances

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