generic-data-0.4.0.0: Utilities for GHC.Generics

Safe HaskellNone
LanguageHaskell2010

Generic.Data

Contents

Description

Generic combinators to derive type class instances.

base classes that GHC can not derive instances for, as of version 8.2:

On base < 4.12 (i.e., GHC < 8.6), import Generic.Data.Orphans to obtain instances needed internally to derive those.

GHC can derive instances for other classes here, although there may be types supported by one method but not the other or vice versa.

Synopsis

Regular classes

Semigroup

gmappend :: (Generic a, Semigroup (Rep a ())) => a -> a -> a Source #

Generic (<>) (or mappend).

instance Semigroup MyType where
  (<>) = gmappend

See also gmempty.

Monoid

gmempty :: (Generic a, Monoid (Rep a ())) => a Source #

Generic mempty.

instance Monoid MyType where
  mempty = gmempty

gmappend' :: (Generic a, Monoid (Rep a ())) => a -> a -> a Source #

Generic (<>) (or mappend).

The difference from gmappend is the Monoid constraint instead of Semigroup, for older versions of base where Semigroup is not a superclass of Monoid.

Eq

Can also be derived by GHC as part of the standard.

geq :: (Generic a, Eq (Rep a ())) => a -> a -> Bool Source #

Generic (==).

instance Eq MyType where
  (==) = geq

Ord

Can also be derived by GHC as part of the standard.

gcompare :: (Generic a, Ord (Rep a ())) => a -> a -> Ordering Source #

Generic compare.

instance Ord MyType where
  compare = gcompare

Show

Can also be derived by GHC as part of the standard.

gshowsPrec :: (Generic a, GShow0 (Rep a)) => Int -> a -> ShowS Source #

Generic showsPrec.

instance Show MyType where
  showsPrec = gshowsPrec

type GShow0 = GShow Proxy Source #

Generic representation of Show types.

Enum

class GEnum opts f Source #

Generic representation of Enum types.

The opts parameter is a type-level option to select different implementations.

Minimal complete definition

gCardinality, gFromEnum, gToEnum

