generic-data-0.1.0.0: Utilities for GHC.Generics

Safe HaskellSafe
LanguageHaskell2010

Generic.Data.Internal.Meta

Description

Type metadata accessors

Type names, constructor names...

Synopsis

Documentation

gdatatypeName :: forall a. (Generic a, GDatatype (Rep a)) => String Source #

Name of the first data constructor in a type as a string.

gdatatypeName @(Maybe AnyType) = "Maybe"

gmoduleName :: forall a. (Generic a, GDatatype (Rep a)) => String Source #

Name of the module where the first type constructor is defined.

gmoduleName @(Maybe AnyType) = "GHC.Base"

gpackageName :: forall a. (Generic a, GDatatype (Rep a)) => String Source #

Name of the package where the first type constructor is defined.

gpackageName @(Maybe AnyType) = "base"

gisNewtype :: forall a. (Generic a, GDatatype (Rep a)) => Bool Source #

True if the first type constructor is a newtype.

fromDatatype :: forall d r. Datatype d => (M1 D d Proxy () -> r) -> r Source #

class GDatatype f where Source #

Generic representations that contain datatype metadata.

Minimal complete definition

gDatatypeName, gModuleName, gPackageName, gIsNewtype

gconName :: forall a. Constructors a => a -> String Source #

Name of the first constructor in a value.

gconName (Just 0) = "Just"

gconFixity :: forall a. Constructors a => a -> Fixity Source #

The fixity of the first constructor.

gconFixity (Just 0) = Prefix
gconFixity ([] :*: id) = Infix RightAssociative 6

gconIsRecord :: forall a. Constructors a => a -> Bool Source #

True if the constructor is a record.

gconIsRecord (Just 0) = False
gconIsRecord (Sum 0) = True
-- newtype Sum a = Sum { getSum :: a }

gconNum :: forall a. Constructors a => Int Source #

Number of constructors.

gconNum @(Maybe AnyType) = 2

newtype ConId a Source #

An opaque identifier for a constructor.

Constructors

ConId Int 

Instances

Eq (ConId k a) Source # 

Methods

(==) :: ConId k a -> ConId k a -> Bool #

(/=) :: ConId k a -> ConId k a -> Bool #

Ord (ConId k a) Source # 

Methods

compare :: ConId k a -> ConId k a -> Ordering #

(<) :: ConId k a -> ConId k a -> Bool #

(<=) :: ConId k a -> ConId k a -> Bool #

(>) :: ConId k a -> ConId k a -> Bool #

(>=) :: ConId k a -> ConId k a -> Bool #

max :: ConId k a -> ConId k a -> ConId k a #

min :: ConId k a -> ConId k a -> ConId k a #

conIdToInt :: forall a. ConId a -> Int Source #

conIdEnum :: forall a. Constructors a => [ConId a] Source #

conId :: forall a. Constructors a => a -> ConId a Source #

conIdMax :: forall a. Constructors a => ConId a Source #

class (Generic a, GConstructors (Rep a)) => Constructors a Source #

Constraint synonym for Generic and GConstructor.

Instances

newtype GConId r Source #

Constructors

GConId Int 

Instances

Eq (GConId k r) Source # 

Methods

(==) :: GConId k r -> GConId k r -> Bool #

(/=) :: GConId k r -> GConId k r -> Bool #

Ord (GConId k r) Source # 

Methods

compare :: GConId k r -> GConId k r -> Ordering #

(<) :: GConId k r -> GConId k r -> Bool #

(<=) :: GConId k r -> GConId k r -> Bool #

(>) :: GConId k r -> GConId k r -> Bool #

(>=) :: GConId k r -> GConId k r -> Bool #

max :: GConId k r -> GConId k r -> GConId k r #

min :: GConId k r -> GConId k r -> GConId k r #

toConId :: forall a. Generic a => GConId (Rep a) -> ConId a Source #

fromConId :: forall a. Generic a => ConId a -> GConId (Rep a) Source #

gConIdMax :: forall r. GConstructors r => GConId r Source #

class GConstructors r where Source #

Generic representations that contain constructor metadata.

Minimal complete definition

gConIdToString, gConId, gConNum, gConFixity, gConIsRecord

Instances

(GConstructors k f, GConstructors k g) => GConstructors k ((:+:) k f g) Source # 

Methods

gConIdToString :: GConId ((k :+: f) g -> *) r -> String Source #

gConId :: r p -> GConId ((k :+: f) g -> *) r Source #

gConNum :: Int Source #

gConFixity :: r p -> Fixity Source #

gConIsRecord :: r p -> Bool Source #

Constructor Meta c => GConstructors k (M1 k C c f) Source # 

Methods

gConIdToString :: GConId (M1 k C c f -> *) r -> String Source #

gConId :: r p -> GConId (M1 k C c f -> *) r Source #

gConNum :: Int Source #

gConFixity :: r p -> Fixity Source #

gConIsRecord :: r p -> Bool Source #

GConstructors k f => GConstructors k (M1 k D c f) Source # 

Methods

gConIdToString :: GConId (M1 k D c f -> *) r -> String Source #

gConId :: r p -> GConId (M1 k D c f -> *) r Source #

gConNum :: Int Source #

gConFixity :: r p -> Fixity Source #

gConIsRecord :: r p -> Bool Source #