Instances
GEnum opts (U1 :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

(GEnum opts f, GEnum opts g) => GEnum opts (f :+: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: (f :+: g) p -> Int Source #

gToEnum :: Int -> (f :+: g) p Source #

(Bounded c, Enum c) => GEnum FiniteEnum (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: K1 i c p -> Int Source #

gToEnum :: Int -> K1 i c p Source #

(GEnum FiniteEnum f, GEnum FiniteEnum g) => GEnum FiniteEnum (f :*: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: (f :*: g) p -> Int Source #

gToEnum :: Int -> (f :*: g) p Source #

GEnum opts f => GEnum opts (M1 i c f) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: M1 i c f p -> Int Source #

gToEnum :: Int -> M1 i c f p Source #

StandardEnum option

Can also be derived by GHC as part of the standard.

data StandardEnum Source #

Standard option for GEnum: derive Enum for types with only nullary constructors (the same restrictions as in the Haskell 2010 report).

gfromEnum :: (Generic a, GEnum StandardEnum (Rep a)) => a -> Int Source #

Generic fromEnum generated with the StandardEnum option.

See also gtoEnum.

genumFrom :: (Generic a, GEnum StandardEnum (Rep a)) => a -> [a] Source #

Generic enumFrom generated with the StandardEnum option.

See also gtoEnum.

genumFromThen :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> [a] Source #

Generic enumFromThen generated with the StandardEnum option.

See also gtoEnum.

genumFromTo :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> [a] Source #

Generic enumFromTo generated with the StandardEnum option.

See also gtoEnum.

genumFromThenTo :: (Generic a, GEnum StandardEnum (Rep a)) => a -> a -> a -> [a] Source #

Generic enumFromThenTo generated with the StandardEnum option.

See also gtoEnum.

FiniteEnum option

data FiniteEnum Source #

Extends the StandardEnum option for GEnum to allow all constructors to have arbitrary many fields. Each field type must be an instance of both Enum and Bounded. Two restrictions require the user's caution:

  • The Enum instances of the field types need to start enumerating from 0. Particularly Int is an unfit field type, because the enumeration of the negative values starts before 0.
  • There can only be up to maxBound values (because the implementation represents the cardinality explicitly as an Int). This restriction makes Word an invalid field type. Notably, it is insufficient for each individual field types to stay below this limit. Instead it applies to the generic type as a whole.

The resulting GEnum instance starts enumerating from 0 up to (cardinality - 1) and respects the generic Ord instance (defined by gcompare). The values from different constructors are enumerated sequentially; they are not interleaved.

data Example = C0 Bool Bool | C1 Bool
  deriving (Eq, Ord, Show, Generic)

cardinality = 6  -- 2    * 2    + 2
                 -- Bool * Bool | Bool

enumeration =
    [ C0 False False
    , C0 False  True
    , C0  True False
    , C0  True  True
    , C1 False
    , C1 True
    ]

enumeration == map gtoFiniteEnum [0 .. 5]
[0 .. 5] == map gfromFiniteEnum enumeration
Instances
(Bounded c, Enum c) => GEnum FiniteEnum (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: K1 i c p -> Int Source #

gToEnum :: Int -> K1 i c p Source #

(GEnum FiniteEnum f, GEnum FiniteEnum g) => GEnum FiniteEnum (f :*: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gCardinality :: Int Source #

gFromEnum :: (f :*: g) p -> Int Source #

gToEnum :: Int -> (f :*: g) p Source #

gfromFiniteEnum :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> Int Source #

Generic fromEnum generated with the FiniteEnum option.

See also gtoFiniteEnum.

gfiniteEnumFrom :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> [a] Source #

Generic enumFrom generated with the FiniteEnum option.

See also gtoFiniteEnum.

gfiniteEnumFromThen :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> [a] Source #

Generic enumFromThen generated with the FiniteEnum option.

See also gtoFiniteEnum.

gfiniteEnumFromTo :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> [a] Source #

Generic enumFromTo generated with the FiniteEnum option.

See also gtoFiniteEnum.

gfiniteEnumFromThenTo :: (Generic a, GEnum FiniteEnum (Rep a)) => a -> a -> a -> [a] Source #

Generic enumFromThenTo generated with the FiniteEnum option.

See also gtoFiniteEnum.

Bounded

Can also be derived by GHC as part of the standard.

gminBound :: (Generic a, GBounded (Rep a)) => a Source #

Generic minBound.

instance Bounded MyType where
  minBound = gminBound
  maxBound = gmaxBound

gmaxBound :: (Generic a, GBounded (Rep a)) => a Source #

Generic maxBound.

See also gminBound.

class GBounded f Source #

Generic representation of Bounded types.

Minimal complete definition

gMinBound, gMaxBound

Instances
GBounded (U1 :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Bounded c => GBounded (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gMinBound :: K1 i c p Source #

gMaxBound :: K1 i c p Source #

(GBounded f, GBounded g) => GBounded (f :+: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gMinBound :: (f :+: g) p Source #

gMaxBound :: (f :+: g) p Source #

(GBounded f, GBounded g) => GBounded (f :*: g) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gMinBound :: (f :*: g) p Source #

gMaxBound :: (f :*: g) p Source #

GBounded f => GBounded (M1 i c f) Source # 
Instance details

Defined in Generic.Data.Internal.Enum

Methods

gMinBound :: M1 i c f p Source #

gMaxBound :: M1 i c f p Source #

Higher-kinded classes

Functor

Can also be derived by GHC (DeriveFunctor extension).

gfmap :: (Generic1 f, Functor (Rep1 f)) => (a -> b) -> f a -> f b Source #

Generic fmap.

instance Functor MyTypeF where
  fmap = gfmap

gconstmap :: (Generic1 f, Functor (Rep1 f)) => a -> f b -> f a Source #

Generic (<$).

See also gfmap.

Foldable

Can also be derived by GHC (DeriveFoldable extension).

gfoldMap :: (Generic1 f, Foldable (Rep1 f), Monoid m) => (a -> m) -> f a -> m Source #

Generic foldMap.

instance Foldable MyTypeF where
  foldMap = gfoldMap

gfoldr :: (Generic1 f, Foldable (Rep1 f)) => (a -> b -> b) -> b -> f a -> b Source #

Generic foldr.

instance Foldable MyTypeF where
  foldr = gfoldr

See also gfoldMap.

Traversable

Can also be derived by GHC (DeriveTraversable extension).

gtraverse :: (Generic1 f, Traversable (Rep1 f), Applicative m) => (a -> m b) -> f a -> m (f b) Source #

Generic traverse.

instance Traversable MyTypeF where
  traverse = gtraverse

gsequenceA :: (Generic1 f, Traversable (Rep1 f), Applicative m) => f (m a) -> m (f a) Source #

Generic sequenceA.

instance Traversable MyTypeF where
  sequenceA = gsequenceA

See also gtraverse.

Applicative

gpure :: (Generic1 f, Applicative (Rep1 f)) => a -> f a Source #

Generic pure.

instance Applicative MyTypeF where
  pure = gpure
  (<*>) = gap

gap :: (Generic1 f, Applicative (Rep1 f)) => f (a -> b) -> f a -> f b Source #

Generic (<*>) (or ap).

See also gpure.

gliftA2 :: (Generic1 f, Applicative (Rep1 f)) => (a -> b -> c) -> f a -> f b -> f c Source #

Generic liftA2.

See also gpure.

Alternative

gempty :: (Generic1 f, Alternative (Rep1 f)) => f a Source #

Generic empty.

instance Alternative MyTypeF where
  empty = gempty
  (<|>) = galt

galt :: (Generic1 f, Alternative (Rep1 f)) => f a -> f a -> f a Source #

Generic (<|>).

See also gempty.

Eq1

gliftEq :: (Generic1 f, Eq1 (Rep1 f)) => (a -> b -> Bool) -> f a -> f b -> Bool Source #

Generic liftEq.

Ord1

gliftCompare :: (Generic1 f, Ord1 (Rep1 f)) => (a -> b -> Ordering) -> f a -> f b -> Ordering Source #

Generic liftCompare.

Show1

gliftShowsPrec :: (Generic1 f, GShow1 (Rep1 f)) => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS Source #

Generic liftShowsPrec.

type GShow1 = GShow Identity Source #

Generic representation of Show1 types.

Fields wrappers for deriving

newtype Id1 f a Source #

A newtype whose instances for simple classes (Eq, Ord, Read, Show) use higher-kinded class instances for f (Eq1, Ord1, Read1, Show1).

Constructors

Id1 

Fields

Instances
Eq1 f => Eq1 (Id1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

liftEq :: (a -> b -> Bool) -> Id1 f a -> Id1 f b -> Bool #

Ord1 f => Ord1 (Id1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

liftCompare :: (a -> b -> Ordering) -> Id1 f a -> Id1 f b -> Ordering #

Read1 f => Read1 (Id1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Id1 f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Id1 f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Id1 f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Id1 f a] #

Show1 f => Show1 (Id1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Id1 f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Id1 f a] -> ShowS #

(Eq1 f, Eq a) => Eq (Id1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

(==) :: Id1 f a -> Id1 f a -> Bool #

(/=) :: Id1 f a -> Id1 f a -> Bool #

(Ord1 f, Ord a) => Ord (Id1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

compare :: Id1 f a -> Id1 f a -> Ordering #

(<) :: Id1 f a -> Id1 f a -> Bool #

(<=) :: Id1 f a -> Id1 f a -> Bool #

(>) :: Id1 f a -> Id1 f a -> Bool #

(>=) :: Id1 f a -> Id1 f a -> Bool #

max :: Id1 f a -> Id1 f a -> Id1 f a #

min :: Id1 f a -> Id1 f a -> Id1 f a #

(Read1 f, Read a) => Read (Id1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

readsPrec :: Int -> ReadS (Id1 f a) #

readList :: ReadS [Id1 f a] #

readPrec :: ReadPrec (Id1 f a) #

readListPrec :: ReadPrec [Id1 f a] #

(Show1 f, Show a) => Show (Id1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

showsPrec :: Int -> Id1 f a -> ShowS #

show :: Id1 f a -> String #

showList :: [Id1 f a] -> ShowS #

newtype Opaque a Source #

A newtype with trivial instances, that considers every value equivalent to every other one, and shows as just "_".

Constructors

Opaque 

Fields

Instances
Eq1 Opaque Source #

All equal.

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

liftEq :: (a -> b -> Bool) -> Opaque a -> Opaque b -> Bool #

Ord1 Opaque Source #

All equal.

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

liftCompare :: (a -> b -> Ordering) -> Opaque a -> Opaque b -> Ordering #

Show1 Opaque Source #

Shown as "_".

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Opaque a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Opaque a] -> ShowS #

Eq (Opaque a) Source #

All equal.

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

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

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

Ord (Opaque a) Source #

All equal.

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

compare :: Opaque a -> Opaque a -> Ordering #

(<) :: Opaque a -> Opaque a -> Bool #

(<=) :: Opaque a -> Opaque a -> Bool #

(>) :: Opaque a -> Opaque a -> Bool #

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

max :: Opaque a -> Opaque a -> Opaque a #

min :: Opaque a -> Opaque a -> Opaque a #

Show (Opaque a) Source #

Shown as "_".

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

showsPrec :: Int -> Opaque a -> ShowS #

show :: Opaque a -> String #

showList :: [Opaque a] -> ShowS #

newtype Opaque1 f a Source #

A higher-kinded version of Opaque.

Constructors

Opaque1 

Fields

Instances
Eq1 (Opaque1 f) Source #

All equal.

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

liftEq :: (a -> b -> Bool) -> Opaque1 f a -> Opaque1 f b -> Bool #

Ord1 (Opaque1 f) Source #

All equal.

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

liftCompare :: (a -> b -> Ordering) -> Opaque1 f a -> Opaque1 f b -> Ordering #

Show1 (Opaque1 f) Source #

Shown as "_".

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Opaque1 f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Opaque1 f a] -> ShowS #

Eq (Opaque1 f a) Source #

All equal.

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

(==) :: Opaque1 f a -> Opaque1 f a -> Bool #

(/=) :: Opaque1 f a -> Opaque1 f a -> Bool #

Ord (Opaque1 f a) Source #

All equal.

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

compare :: Opaque1 f a -> Opaque1 f a -> Ordering #

(<) :: Opaque1 f a -> Opaque1 f a -> Bool #

(<=) :: Opaque1 f a -> Opaque1 f a -> Bool #

(>) :: Opaque1 f a -> Opaque1 f a -> Bool #

(>=) :: Opaque1 f a -> Opaque1 f a -> Bool #

max :: Opaque1 f a -> Opaque1 f a -> Opaque1 f a #

min :: Opaque1 f a -> Opaque1 f a -> Opaque1 f a #

Show (Opaque1 f a) Source #

Shown as "_".

Instance details

Defined in Generic.Data.Internal.Resolvers

Methods

showsPrec :: Int -> Opaque1 f a -> ShowS #

show :: Opaque1 f a -> String #

showList :: [Opaque1 f a] -> ShowS #

Carriers of generic instances

newtype Generically a Source #

Type with instances derived via Generic.

Constructors

Generically 

Fields

Instances
(Generic a, GBounded (Rep a)) => Bounded (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, GEnum StandardEnum (Rep a)) => Enum (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, Eq (Rep a ())) => Eq (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, Ord (Rep a ())) => Ord (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, GShow0 (Rep a)) => Show (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Generic a => Generic (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Associated Types

type Rep (Generically a) :: Type -> Type #

Methods

from :: Generically a -> Rep (Generically a) x #

to :: Rep (Generically a) x -> Generically a #

(Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic a, Monoid (Rep a ())) => Monoid (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

type Rep (Generically a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

type Rep (Generically a) = Rep a

newtype Generically1 f a Source #

Type with instances derived via Generic1.

Constructors

Generically1 

Fields

Instances
(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

fmap :: (a -> b) -> Generically1 f a -> Generically1 f b #

(<$) :: a -> Generically1 f b -> Generically1 f a #

(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

pure :: a -> Generically1 f a #

(<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b #

liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c #

(*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b #

(<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a #

(Generic1 f, Foldable (Rep1 f)) => Foldable (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

fold :: Monoid m => Generically1 f m -> m #

foldMap :: Monoid m => (a -> m) -> Generically1 f a -> m #

foldr :: (a -> b -> b) -> b -> Generically1 f a -> b #

foldr' :: (a -> b -> b) -> b -> Generically1 f a -> b #

foldl :: (b -> a -> b) -> b -> Generically1 f a -> b #

foldl' :: (b -> a -> b) -> b -> Generically1 f a -> b #

foldr1 :: (a -> a -> a) -> Generically1 f a -> a #

foldl1 :: (a -> a -> a) -> Generically1 f a -> a #

toList :: Generically1 f a -> [a] #

null :: Generically1 f a -> Bool #

length :: Generically1 f a -> Int #

elem :: Eq a => a -> Generically1 f a -> Bool #

maximum :: Ord a => Generically1 f a -> a #

minimum :: Ord a => Generically1 f a -> a #

sum :: Num a => Generically1 f a -> a #

product :: Num a => Generically1 f a -> a #

(Generic1 f, Traversable (Rep1 f)) => Traversable (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Generically1 f a -> f0 (Generically1 f b) #

sequenceA :: Applicative f0 => Generically1 f (f0 a) -> f0 (Generically1 f a) #

mapM :: Monad m => (a -> m b) -> Generically1 f a -> m (Generically1 f b) #

sequence :: Monad m => Generically1 f (m a) -> m (Generically1 f a) #

(Generic1 f, Eq1 (Rep1 f)) => Eq1 (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

liftEq :: (a -> b -> Bool) -> Generically1 f a -> Generically1 f b -> Bool #

(Generic1 f, Ord1 (Rep1 f)) => Ord1 (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

liftCompare :: (a -> b -> Ordering) -> Generically1 f a -> Generically1 f b -> Ordering #

(Generic1 f, GShow1 (Rep1 f)) => Show1 (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Generically1 f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Generically1 f a] -> ShowS #

(Generic1 f, Alternative (Rep1 f)) => Alternative (Generically1 f) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

empty :: Generically1 f a #

(<|>) :: Generically1 f a -> Generically1 f a -> Generically1 f a #

some :: Generically1 f a -> Generically1 f [a] #

many :: Generically1 f a -> Generically1 f [a] #

Generic1 f => Generic1 (Generically1 f :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Associated Types

type Rep1 (Generically1 f) :: k -> Type #

Methods

from1 :: Generically1 f a -> Rep1 (Generically1 f) a #

to1 :: Rep1 (Generically1 f) a -> Generically1 f a #

(Generic1 f, Eq1 (Rep1 f), Eq a) => Eq (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Methods

(==) :: Generically1 f a -> Generically1 f a -> Bool #

(/=) :: Generically1 f a -> Generically1 f a -> Bool #

(Generic1 f, Ord1 (Rep1 f), Ord a) => Ord (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

(Generic1 f, GShow1 (Rep1 f), Show a) => Show (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Generic (f a) => Generic (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

Associated Types

type Rep (Generically1 f a) :: Type -> Type #

Methods

from :: Generically1 f a -> Rep (Generically1 f a) x #

to :: Rep (Generically1 f a) x -> Generically1 f a #

type Rep1 (Generically1 f :: Type -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

type Rep1 (Generically1 f :: Type -> Type) = Rep1 f
type Rep (Generically1 f a) Source # 
Instance details

Defined in Generic.Data.Internal.Generically

type Rep (Generically1 f a) = Rep (f a)

Newtype

Generic pack/unpack.

class (Generic a, Coercible a (Old a), Newtype' a) => Newtype a Source #

Class of newtypes.

Instances
(Generic a, Coercible a (Old a), Newtype' a) => Newtype a Source # 
Instance details

Defined in Generic.Data.Internal.Newtype

pack :: Newtype a => Old a -> a Source #

Generic newtype constructor.

unpack :: Newtype a => a -> Old a Source #

Generic newtype destructor.

Accessing metadata

Using TypeApplications.

Datatype

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.

class GDatatype f Source #

Generic representations that contain datatype metadata.

Minimal complete definition

gDatatypeName, gModuleName, gPackageName, gIsNewtype

Constructor

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

gconIndex :: forall a. Constructors a => a -> Int Source #

Index of a constructor.

gconIndex Nothing = 0
gconIndex (Just "test") = 1

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

Constraint synonym for Generic and GConstructor.

Instances
(Generic a, GConstructors (Rep a)) => Constructors a Source # 
Instance details

Defined in Generic.Data.Internal.Meta

class GConstructors r Source #

Generic representations that contain constructor metadata.

Minimal complete definition

gConIdToString, gConId, gConNum, gConFixity, gConIsRecord

Instances
(GConstructors f, GConstructors g) => GConstructors (f :+: g :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Meta

Methods

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

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

gConNum :: Int Source #

gConFixity :: (f :+: g) p -> Fixity Source #

gConIsRecord :: (f :+: g) p -> Bool Source #

Constructor c => GConstructors (M1 C c f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Meta

Methods

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

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

gConNum :: Int Source #

gConFixity :: M1 C c f p -> Fixity Source #

gConIsRecord :: M1 C c f p -> Bool Source #

GConstructors f => GConstructors (M1 D c f :: k -> Type) Source # 
Instance details

Defined in Generic.Data.Internal.Meta

Methods

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

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

gConNum :: Int Source #

gConFixity :: M1 D c f p -> Fixity Source #

gConIsRecord :: M1 D c f p -> Bool Source #

Constructor tags

data ConId a Source #

An opaque identifier for a constructor.

Instances
Eq (ConId a) Source # 
Instance details

Defined in Generic.Data.Internal.Meta

Methods

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

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

Ord (ConId a) Source # 
Instance details

Defined in Generic.Data.Internal.Meta

Methods

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

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

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

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

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

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

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

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

Identifier of a constructor.

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

Index of a constructor, given its identifier. See also gconIndex.

conIdToString :: forall a. Constructors a => ConId a -> String Source #

Name of a constructor. See also gconName.

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

All constructor identifiers.

gconNum @a = length (conIdEnum @a)

Using type families

type family MetaOf (f :: * -> *) :: Meta where ... Source #

Meta field of the M1 type constructor.

Equations

MetaOf (M1 i d f) = d 

type family MetaDataName (m :: Meta) :: Symbol where ... Source #

Name of the data type (MetaData).

Equations

MetaDataName (MetaData n _m _p _nt) = n 

type family MetaDataModule (m :: Meta) :: Symbol where ... Source #

Name of the module where the data type is defined (MetaData)

Equations

MetaDataModule (MetaData _n m _p _nt) = m 

type family MetaDataPackage (m :: Meta) :: Symbol where ... Source #

Name of the package where the data type is defined (MetaData)

Equations

MetaDataPackage (MetaData _n _m p _nt) = p 

type family MetaDataNewtype (m :: Meta) :: Bool where ... Source #

True if the data type is a newtype (MetaData).

Equations

MetaDataNewtype (MetaData _n _m _p nt) = nt 

type family MetaConsName (m :: Meta) :: Symbol where ... Source #

Name of the constructor (MetaCons).

Equations

MetaConsName (MetaCons n _f _s) = n 

type family MetaConsFixity (m :: Meta) :: FixityI where ... Source #

Fixity of the constructor (MetaCons).

Equations

MetaConsFixity (MetaCons _n f s) = f 

type family MetaConsRecord (m :: Meta) :: Bool where ... Source #

True for a record constructor (MetaCons).

Equations

MetaConsRecord (MetaCons _n _f s) = s 

type family MetaSelNameM (m :: Meta) :: Maybe Symbol where ... Source #

Just the name of the record field, if it is one (MetaSel).

Equations

MetaSelNameM (MetaSel mn _su _ss _ds) = mn 

type family MetaSelName (m :: Meta) :: Symbol where ... Source #

Name of the record field; undefined for non-record fields (MetaSel).

Equations

MetaSelName (MetaSel (Just n) _su _ss _ds) = n 

type family MetaSelUnpack (m :: Meta) :: SourceUnpackedness where ... Source #

Unpackedness annotation of a field (MetaSel).

Equations

MetaSelUnpack (MetaSel _mn su _ss _ds) = su 

type family MetaSelSourceStrictness (m :: Meta) :: SourceStrictness where ... Source #

Strictness annotation of a field (MetaSel).

Equations

MetaSelSourceStrictness (MetaSel _mn _su ss _ds) = ss 

type family MetaSelStrictness (m :: Meta) :: DecidedStrictness where ... Source #

Inferred strictness of a field (MetaSel).

Equations

MetaSelStrictness (MetaSel _mn _su _ss ds) = ds