staged-gg-0.1: GHC.Generics style staged generics
Safe HaskellNone
LanguageHaskell2010

Staged.GHC.Generics.Types

Synopsis

Generic representation types

data V2 (q :: Type -> Type) (p :: k) Source #

Instances

Instances details
Eq (V2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

(==) :: V2 q p -> V2 q p -> Bool #

(/=) :: V2 q p -> V2 q p -> Bool #

Ord (V2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

compare :: V2 q p -> V2 q p -> Ordering #

(<) :: V2 q p -> V2 q p -> Bool #

(<=) :: V2 q p -> V2 q p -> Bool #

(>) :: V2 q p -> V2 q p -> Bool #

(>=) :: V2 q p -> V2 q p -> Bool #

max :: V2 q p -> V2 q p -> V2 q p #

min :: V2 q p -> V2 q p -> V2 q p #

Read (V2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

readsPrec :: Int -> ReadS (V2 q p) #

readList :: ReadS [V2 q p] #

readPrec :: ReadPrec (V2 q p) #

readListPrec :: ReadPrec [V2 q p] #

Show (V2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

showsPrec :: Int -> V2 q p -> ShowS #

show :: V2 q p -> String #

showList :: [V2 q p] -> ShowS #

data U2 (q :: Type -> Type) (p :: k) Source #

Constructors

U2 

Instances

Instances details
Eq (U2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

(==) :: U2 q p -> U2 q p -> Bool #

(/=) :: U2 q p -> U2 q p -> Bool #

Ord (U2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

compare :: U2 q p -> U2 q p -> Ordering #

(<) :: U2 q p -> U2 q p -> Bool #

(<=) :: U2 q p -> U2 q p -> Bool #

(>) :: U2 q p -> U2 q p -> Bool #

(>=) :: U2 q p -> U2 q p -> Bool #

max :: U2 q p -> U2 q p -> U2 q p #

min :: U2 q p -> U2 q p -> U2 q p #

Read (U2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

readsPrec :: Int -> ReadS (U2 q p) #

readList :: ReadS [U2 q p] #

readPrec :: ReadPrec (U2 q p) #

readListPrec :: ReadPrec [U2 q p] #

Show (U2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

showsPrec :: Int -> U2 q p -> ShowS #

show :: U2 q p -> String #

showList :: [U2 q p] -> ShowS #

newtype M2 (i :: Type) (c :: Meta) (f :: (Type -> Type) -> k -> Type) (q :: Type -> Type) (p :: k) Source #

Constructors

M2 

Fields

Instances

Instances details
Eq (f q p) => Eq (M2 i c f q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

(==) :: M2 i c f q p -> M2 i c f q p -> Bool #

(/=) :: M2 i c f q p -> M2 i c f q p -> Bool #

Ord (f q p) => Ord (M2 i c f q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

compare :: M2 i c f q p -> M2 i c f q p -> Ordering #

(<) :: M2 i c f q p -> M2 i c f q p -> Bool #

(<=) :: M2 i c f q p -> M2 i c f q p -> Bool #

(>) :: M2 i c f q p -> M2 i c f q p -> Bool #

(>=) :: M2 i c f q p -> M2 i c f q p -> Bool #

max :: M2 i c f q p -> M2 i c f q p -> M2 i c f q p #

min :: M2 i c f q p -> M2 i c f q p -> M2 i c f q p #

Read (f q p) => Read (M2 i c f q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

readsPrec :: Int -> ReadS (M2 i c f q p) #

readList :: ReadS [M2 i c f q p] #

readPrec :: ReadPrec (M2 i c f q p) #

readListPrec :: ReadPrec [M2 i c f q p] #

Show (f q p) => Show (M2 i c f q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

showsPrec :: Int -> M2 i c f q p -> ShowS #

show :: M2 i c f q p -> String #

showList :: [M2 i c f q p] -> ShowS #

newtype K2 c (q :: Type -> Type) (p :: k) Source #

Constructors

K2 

Fields

Instances

Instances details
Eq (q c) => Eq (K2 c q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

(==) :: K2 c q p -> K2 c q p -> Bool #

(/=) :: K2 c q p -> K2 c q p -> Bool #

Ord (q c) => Ord (K2 c q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

compare :: K2 c q p -> K2 c q p -> Ordering #

(<) :: K2 c q p -> K2 c q p -> Bool #

(<=) :: K2 c q p -> K2 c q p -> Bool #

(>) :: K2 c q p -> K2 c q p -> Bool #

(>=) :: K2 c q p -> K2 c q p -> Bool #

max :: K2 c q p -> K2 c q p -> K2 c q p #

min :: K2 c q p -> K2 c q p -> K2 c q p #

Read (q c) => Read (K2 c q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

readsPrec :: Int -> ReadS (K2 c q p) #

readList :: ReadS [K2 c q p] #

readPrec :: ReadPrec (K2 c q p) #

readListPrec :: ReadPrec [K2 c q p] #

Show (q c) => Show (K2 c q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

showsPrec :: Int -> K2 c q p -> ShowS #

show :: K2 c q p -> String #

showList :: [K2 c q p] -> ShowS #

newtype Par2 (q :: Type -> Type) (p :: Type) Source #

Constructors

Par2 

Fields

Instances

Instances details
Eq (q p) => Eq (Par2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

(==) :: Par2 q p -> Par2 q p -> Bool #

(/=) :: Par2 q p -> Par2 q p -> Bool #

Ord (q p) => Ord (Par2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

compare :: Par2 q p -> Par2 q p -> Ordering #

(<) :: Par2 q p -> Par2 q p -> Bool #

(<=) :: Par2 q p -> Par2 q p -> Bool #

(>) :: Par2 q p -> Par2 q p -> Bool #

(>=) :: Par2 q p -> Par2 q p -> Bool #

max :: Par2 q p -> Par2 q p -> Par2 q p #

min :: Par2 q p -> Par2 q p -> Par2 q p #

Read (q p) => Read (Par2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

readsPrec :: Int -> ReadS (Par2 q p) #

readList :: ReadS [Par2 q p] #

readPrec :: ReadPrec (Par2 q p) #

readListPrec :: ReadPrec [Par2 q p] #

Show (q p) => Show (Par2 q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

showsPrec :: Int -> Par2 q p -> ShowS #

show :: Par2 q p -> String #

showList :: [Par2 q p] -> ShowS #

data ((f :: (Type -> Type) -> k -> Type) :++: (g :: (Type -> Type) -> k -> Type)) (q :: Type -> Type) (p :: k) infixr 5 Source #

Constructors

L2 (f q p) 
R2 (g q p) 

Instances

Instances details
(Eq (f q p), Eq (g q p)) => Eq ((f :++: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

(==) :: (f :++: g) q p -> (f :++: g) q p -> Bool #

(/=) :: (f :++: g) q p -> (f :++: g) q p -> Bool #

(Ord (f q p), Ord (g q p)) => Ord ((f :++: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

compare :: (f :++: g) q p -> (f :++: g) q p -> Ordering #

(<) :: (f :++: g) q p -> (f :++: g) q p -> Bool #

(<=) :: (f :++: g) q p -> (f :++: g) q p -> Bool #

(>) :: (f :++: g) q p -> (f :++: g) q p -> Bool #

(>=) :: (f :++: g) q p -> (f :++: g) q p -> Bool #

max :: (f :++: g) q p -> (f :++: g) q p -> (f :++: g) q p #

min :: (f :++: g) q p -> (f :++: g) q p -> (f :++: g) q p #

(Read (f q p), Read (g q p)) => Read ((f :++: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

readsPrec :: Int -> ReadS ((f :++: g) q p) #

readList :: ReadS [(f :++: g) q p] #

readPrec :: ReadPrec ((f :++: g) q p) #

readListPrec :: ReadPrec [(f :++: g) q p] #

(Show (f q p), Show (g q p)) => Show ((f :++: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

showsPrec :: Int -> (f :++: g) q p -> ShowS #

show :: (f :++: g) q p -> String #

showList :: [(f :++: g) q p] -> ShowS #

data ((f :: (Type -> Type) -> k -> Type) :**: (g :: (Type -> Type) -> k -> Type)) (q :: Type -> Type) (p :: k) infixr 6 Source #

Constructors

(f q p) :**: (g q p) infixr 6 

Instances

Instances details
(Eq (f q p), Eq (g q p)) => Eq ((f :**: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

(==) :: (f :**: g) q p -> (f :**: g) q p -> Bool #

(/=) :: (f :**: g) q p -> (f :**: g) q p -> Bool #

(Ord (f q p), Ord (g q p)) => Ord ((f :**: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

compare :: (f :**: g) q p -> (f :**: g) q p -> Ordering #

(<) :: (f :**: g) q p -> (f :**: g) q p -> Bool #

(<=) :: (f :**: g) q p -> (f :**: g) q p -> Bool #

(>) :: (f :**: g) q p -> (f :**: g) q p -> Bool #

(>=) :: (f :**: g) q p -> (f :**: g) q p -> Bool #

max :: (f :**: g) q p -> (f :**: g) q p -> (f :**: g) q p #

min :: (f :**: g) q p -> (f :**: g) q p -> (f :**: g) q p #

(Read (f q p), Read (g q p)) => Read ((f :**: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

readsPrec :: Int -> ReadS ((f :**: g) q p) #

readList :: ReadS [(f :**: g) q p] #

readPrec :: ReadPrec ((f :**: g) q p) #

readListPrec :: ReadPrec [(f :**: g) q p] #

(Show (f q p), Show (g q p)) => Show ((f :**: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

showsPrec :: Int -> (f :**: g) q p -> ShowS #

show :: (f :**: g) q p -> String #

showList :: [(f :**: g) q p] -> ShowS #

newtype ((f :: (Type -> Type) -> k2 -> Type) :@@: (g :: k1 -> k2)) (q :: Type -> Type) (p :: k1) infixl 7 Source #

Constructors

App2 

Fields

Instances

Instances details
Eq (f q (g p)) => Eq ((f :@@: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

(==) :: (f :@@: g) q p -> (f :@@: g) q p -> Bool #

(/=) :: (f :@@: g) q p -> (f :@@: g) q p -> Bool #

Ord (f q (g p)) => Ord ((f :@@: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

compare :: (f :@@: g) q p -> (f :@@: g) q p -> Ordering #

(<) :: (f :@@: g) q p -> (f :@@: g) q p -> Bool #

(<=) :: (f :@@: g) q p -> (f :@@: g) q p -> Bool #

(>) :: (f :@@: g) q p -> (f :@@: g) q p -> Bool #

(>=) :: (f :@@: g) q p -> (f :@@: g) q p -> Bool #

max :: (f :@@: g) q p -> (f :@@: g) q p -> (f :@@: g) q p #

min :: (f :@@: g) q p -> (f :@@: g) q p -> (f :@@: g) q p #

Read (f q (g p)) => Read ((f :@@: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

readsPrec :: Int -> ReadS ((f :@@: g) q p) #

readList :: ReadS [(f :@@: g) q p] #

readPrec :: ReadPrec ((f :@@: g) q p) #

readListPrec :: ReadPrec [(f :@@: g) q p] #

Show (f q (g p)) => Show ((f :@@: g) q p) Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Methods

showsPrec :: Int -> (f :@@: g) q p -> ShowS #

show :: (f :@@: g) q p -> String #

showList :: [(f :@@: g) q p] -> ShowS #

Synonyms for convenience

type D2 = M2 D Source #

type C2 = M2 C Source #

type S2 = M2 S Source #

data D #

Tag for M1: datatype

Instances

Instances details
Generic D Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep D :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep D (Code q) x -> Code q D Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q D -> (Rep D (Code q) x -> Code q r) -> Code q r Source #

type Rep D Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

type Rep D = D2 ('MetaData "D" "GHC.Generics" "base" 'False) (V2 :: (Type -> Type) -> Type -> Type)

data C #

Tag for M1: constructor

Instances

Instances details
Generic C Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep C :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep C (Code q) x -> Code q C Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q C -> (Rep C (Code q) x -> Code q r) -> Code q r Source #

type Rep C Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

type Rep C = D2 ('MetaData "C" "GHC.Generics" "base" 'False) (V2 :: (Type -> Type) -> Type -> Type)

data S #

Tag for M1: record selector

Instances

Instances details
Generic S Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep S :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep S (Code q) x -> Code q S Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q S -> (Rep S (Code q) x -> Code q r) -> Code q r Source #

type Rep S Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

type Rep S = D2 ('MetaData "S" "GHC.Generics" "base" 'False) (V2 :: (Type -> Type) -> Type -> Type)

Meta-information

class Datatype (d :: k) where #

Class for datatypes that represent datatypes

Minimal complete definition

datatypeName, moduleName, packageName

Methods

datatypeName :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> [Char] #

The name of the datatype (unqualified)

moduleName :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> [Char] #

The fully-qualified name of the module where the type is declared

packageName :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> [Char] #

The package name of the module where the type is declared

Since: base-4.9.0.0

isNewtype :: forall k1 t (f :: k1 -> Type) (a :: k1). t d f a -> Bool #

Marks if the datatype is actually a newtype

Since: base-4.7.0.0

Instances

Instances details
(KnownSymbol n, KnownSymbol m, KnownSymbol p, SingI nt) => Datatype ('MetaData n m p nt :: Meta)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

datatypeName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] #

moduleName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] #

packageName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] #

isNewtype :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> Bool #

class Constructor (c :: k) where #

Class for datatypes that represent data constructors

Minimal complete definition

conName

Methods

conName :: forall k1 t (f :: k1 -> Type) (a :: k1). t c f a -> [Char] #

The name of the constructor

conFixity :: forall k1 t (f :: k1 -> Type) (a :: k1). t c f a -> Fixity #

The fixity of the constructor

conIsRecord :: forall k1 t (f :: k1 -> Type) (a :: k1). t c f a -> Bool #

Marks if this constructor is a record

Instances

Instances details
(KnownSymbol n, SingI f, SingI r) => Constructor ('MetaCons n f r :: Meta)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

conName :: forall k1 t (f0 :: k1 -> Type) (a :: k1). t ('MetaCons n f r) f0 a -> [Char] #

conFixity :: forall k1 t (f0 :: k1 -> Type) (a :: k1). t ('MetaCons n f r) f0 a -> Fixity #

conIsRecord :: forall k1 t (f0 :: k1 -> Type) (a :: k1). t ('MetaCons n f r) f0 a -> Bool #

class Selector (s :: k) where #

Class for datatypes that represent records

Methods

selName :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> [Char] #

The name of the selector

selSourceUnpackedness :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> SourceUnpackedness #

The selector's unpackedness annotation (if any)

Since: base-4.9.0.0

selSourceStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> SourceStrictness #

The selector's strictness annotation (if any)

Since: base-4.9.0.0

selDecidedStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t s f a -> DecidedStrictness #

The strictness that the compiler inferred for the selector

Since: base-4.9.0.0

Instances

Instances details
(SingI mn, SingI su, SingI ss, SingI ds) => Selector ('MetaSel mn su ss ds :: Meta)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

selName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> [Char] #

selSourceUnpackedness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> SourceUnpackedness #

selSourceStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> SourceStrictness #

selDecidedStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> DecidedStrictness #

data Fixity #

Datatype to represent the fixity of a constructor. An infix | declaration directly corresponds to an application of Infix.

Constructors

Prefix 
Infix Associativity Int 

Instances

Instances details
Eq Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: Fixity -> Fixity -> Bool #

(/=) :: Fixity -> Fixity -> Bool #

Data Fixity

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

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

toConstr :: Fixity -> Constr #

dataTypeOf :: Fixity -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Read Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Generic Fixity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Fixity Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Fixity :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Fixity (Code q) x -> Code q Fixity Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Fixity -> (Rep Fixity (Code q) x -> Code q r) -> Code q r Source #

type Rep Fixity 
Instance details

Defined in GHC.Generics

type Rep Fixity Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

data FixityI #

This variant of Fixity appears at the type level.

Since: base-4.9.0.0

Instances

Instances details
SingKind FixityI

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep FixityI

Methods

fromSing :: forall (a :: FixityI). Sing a -> DemoteRep FixityI

SingI 'PrefixI

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'PrefixI

(SingI a, KnownNat n) => SingI ('InfixI a n :: FixityI)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing ('InfixI a n)

type DemoteRep FixityI 
Instance details

Defined in GHC.Generics

type DemoteRep FixityI = Fixity
data Sing (a :: FixityI) 
Instance details

Defined in GHC.Generics

data Sing (a :: FixityI) where

data Associativity #

Datatype to represent the associativity of a constructor

Instances

Instances details
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 :: forall r r'. (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

Since: base-4.7.0.0

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

Methods

fromSing :: forall (a :: Associativity). Sing a -> DemoteRep Associativity

Generic Associativity Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Associativity :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Associativity (Code q) x -> Code q Associativity Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Associativity -> (Rep Associativity (Code q) x -> Code q r) -> Code q r 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 
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)))
type DemoteRep Associativity 
Instance details

Defined in GHC.Generics

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

Defined in GHC.Generics

type Rep Associativity Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

type Rep Associativity = D2 ('MetaData "Associativity" "GHC.Generics" "base" 'False) (C2 ('MetaCons "LeftAssociative" 'PrefixI 'False) (U2 :: (Type -> Type) -> Type -> Type) :++: (C2 ('MetaCons "RightAssociative" 'PrefixI 'False) (U2 :: (Type -> Type) -> Type -> Type) :++: C2 ('MetaCons "NotAssociative" 'PrefixI 'False) (U2 :: (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

Instances details
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 :: forall r r'. (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

Since: base-4.9.0.0

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

Methods

fromSing :: forall (a :: SourceUnpackedness). Sing a -> DemoteRep SourceUnpackedness

Generic SourceUnpackedness Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep SourceUnpackedness :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep SourceUnpackedness (Code q) x -> Code q SourceUnpackedness Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q SourceUnpackedness -> (Rep SourceUnpackedness (Code q) x -> Code q r) -> Code q r 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 
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)))
type DemoteRep SourceUnpackedness 
Instance details

Defined in GHC.Generics

data Sing (a :: SourceUnpackedness) 
Instance details

Defined in GHC.Generics

type Rep SourceUnpackedness Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

type Rep SourceUnpackedness = D2 ('MetaData "SourceUnpackedness" "GHC.Generics" "base" 'False) (C2 ('MetaCons "NoSourceUnpackedness" 'PrefixI 'False) (U2 :: (Type -> Type) -> Type -> Type) :++: (C2 ('MetaCons "SourceNoUnpack" 'PrefixI 'False) (U2 :: (Type -> Type) -> Type -> Type) :++: C2 ('MetaCons "SourceUnpack" 'PrefixI 'False) (U2 :: (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

Instances details
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 :: forall r r'. (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

Since: base-4.9.0.0

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

Methods

fromSing :: forall (a :: SourceStrictness). Sing a -> DemoteRep SourceStrictness

Generic SourceStrictness Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep SourceStrictness :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep SourceStrictness (Code q) x -> Code q SourceStrictness Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q SourceStrictness -> (Rep SourceStrictness (Code q) x -> Code q r) -> Code q r 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 
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)))
type DemoteRep SourceStrictness 
Instance details

Defined in GHC.Generics

data Sing (a :: SourceStrictness) 
Instance details

Defined in GHC.Generics

type Rep SourceStrictness Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

type Rep SourceStrictness = D2 ('MetaData "SourceStrictness" "GHC.Generics" "base" 'False) (C2 ('MetaCons "NoSourceStrictness" 'PrefixI 'False) (U2 :: (Type -> Type) -> Type -> Type) :++: (C2 ('MetaCons "SourceLazy" 'PrefixI 'False) (U2 :: (Type -> Type) -> Type -> Type) :++: C2 ('MetaCons "SourceStrict" 'PrefixI 'False) (U2 :: (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

Instances details
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 :: forall r r'. (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

Since: base-4.9.0.0

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

Methods

fromSing :: forall (a :: DecidedStrictness). Sing a -> DemoteRep DecidedStrictness

Generic DecidedStrictness Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep DecidedStrictness :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep DecidedStrictness (Code q) x -> Code q DecidedStrictness Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q DecidedStrictness -> (Rep DecidedStrictness (Code q) x -> Code q r) -> Code q r 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 
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)))
type DemoteRep DecidedStrictness 
Instance details

Defined in GHC.Generics

data Sing (a :: DecidedStrictness) 
Instance details

Defined in GHC.Generics

type Rep DecidedStrictness Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

type Rep DecidedStrictness = D2 ('MetaData "DecidedStrictness" "GHC.Generics" "base" 'False) (C2 ('MetaCons "DecidedLazy" 'PrefixI 'False) (U2 :: (Type -> Type) -> Type -> Type) :++: (C2 ('MetaCons "DecidedStrict" 'PrefixI 'False) (U2 :: (Type -> Type) -> Type -> Type) :++: C2 ('MetaCons "DecidedUnpack" 'PrefixI 'False) (U2 :: (Type -> Type) -> Type -> Type)))

data Meta #

Datatype to represent metadata associated with a datatype (MetaData), constructor (MetaCons), or field selector (MetaSel).

  • In MetaData n m p nt, n is the datatype's name, m is the module in which the datatype is defined, p is the package in which the datatype is defined, and nt is 'True if the datatype is a newtype.
  • In MetaCons n f s, n is the constructor's name, f is its fixity, and s is 'True if the constructor contains record selectors.
  • In MetaSel mn su ss ds, if the field uses record syntax, then mn is Just the record name. Otherwise, mn is Nothing. su and ss are the field's unpackedness and strictness annotations, and ds is the strictness that GHC infers for the field.

Since: base-4.9.0.0

Instances

Instances details
(KnownSymbol n, SingI f, SingI r) => Constructor ('MetaCons n f r :: Meta)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

conName :: forall k1 t (f0 :: k1 -> Type) (a :: k1). t ('MetaCons n f r) f0 a -> [Char] #

conFixity :: forall k1 t (f0 :: k1 -> Type) (a :: k1). t ('MetaCons n f r) f0 a -> Fixity #

conIsRecord :: forall k1 t (f0 :: k1 -> Type) (a :: k1). t ('MetaCons n f r) f0 a -> Bool #

(KnownSymbol n, KnownSymbol m, KnownSymbol p, SingI nt) => Datatype ('MetaData n m p nt :: Meta)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

datatypeName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] #

moduleName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] #

packageName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> [Char] #

isNewtype :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaData n m p nt) f a -> Bool #

(SingI mn, SingI su, SingI ss, SingI ds) => Selector ('MetaSel mn su ss ds :: Meta)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

selName :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> [Char] #

selSourceUnpackedness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> SourceUnpackedness #

selSourceStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> SourceStrictness #

selDecidedStrictness :: forall k1 t (f :: k1 -> Type) (a :: k1). t ('MetaSel mn su ss ds) f a -> DecidedStrictness #

Generic type classes

class Generic (a :: Type) where Source #

Associated Types

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

type Rep a = Translate (Rep a)

Methods

to :: Quote q => Rep a (Code q) x -> Code q a Source #

from :: Quote q => Code q a -> (Rep a (Code q) x -> Code q r) -> Code q r Source #

Instances

Instances details
Generic Bool Source # 
Instance details

Defined in Staged.GHC.Generics.Types

Associated Types

type Rep Bool :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Bool (Code q) x -> Code q Bool Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Bool -> (Rep Bool (Code q) x -> Code q r) -> Code q r Source #

Generic Ordering Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Ordering :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Ordering (Code q) x -> Code q Ordering Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Ordering -> (Rep Ordering (Code q) x -> Code q r) -> Code q r Source #

Generic RuntimeRep Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep RuntimeRep :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep RuntimeRep (Code q) x -> Code q RuntimeRep Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q RuntimeRep -> (Rep RuntimeRep (Code q) x -> Code q r) -> Code q r Source #

Generic VecCount Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep VecCount :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep VecCount (Code q) x -> Code q VecCount Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q VecCount -> (Rep VecCount (Code q) x -> Code q r) -> Code q r Source #

Generic VecElem Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep VecElem :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep VecElem (Code q) x -> Code q VecElem Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q VecElem -> (Rep VecElem (Code q) x -> Code q r) -> Code q r Source #

Generic R Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep R :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep R (Code q) x -> Code q R Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q R -> (Rep R (Code q) x -> Code q r) -> Code q r Source #

Generic D Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep D :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep D (Code q) x -> Code q D Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q D -> (Rep D (Code q) x -> Code q r) -> Code q r Source #

Generic C Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep C :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep C (Code q) x -> Code q C Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q C -> (Rep C (Code q) x -> Code q r) -> Code q r Source #

Generic S Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep S :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep S (Code q) x -> Code q S Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q S -> (Rep S (Code q) x -> Code q r) -> Code q r Source #

Generic CallStack Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CallStack :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CallStack (Code q) x -> Code q CallStack Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CallStack -> (Rep CallStack (Code q) x -> Code q r) -> Code q r Source #

Generic () Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep () :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep () (Code q) x -> Code q () Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q () -> (Rep () (Code q) x -> Code q r) -> Code q r Source #

Generic E0 Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep E0 :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep E0 (Code q) x -> Code q E0 Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q E0 -> (Rep E0 (Code q) x -> Code q r) -> Code q r Source #

Generic E1 Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep E1 :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep E1 (Code q) x -> Code q E1 Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q E1 -> (Rep E1 (Code q) x -> Code q r) -> Code q r Source #

Generic E2 Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep E2 :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep E2 (Code q) x -> Code q E2 Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q E2 -> (Rep E2 (Code q) x -> Code q r) -> Code q r Source #

Generic E3 Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep E3 :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep E3 (Code q) x -> Code q E3 Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q E3 -> (Rep E3 (Code q) x -> Code q r) -> Code q r Source #

Generic E6 Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep E6 :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep E6 (Code q) x -> Code q E6 Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q E6 -> (Rep E6 (Code q) x -> Code q r) -> Code q r Source #

Generic E9 Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep E9 :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep E9 (Code q) x -> Code q E9 Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q E9 -> (Rep E9 (Code q) x -> Code q r) -> Code q r Source #

Generic E12 Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep E12 :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep E12 (Code q) x -> Code q E12 Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q E12 -> (Rep E12 (Code q) x -> Code q r) -> Code q r Source #

Generic Void Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Void :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Void (Code q) x -> Code q Void Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Void -> (Rep Void (Code q) x -> Code q r) -> Code q r Source #

Generic DataRep Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep DataRep :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep DataRep (Code q) x -> Code q DataRep Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q DataRep -> (Rep DataRep (Code q) x -> Code q r) -> Code q r Source #

Generic ConstrRep Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ConstrRep :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ConstrRep (Code q) x -> Code q ConstrRep Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ConstrRep -> (Rep ConstrRep (Code q) x -> Code q r) -> Code q r Source #

Generic Fixity Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Fixity :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Fixity (Code q) x -> Code q Fixity Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Fixity -> (Rep Fixity (Code q) x -> Code q r) -> Code q r Source #

Generic SrcLoc Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep SrcLoc :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep SrcLoc (Code q) x -> Code q SrcLoc Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q SrcLoc -> (Rep SrcLoc (Code q) x -> Code q r) -> Code q r Source #

Generic Location Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Location :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Location (Code q) x -> Code q Location Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Location -> (Rep Location (Code q) x -> Code q r) -> Code q r Source #

Generic RTSStats Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep RTSStats :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep RTSStats (Code q) x -> Code q RTSStats Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q RTSStats -> (Rep RTSStats (Code q) x -> Code q r) -> Code q r Source #

Generic GCDetails Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep GCDetails :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep GCDetails (Code q) x -> Code q GCDetails Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q GCDetails -> (Rep GCDetails (Code q) x -> Code q r) -> Code q r Source #

Generic ByteOrder Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ByteOrder :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ByteOrder (Code q) x -> Code q ByteOrder Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ByteOrder -> (Rep ByteOrder (Code q) x -> Code q r) -> Code q r Source #

Generic StaticPtrInfo Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep StaticPtrInfo :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep StaticPtrInfo (Code q) x -> Code q StaticPtrInfo Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q StaticPtrInfo -> (Rep StaticPtrInfo (Code q) x -> Code q r) -> Code q r Source #

Generic FormatAdjustment Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep FormatAdjustment :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep FormatAdjustment (Code q) x -> Code q FormatAdjustment Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q FormatAdjustment -> (Rep FormatAdjustment (Code q) x -> Code q r) -> Code q r Source #

Generic FormatSign Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep FormatSign :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep FormatSign (Code q) x -> Code q FormatSign Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q FormatSign -> (Rep FormatSign (Code q) x -> Code q r) -> Code q r Source #

Generic FieldFormat Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep FieldFormat :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep FieldFormat (Code q) x -> Code q FieldFormat Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q FieldFormat -> (Rep FieldFormat (Code q) x -> Code q r) -> Code q r Source #

Generic FormatParse Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep FormatParse :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep FormatParse (Code q) x -> Code q FormatParse Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q FormatParse -> (Rep FormatParse (Code q) x -> Code q r) -> Code q r Source #

Generic HandlePosn Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep HandlePosn :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep HandlePosn (Code q) x -> Code q HandlePosn Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q HandlePosn -> (Rep HandlePosn (Code q) x -> Code q r) -> Code q r Source #

Generic PatternMatchFail Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep PatternMatchFail :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep PatternMatchFail (Code q) x -> Code q PatternMatchFail Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q PatternMatchFail -> (Rep PatternMatchFail (Code q) x -> Code q r) -> Code q r Source #

Generic RecSelError Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep RecSelError :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep RecSelError (Code q) x -> Code q RecSelError Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q RecSelError -> (Rep RecSelError (Code q) x -> Code q r) -> Code q r Source #

Generic RecConError Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep RecConError :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep RecConError (Code q) x -> Code q RecConError Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q RecConError -> (Rep RecConError (Code q) x -> Code q r) -> Code q r Source #

Generic RecUpdError Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep RecUpdError :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep RecUpdError (Code q) x -> Code q RecUpdError Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q RecUpdError -> (Rep RecUpdError (Code q) x -> Code q r) -> Code q r Source #

Generic NoMethodError Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep NoMethodError :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep NoMethodError (Code q) x -> Code q NoMethodError Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q NoMethodError -> (Rep NoMethodError (Code q) x -> Code q r) -> Code q r Source #

Generic TypeError Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep TypeError :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep TypeError (Code q) x -> Code q TypeError Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q TypeError -> (Rep TypeError (Code q) x -> Code q r) -> Code q r Source #

Generic NonTermination Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep NonTermination :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep NonTermination (Code q) x -> Code q NonTermination Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q NonTermination -> (Rep NonTermination (Code q) x -> Code q r) -> Code q r Source #

Generic NestedAtomically Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep NestedAtomically :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep NestedAtomically (Code q) x -> Code q NestedAtomically Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q NestedAtomically -> (Rep NestedAtomically (Code q) x -> Code q r) -> Code q r Source #

Generic BlockReason Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep BlockReason :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep BlockReason (Code q) x -> Code q BlockReason Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q BlockReason -> (Rep BlockReason (Code q) x -> Code q r) -> Code q r Source #

Generic ThreadStatus Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ThreadStatus :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ThreadStatus (Code q) x -> Code q ThreadStatus Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ThreadStatus -> (Rep ThreadStatus (Code q) x -> Code q r) -> Code q r Source #

Generic GiveGCStats Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep GiveGCStats :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep GiveGCStats (Code q) x -> Code q GiveGCStats Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q GiveGCStats -> (Rep GiveGCStats (Code q) x -> Code q r) -> Code q r Source #

Generic GCFlags Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep GCFlags :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep GCFlags (Code q) x -> Code q GCFlags Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q GCFlags -> (Rep GCFlags (Code q) x -> Code q r) -> Code q r Source #

Generic ConcFlags Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ConcFlags :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ConcFlags (Code q) x -> Code q ConcFlags Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ConcFlags -> (Rep ConcFlags (Code q) x -> Code q r) -> Code q r Source #

Generic MiscFlags Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep MiscFlags :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep MiscFlags (Code q) x -> Code q MiscFlags Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q MiscFlags -> (Rep MiscFlags (Code q) x -> Code q r) -> Code q r Source #

Generic DebugFlags Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep DebugFlags :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep DebugFlags (Code q) x -> Code q DebugFlags Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q DebugFlags -> (Rep DebugFlags (Code q) x -> Code q r) -> Code q r Source #

Generic DoCostCentres Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep DoCostCentres :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep DoCostCentres (Code q) x -> Code q DoCostCentres Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q DoCostCentres -> (Rep DoCostCentres (Code q) x -> Code q r) -> Code q r Source #

Generic CCFlags Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CCFlags :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CCFlags (Code q) x -> Code q CCFlags Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CCFlags -> (Rep CCFlags (Code q) x -> Code q r) -> Code q r Source #

Generic DoHeapProfile Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep DoHeapProfile :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep DoHeapProfile (Code q) x -> Code q DoHeapProfile Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q DoHeapProfile -> (Rep DoHeapProfile (Code q) x -> Code q r) -> Code q r Source #

Generic ProfFlags Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ProfFlags :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ProfFlags (Code q) x -> Code q ProfFlags Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ProfFlags -> (Rep ProfFlags (Code q) x -> Code q r) -> Code q r Source #

Generic DoTrace Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep DoTrace :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep DoTrace (Code q) x -> Code q DoTrace Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q DoTrace -> (Rep DoTrace (Code q) x -> Code q r) -> Code q r Source #

Generic TraceFlags Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep TraceFlags :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep TraceFlags (Code q) x -> Code q TraceFlags Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q TraceFlags -> (Rep TraceFlags (Code q) x -> Code q r) -> Code q r Source #

Generic TickyFlags Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep TickyFlags :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep TickyFlags (Code q) x -> Code q TickyFlags Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q TickyFlags -> (Rep TickyFlags (Code q) x -> Code q r) -> Code q r Source #

Generic ParFlags Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ParFlags :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ParFlags (Code q) x -> Code q ParFlags Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ParFlags -> (Rep ParFlags (Code q) x -> Code q r) -> Code q r Source #

Generic RTSFlags Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep RTSFlags :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep RTSFlags (Code q) x -> Code q RTSFlags Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q RTSFlags -> (Rep RTSFlags (Code q) x -> Code q r) -> Code q r Source #

Generic Errno Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Errno :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Errno (Code q) x -> Code q Errno Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Errno -> (Rep Errno (Code q) x -> Code q r) -> Code q r Source #

Generic CodingFailureMode Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CodingFailureMode :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CodingFailureMode (Code q) x -> Code q CodingFailureMode Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CodingFailureMode -> (Rep CodingFailureMode (Code q) x -> Code q r) -> Code q r Source #

Generic BlockedIndefinitelyOnMVar Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep BlockedIndefinitelyOnMVar :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep BlockedIndefinitelyOnMVar (Code q) x -> Code q BlockedIndefinitelyOnMVar Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q BlockedIndefinitelyOnMVar -> (Rep BlockedIndefinitelyOnMVar (Code q) x -> Code q r) -> Code q r Source #

Generic BlockedIndefinitelyOnSTM Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep BlockedIndefinitelyOnSTM :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep BlockedIndefinitelyOnSTM (Code q) x -> Code q BlockedIndefinitelyOnSTM Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q BlockedIndefinitelyOnSTM -> (Rep BlockedIndefinitelyOnSTM (Code q) x -> Code q r) -> Code q r Source #

Generic Deadlock Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Deadlock :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Deadlock (Code q) x -> Code q Deadlock Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Deadlock -> (Rep Deadlock (Code q) x -> Code q r) -> Code q r Source #

Generic AllocationLimitExceeded Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep AllocationLimitExceeded :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep AllocationLimitExceeded (Code q) x -> Code q AllocationLimitExceeded Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q AllocationLimitExceeded -> (Rep AllocationLimitExceeded (Code q) x -> Code q r) -> Code q r Source #

Generic AssertionFailed Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep AssertionFailed :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep AssertionFailed (Code q) x -> Code q AssertionFailed Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q AssertionFailed -> (Rep AssertionFailed (Code q) x -> Code q r) -> Code q r Source #

Generic AsyncException Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep AsyncException :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep AsyncException (Code q) x -> Code q AsyncException Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q AsyncException -> (Rep AsyncException (Code q) x -> Code q r) -> Code q r Source #

Generic ArrayException Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ArrayException :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ArrayException (Code q) x -> Code q ArrayException Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ArrayException -> (Rep ArrayException (Code q) x -> Code q r) -> Code q r Source #

Generic FixIOException Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep FixIOException :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep FixIOException (Code q) x -> Code q FixIOException Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q FixIOException -> (Rep FixIOException (Code q) x -> Code q r) -> Code q r Source #

Generic ExitCode Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ExitCode :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ExitCode (Code q) x -> Code q ExitCode Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ExitCode -> (Rep ExitCode (Code q) x -> Code q r) -> Code q r Source #

Generic IOErrorType Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep IOErrorType :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep IOErrorType (Code q) x -> Code q IOErrorType Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q IOErrorType -> (Rep IOErrorType (Code q) x -> Code q r) -> Code q r Source #

Generic BufferMode Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep BufferMode :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep BufferMode (Code q) x -> Code q BufferMode Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q BufferMode -> (Rep BufferMode (Code q) x -> Code q r) -> Code q r Source #

Generic Newline Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Newline :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Newline (Code q) x -> Code q Newline Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Newline -> (Rep Newline (Code q) x -> Code q r) -> Code q r Source #

Generic NewlineMode Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep NewlineMode :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep NewlineMode (Code q) x -> Code q NewlineMode Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q NewlineMode -> (Rep NewlineMode (Code q) x -> Code q r) -> Code q r Source #

Generic IODeviceType Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep IODeviceType :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep IODeviceType (Code q) x -> Code q IODeviceType Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q IODeviceType -> (Rep IODeviceType (Code q) x -> Code q r) -> Code q r Source #

Generic SeekMode Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep SeekMode :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep SeekMode (Code q) x -> Code q SeekMode Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q SeekMode -> (Rep SeekMode (Code q) x -> Code q r) -> Code q r Source #

Generic CodingProgress Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CodingProgress :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CodingProgress (Code q) x -> Code q CodingProgress Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CodingProgress -> (Rep CodingProgress (Code q) x -> Code q r) -> Code q r Source #

Generic BufferState Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep BufferState :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep BufferState (Code q) x -> Code q BufferState Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q BufferState -> (Rep BufferState (Code q) x -> Code q r) -> Code q r Source #

Generic MaskingState Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep MaskingState :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep MaskingState (Code q) x -> Code q MaskingState Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q MaskingState -> (Rep MaskingState (Code q) x -> Code q r) -> Code q r Source #

Generic IOException Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep IOException :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep IOException (Code q) x -> Code q IOException Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q IOException -> (Rep IOException (Code q) x -> Code q r) -> Code q r Source #

Generic LockMode Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep LockMode :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep LockMode (Code q) x -> Code q LockMode Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q LockMode -> (Rep LockMode (Code q) x -> Code q r) -> Code q r Source #

Generic ErrorCall Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ErrorCall :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ErrorCall (Code q) x -> Code q ErrorCall Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ErrorCall -> (Rep ErrorCall (Code q) x -> Code q r) -> Code q r Source #

Generic ArithException Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ArithException :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ArithException (Code q) x -> Code q ArithException Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ArithException -> (Rep ArithException (Code q) x -> Code q r) -> Code q r Source #

Generic All Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep All :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep All (Code q) x -> Code q All Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q All -> (Rep All (Code q) x -> Code q r) -> Code q r Source #

Generic Any Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Any :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Any (Code q) x -> Code q Any Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Any -> (Rep Any (Code q) x -> Code q r) -> Code q r Source #

Generic Fixity Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Fixity :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Fixity (Code q) x -> Code q Fixity Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Fixity -> (Rep Fixity (Code q) x -> Code q r) -> Code q r Source #

Generic Associativity Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Associativity :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Associativity (Code q) x -> Code q Associativity Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Associativity -> (Rep Associativity (Code q) x -> Code q r) -> Code q r Source #

Generic SourceUnpackedness Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep SourceUnpackedness :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep SourceUnpackedness (Code q) x -> Code q SourceUnpackedness Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q SourceUnpackedness -> (Rep SourceUnpackedness (Code q) x -> Code q r) -> Code q r Source #

Generic SourceStrictness Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep SourceStrictness :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep SourceStrictness (Code q) x -> Code q SourceStrictness Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q SourceStrictness -> (Rep SourceStrictness (Code q) x -> Code q r) -> Code q r Source #

Generic DecidedStrictness Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep DecidedStrictness :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep DecidedStrictness (Code q) x -> Code q DecidedStrictness Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q DecidedStrictness -> (Rep DecidedStrictness (Code q) x -> Code q r) -> Code q r Source #

Generic CChar Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CChar :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CChar (Code q) x -> Code q CChar Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CChar -> (Rep CChar (Code q) x -> Code q r) -> Code q r Source #

Generic CSChar Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CSChar :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CSChar (Code q) x -> Code q CSChar Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CSChar -> (Rep CSChar (Code q) x -> Code q r) -> Code q r Source #

Generic CUChar Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CUChar :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CUChar (Code q) x -> Code q CUChar Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CUChar -> (Rep CUChar (Code q) x -> Code q r) -> Code q r Source #

Generic CShort Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CShort :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CShort (Code q) x -> Code q CShort Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CShort -> (Rep CShort (Code q) x -> Code q r) -> Code q r Source #

Generic CUShort Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CUShort :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CUShort (Code q) x -> Code q CUShort Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CUShort -> (Rep CUShort (Code q) x -> Code q r) -> Code q r Source #

Generic CInt Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CInt :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CInt (Code q) x -> Code q CInt Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CInt -> (Rep CInt (Code q) x -> Code q r) -> Code q r Source #

Generic CUInt Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CUInt :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CUInt (Code q) x -> Code q CUInt Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CUInt -> (Rep CUInt (Code q) x -> Code q r) -> Code q r Source #

Generic CLong Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CLong :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CLong (Code q) x -> Code q CLong Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CLong -> (Rep CLong (Code q) x -> Code q r) -> Code q r Source #

Generic CULong Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CULong :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CULong (Code q) x -> Code q CULong Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CULong -> (Rep CULong (Code q) x -> Code q r) -> Code q r Source #

Generic CLLong Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CLLong :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CLLong (Code q) x -> Code q CLLong Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CLLong -> (Rep CLLong (Code q) x -> Code q r) -> Code q r Source #

Generic CULLong Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CULLong :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CULLong (Code q) x -> Code q CULLong Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CULLong -> (Rep CULLong (Code q) x -> Code q r) -> Code q r Source #

Generic CFloat Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CFloat :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CFloat (Code q) x -> Code q CFloat Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CFloat -> (Rep CFloat (Code q) x -> Code q r) -> Code q r Source #

Generic CDouble Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CDouble :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CDouble (Code q) x -> Code q CDouble Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CDouble -> (Rep CDouble (Code q) x -> Code q r) -> Code q r Source #

Generic CPtrdiff Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CPtrdiff :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CPtrdiff (Code q) x -> Code q CPtrdiff Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CPtrdiff -> (Rep CPtrdiff (Code q) x -> Code q r) -> Code q r Source #

Generic CSize Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CSize :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CSize (Code q) x -> Code q CSize Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CSize -> (Rep CSize (Code q) x -> Code q r) -> Code q r Source #

Generic CWchar Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CWchar :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CWchar (Code q) x -> Code q CWchar Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CWchar -> (Rep CWchar (Code q) x -> Code q r) -> Code q r Source #

Generic CSigAtomic Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CSigAtomic :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CSigAtomic (Code q) x -> Code q CSigAtomic Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CSigAtomic -> (Rep CSigAtomic (Code q) x -> Code q r) -> Code q r Source #

Generic CClock Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CClock :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CClock (Code q) x -> Code q CClock Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CClock -> (Rep CClock (Code q) x -> Code q r) -> Code q r Source #

Generic CTime Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CTime :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CTime (Code q) x -> Code q CTime Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CTime -> (Rep CTime (Code q) x -> Code q r) -> Code q r Source #

Generic CUSeconds Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CUSeconds :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CUSeconds (Code q) x -> Code q CUSeconds Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CUSeconds -> (Rep CUSeconds (Code q) x -> Code q r) -> Code q r Source #

Generic CSUSeconds Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CSUSeconds :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CSUSeconds (Code q) x -> Code q CSUSeconds Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CSUSeconds -> (Rep CSUSeconds (Code q) x -> Code q r) -> Code q r Source #

Generic CIntPtr Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CIntPtr :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CIntPtr (Code q) x -> Code q CIntPtr Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CIntPtr -> (Rep CIntPtr (Code q) x -> Code q r) -> Code q r Source #

Generic CUIntPtr Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CUIntPtr :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CUIntPtr (Code q) x -> Code q CUIntPtr Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CUIntPtr -> (Rep CUIntPtr (Code q) x -> Code q r) -> Code q r Source #

Generic CIntMax Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CIntMax :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CIntMax (Code q) x -> Code q CIntMax Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CIntMax -> (Rep CIntMax (Code q) x -> Code q r) -> Code q r Source #

Generic CUIntMax Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep CUIntMax :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep CUIntMax (Code q) x -> Code q CUIntMax Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q CUIntMax -> (Rep CUIntMax (Code q) x -> Code q r) -> Code q r Source #

Generic IOMode Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep IOMode :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep IOMode (Code q) x -> Code q IOMode Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q IOMode -> (Rep IOMode (Code q) x -> Code q r) -> Code q r Source #

Generic Fingerprint Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Fingerprint :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Fingerprint (Code q) x -> Code q Fingerprint Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Fingerprint -> (Rep Fingerprint (Code q) x -> Code q r) -> Code q r Source #

Generic Lexeme Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Lexeme :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Lexeme (Code q) x -> Code q Lexeme Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Lexeme -> (Rep Lexeme (Code q) x -> Code q r) -> Code q r Source #

Generic Number Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Number :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Number (Code q) x -> Code q Number Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Number -> (Rep Number (Code q) x -> Code q r) -> Code q r Source #

Generic FFFormat Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep FFFormat :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep FFFormat (Code q) x -> Code q FFFormat Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q FFFormat -> (Rep FFFormat (Code q) x -> Code q r) -> Code q r Source #

Generic GeneralCategory Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep GeneralCategory :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep GeneralCategory (Code q) x -> Code q GeneralCategory Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q GeneralCategory -> (Rep GeneralCategory (Code q) x -> Code q r) -> Code q r Source #

Generic Version Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep Version :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep Version (Code q) x -> Code q Version Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q Version -> (Rep Version (Code q) x -> Code q r) -> Code q r Source #

Generic SrcLoc Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep SrcLoc :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep SrcLoc (Code q) x -> Code q SrcLoc Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q SrcLoc -> (Rep SrcLoc (Code q) x -> Code q r) -> Code q r Source #

Generic (Maybe a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Maybe a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Maybe a) (Code q) x -> Code q (Maybe a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Maybe a) -> (Rep (Maybe a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Par1 p) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Par1 p) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Par1 p) (Code q) x -> Code q (Par1 p) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Par1 p) -> (Rep (Par1 p) (Code q) x -> Code q r) -> Code q r Source #

Generic (Complex a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Complex a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Complex a) (Code q) x -> Code q (Complex a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Complex a) -> (Rep (Complex a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Min a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Min a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Min a) (Code q) x -> Code q (Min a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Min a) -> (Rep (Min a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Max a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Max a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Max a) (Code q) x -> Code q (Max a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Max a) -> (Rep (Max a) (Code q) x -> Code q r) -> Code q r Source #

Generic (First a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (First a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (First a) (Code q) x -> Code q (First a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (First a) -> (Rep (First a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Last a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Last a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Last a) (Code q) x -> Code q (Last a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Last a) -> (Rep (Last a) (Code q) x -> Code q r) -> Code q r Source #

Generic (WrappedMonoid m) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (WrappedMonoid m) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (WrappedMonoid m) (Code q) x -> Code q (WrappedMonoid m) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (WrappedMonoid m) -> (Rep (WrappedMonoid m) (Code q) x -> Code q r) -> Code q r Source #

Generic (Option a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Option a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Option a) (Code q) x -> Code q (Option a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Option a) -> (Rep (Option a) (Code q) x -> Code q r) -> Code q r Source #

Generic (ArgOrder a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (ArgOrder a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (ArgOrder a) (Code q) x -> Code q (ArgOrder a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (ArgOrder a) -> (Rep (ArgOrder a) (Code q) x -> Code q r) -> Code q r Source #

Generic (OptDescr a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (OptDescr a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (OptDescr a) (Code q) x -> Code q (OptDescr a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (OptDescr a) -> (Rep (OptDescr a) (Code q) x -> Code q r) -> Code q r Source #

Generic (ArgDescr a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (ArgDescr a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (ArgDescr a) (Code q) x -> Code q (ArgDescr a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (ArgDescr a) -> (Rep (ArgDescr a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Identity a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Identity a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Identity a) (Code q) x -> Code q (Identity a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Identity a) -> (Rep (Identity a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Buffer e) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Buffer e) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Buffer e) (Code q) x -> Code q (Buffer e) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Buffer e) -> (Rep (Buffer e) (Code q) x -> Code q r) -> Code q r Source #

Generic (First a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (First a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (First a) (Code q) x -> Code q (First a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (First a) -> (Rep (First a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Last a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Last a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Last a) (Code q) x -> Code q (Last a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Last a) -> (Rep (Last a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Dual a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Dual a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Dual a) (Code q) x -> Code q (Dual a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Dual a) -> (Rep (Dual a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Endo a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Endo a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Endo a) (Code q) x -> Code q (Endo a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Endo a) -> (Rep (Endo a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Sum a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Sum a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Sum a) (Code q) x -> Code q (Sum a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Sum a) -> (Rep (Sum a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Product a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Product a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Product a) (Code q) x -> Code q (Product a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Product a) -> (Rep (Product a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Down a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Down a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Down a) (Code q) x -> Code q (Down a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Down a) -> (Rep (Down a) (Code q) x -> Code q r) -> Code q r Source #

Generic (NonEmpty a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (NonEmpty a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (NonEmpty a) (Code q) x -> Code q (NonEmpty a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (NonEmpty a) -> (Rep (NonEmpty a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Either a b) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Either a b) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Either a b) (Code q) x -> Code q (Either a b) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Either a b) -> (Rep (Either a b) (Code q) x -> Code q r) -> Code q r Source #

Generic (V1 p) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (V1 p) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (V1 p) (Code q) x -> Code q (V1 p) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (V1 p) -> (Rep (V1 p) (Code q) x -> Code q r) -> Code q r Source #

Generic (U1 p) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (U1 p) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (U1 p) (Code q) x -> Code q (U1 p) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (U1 p) -> (Rep (U1 p) (Code q) x -> Code q r) -> Code q r Source #

Generic (a, b) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (a, b) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (a, b) (Code q) x -> Code q (a, b) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (a, b) -> (Rep (a, b) (Code q) x -> Code q r) -> Code q r Source #

Generic (Fixed a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Fixed a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Fixed a) (Code q) x -> Code q (Fixed a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Fixed a) -> (Rep (Fixed a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Arg a b) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Arg a b) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Arg a b) (Code q) x -> Code q (Arg a b) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Arg a b) -> (Rep (Arg a b) (Code q) x -> Code q r) -> Code q r Source #

Generic (Proxy t) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Proxy t) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Proxy t) (Code q) x -> Code q (Proxy t) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Proxy t) -> (Rep (Proxy t) (Code q) x -> Code q r) -> Code q r Source #

Generic (a, b, c) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (a, b, c) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (a, b, c) (Code q) x -> Code q (a, b, c) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (a, b, c) -> (Rep (a, b, c) (Code q) x -> Code q r) -> Code q r Source #

Generic (BufferCodec from to state) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (BufferCodec from to state) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (BufferCodec from to state) (Code q) x -> Code q (BufferCodec from to state) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (BufferCodec from to state) -> (Rep (BufferCodec from to state) (Code q) x -> Code q r) -> Code q r Source #

Generic (Const a b) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Const a b) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Const a b) (Code q) x -> Code q (Const a b) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Const a b) -> (Rep (Const a b) (Code q) x -> Code q r) -> Code q r Source #

Generic (Alt f a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Alt f a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Alt f a) (Code q) x -> Code q (Alt f a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Alt f a) -> (Rep (Alt f a) (Code q) x -> Code q r) -> Code q r Source #

Generic (K1 i c p) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (K1 i c p) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (K1 i c p) (Code q) x -> Code q (K1 i c p) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (K1 i c p) -> (Rep (K1 i c p) (Code q) x -> Code q r) -> Code q r Source #

Generic ((f :+: g) p) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ((f :+: g) p) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ((f :+: g) p) (Code q) x -> Code q ((f :+: g) p) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ((f :+: g) p) -> (Rep ((f :+: g) p) (Code q) x -> Code q r) -> Code q r Source #

Generic ((f :*: g) p) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ((f :*: g) p) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ((f :*: g) p) (Code q) x -> Code q ((f :*: g) p) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ((f :*: g) p) -> (Rep ((f :*: g) p) (Code q) x -> Code q r) -> Code q r Source #

Generic (a, b, c, d) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (a, b, c, d) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (a, b, c, d) (Code q) x -> Code q (a, b, c, d) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (a, b, c, d) -> (Rep (a, b, c, d) (Code q) x -> Code q r) -> Code q r Source #

Generic (Product f g a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Product f g a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Product f g a) (Code q) x -> Code q (Product f g a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Product f g a) -> (Rep (Product f g a) (Code q) x -> Code q r) -> Code q r Source #

Generic (Sum f g a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Sum f g a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Sum f g a) (Code q) x -> Code q (Sum f g a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Sum f g a) -> (Rep (Sum f g a) (Code q) x -> Code q r) -> Code q r Source #

Generic (M1 i c f p) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (M1 i c f p) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (M1 i c f p) (Code q) x -> Code q (M1 i c f p) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (M1 i c f p) -> (Rep (M1 i c f p) (Code q) x -> Code q r) -> Code q r Source #

Generic ((f :.: g) p) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep ((f :.: g) p) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep ((f :.: g) p) (Code q) x -> Code q ((f :.: g) p) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q ((f :.: g) p) -> (Rep ((f :.: g) p) (Code q) x -> Code q r) -> Code q r Source #

Generic (a, b, c, d, e) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (a, b, c, d, e) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (a, b, c, d, e) (Code q) x -> Code q (a, b, c, d, e) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (a, b, c, d, e) -> (Rep (a, b, c, d, e) (Code q) x -> Code q r) -> Code q r Source #

Generic (Compose f g a) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (Compose f g a) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (Compose f g a) (Code q) x -> Code q (Compose f g a) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (Compose f g a) -> (Rep (Compose f g a) (Code q) x -> Code q r) -> Code q r Source #

Generic (a, b, c, d, e, f) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep (a, b, c, d, e, f) :: (Type -> Type) -> Type -> Type Source #

Methods

to :: forall (q :: Type -> Type) x. Quote q => Rep (a, b, c, d, e, f) (Code q) x -> Code q (a, b, c, d, e, f) Source #

from :: forall (q :: Type -> Type) x r. Quote q => Code q (a, b, c, d, e, f) -> (Rep (a, b, c, d, e, f) (Code q) x -> Code q r) -> Code q r Source #

class Generic1 (f :: k -> Type) where Source #

Associated Types

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

type Rep1 f = Translate (Rep1 f)

Methods

to1 :: Quote q => Rep1 f (Code q) x -> Code q (f x) Source #

from1 :: Quote q => Code q (f x) -> (Rep1 f (Code q) x -> Code q r) -> Code q r Source #

Instances

Instances details
Generic1 [] Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 [] :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 [] (Code q) x -> Code q [x] Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q [x] -> (Rep1 [] (Code q) x -> Code q r) -> Code q r Source #

Generic1 Maybe Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Maybe :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Maybe (Code q) x -> Code q (Maybe x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Maybe x) -> (Rep1 Maybe (Code q) x -> Code q r) -> Code q r Source #

Generic1 Min Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Min :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Min (Code q) x -> Code q (Min x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Min x) -> (Rep1 Min (Code q) x -> Code q r) -> Code q r Source #

Generic1 Max Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Max :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Max (Code q) x -> Code q (Max x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Max x) -> (Rep1 Max (Code q) x -> Code q r) -> Code q r Source #

Generic1 First Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 First :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 First (Code q) x -> Code q (First x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (First x) -> (Rep1 First (Code q) x -> Code q r) -> Code q r Source #

Generic1 Last Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Last :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Last (Code q) x -> Code q (Last x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Last x) -> (Rep1 Last (Code q) x -> Code q r) -> Code q r Source #

Generic1 WrappedMonoid Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 WrappedMonoid :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 WrappedMonoid (Code q) x -> Code q (WrappedMonoid x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (WrappedMonoid x) -> (Rep1 WrappedMonoid (Code q) x -> Code q r) -> Code q r Source #

Generic1 Option Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Option :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Option (Code q) x -> Code q (Option x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Option x) -> (Rep1 Option (Code q) x -> Code q r) -> Code q r Source #

Generic1 Identity Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Identity :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Identity (Code q) x -> Code q (Identity x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Identity x) -> (Rep1 Identity (Code q) x -> Code q r) -> Code q r Source #

Generic1 First Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 First :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 First (Code q) x -> Code q (First x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (First x) -> (Rep1 First (Code q) x -> Code q r) -> Code q r Source #

Generic1 Last Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Last :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Last (Code q) x -> Code q (Last x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Last x) -> (Rep1 Last (Code q) x -> Code q r) -> Code q r Source #

Generic1 Dual Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Dual :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Dual (Code q) x -> Code q (Dual x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Dual x) -> (Rep1 Dual (Code q) x -> Code q r) -> Code q r Source #

Generic1 Sum Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Sum :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Sum (Code q) x -> Code q (Sum x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Sum x) -> (Rep1 Sum (Code q) x -> Code q r) -> Code q r Source #

Generic1 Product Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Product :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Product (Code q) x -> Code q (Product x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Product x) -> (Rep1 Product (Code q) x -> Code q r) -> Code q r Source #

Generic1 Down Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Down :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 Down (Code q) x -> Code q (Down x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Down x) -> (Rep1 Down (Code q) x -> Code q r) -> Code q r Source #

Generic1 NonEmpty Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 NonEmpty :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 NonEmpty (Code q) x -> Code q (NonEmpty x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (NonEmpty x) -> (Rep1 NonEmpty (Code q) x -> Code q r) -> Code q r Source #

Generic1 (Either a :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 (Either a) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 (Either a) (Code q) x -> Code q (Either a x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Either a x) -> (Rep1 (Either a) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,) a :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,) a) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 ((,) a) (Code q) x -> Code q (a, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (a, x) -> (Rep1 ((,) a) (Code q) x -> Code q r) -> Code q r Source #

Generic1 (Arg a :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 (Arg a) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 (Arg a) (Code q) x -> Code q (Arg a x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Arg a x) -> (Rep1 (Arg a) (Code q) x -> Code q r) -> Code q r Source #

Generic1 (Proxy :: k -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 Proxy :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 Proxy (Code q) x -> Code q (Proxy x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (Proxy x) -> (Rep1 Proxy (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,) a b :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,) a b) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 ((,,) a b) (Code q) x -> Code q (a, b, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (a, b, x) -> (Rep1 ((,,) a b) (Code q) x -> Code q r) -> Code q r Source #

Generic1 (Const a :: k -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 (Const a) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 (Const a) (Code q) x -> Code q (Const a x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (Const a x) -> (Rep1 (Const a) (Code q) x -> Code q r) -> Code q r Source #

Generic1 (Alt f :: k -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 (Alt f) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 (Alt f) (Code q) x -> Code q (Alt f x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (Alt f x) -> (Rep1 (Alt f) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,) a b c :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,) a b c) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 ((,,,) a b c) (Code q) x -> Code q (a, b, c, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (a, b, c, x) -> (Rep1 ((,,,) a b c) (Code q) x -> Code q r) -> Code q r Source #

Generic1 (Product f g :: k -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 (Product f g) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 (Product f g) (Code q) x -> Code q (Product f g x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (Product f g x) -> (Rep1 (Product f g) (Code q) x -> Code q r) -> Code q r Source #

Generic1 (Sum f g :: k -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 (Sum f g) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 (Sum f g) (Code q) x -> Code q (Sum f g x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (Sum f g x) -> (Rep1 (Sum f g) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,) a b c d :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,) a b c d) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 ((,,,,) a b c d) (Code q) x -> Code q (a, b, c, d, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (a, b, c, d, x) -> (Rep1 ((,,,,) a b c d) (Code q) x -> Code q r) -> Code q r Source #

Generic1 (Compose f g :: k1 -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 (Compose f g) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 (Compose f g) (Code q) x -> Code q (Compose f g x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (Compose f g x) -> (Rep1 (Compose f g) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,) a b c d e :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,) a b c d e) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 ((,,,,,) a b c d e) (Code q) x -> Code q (a, b, c, d, e, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (a, b, c, d, e, x) -> (Rep1 ((,,,,,) a b c d e) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,) a b c d e f :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,) a b c d e f) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 ((,,,,,,) a b c d e f) (Code q) x -> Code q (a, b, c, d, e, f, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (a, b, c, d, e, f, x) -> (Rep1 ((,,,,,,) a b c d e f) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,) a b c d e f g :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,) a b c d e f g) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 ((,,,,,,,) a b c d e f g) (Code q) x -> Code q (a, b, c, d, e, f, g, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (a, b, c, d, e, f, g, x) -> (Rep1 ((,,,,,,,) a b c d e f g) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,,) a b c d e f g h :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,) a b c d e f g h) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 ((,,,,,,,,) a b c d e f g h) (Code q) x -> Code q (a, b, c, d, e, f, g, h, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (a, b, c, d, e, f, g, h, x) -> (Rep1 ((,,,,,,,,) a b c d e f g h) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,,,) a b c d e f g h i :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,) a b c d e f g h i) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 ((,,,,,,,,,) a b c d e f g h i) (Code q) x -> Code q (a, b, c, d, e, f, g, h, i, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (a, b, c, d, e, f, g, h, i, x) -> (Rep1 ((,,,,,,,,,) a b c d e f g h i) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,,,,) a b c d e f g h i j :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,) a b c d e f g h i j) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k). Quote q => Rep1 ((,,,,,,,,,,) a b c d e f g h i j) (Code q) x -> Code q (a, b, c, d, e, f, g, h, i, j, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k) r. Quote q => Code q (a, b, c, d, e, f, g, h, i, j, x) -> (Rep1 ((,,,,,,,,,,) a b c d e f g h i j) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,,,,,) a b c d e f g h i j k :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) (Code q) x -> Code q (a, b, c, d, e, f, g, h, i, j, k, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (a, b, c, d, e, f, g, h, i, j, k, x) -> (Rep1 ((,,,,,,,,,,,) a b c d e f g h i j k) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,,,,,,) a b c d e f g h i j k l :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) (Code q) x -> Code q (a, b, c, d, e, f, g, h, i, j, k, l, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (a, b, c, d, e, f, g, h, i, j, k, l, x) -> (Rep1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) (Code q) x -> Code q (a, b, c, d, e, f, g, h, i, j, k, l, m, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (a, b, c, d, e, f, g, h, i, j, k, l, m, x) -> (Rep1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) (Code q) x -> Code q (a, b, c, d, e, f, g, h, i, j, k, l, m, n, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (a, b, c, d, e, f, g, h, i, j, k, l, m, n, x) -> (Rep1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 ((,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o) (Code q) x -> Code q (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, x) -> (Rep1 ((,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q :: Type -> Type) (x :: k0). Quote q => Rep1 ((,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p) (Code q) x -> Code q (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, x) Source #

from1 :: forall (q :: Type -> Type) (x :: k0) r. Quote q => Code q (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, x) -> (Rep1 ((,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p) (Code q) x -> Code q r) -> Code q r Source #

Generic1 ((,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q) (Code q0) x -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, x) Source #

from1 :: forall (q0 :: Type -> Type) (x :: k0) r. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, x) -> (Rep1 ((,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q) (Code q0) x -> Code q0 r) -> Code q0 r Source #

Generic1 ((,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r) (Code q0) x -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, x) Source #

from1 :: forall (q0 :: Type -> Type) (x :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, x) -> (Rep1 ((,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r) (Code q0) x -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s) (Code q0) x -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, x) Source #

from1 :: forall (q0 :: Type -> Type) (x :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, x) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s) (Code q0) x -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t) (Code q0) x -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, x) Source #

from1 :: forall (q0 :: Type -> Type) (x :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, x) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t) (Code q0) x -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u) (Code q0) x -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, x) Source #

from1 :: forall (q0 :: Type -> Type) (x :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, x) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u) (Code q0) x -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v) (Code q0) x -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, x) Source #

from1 :: forall (q0 :: Type -> Type) (x :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, x) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v) (Code q0) x -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w) (Code q0) x -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source #

from1 :: forall (q0 :: Type -> Type) (x :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w) (Code q0) x -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x0 :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x) (Code q0) x0 -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, x0) Source #

from1 :: forall (q0 :: Type -> Type) (x0 :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, x0) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x) (Code q0) x0 -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x0 :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y) (Code q0) x0 -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, x0) Source #

from1 :: forall (q0 :: Type -> Type) (x0 :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, x0) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y) (Code q0) x0 -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x0 :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z) (Code q0) x0 -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, x0) Source #

from1 :: forall (q0 :: Type -> Type) (x0 :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, x0) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z) (Code q0) x0 -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26 :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x0 :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26) (Code q0) x0 -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, x0) Source #

from1 :: forall (q0 :: Type -> Type) (x0 :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, x0) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26) (Code q0) x0 -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26 t27 :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26 t27) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x0 :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26 t27) (Code q0) x0 -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, x0) Source #

from1 :: forall (q0 :: Type -> Type) (x0 :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, x0) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26 t27) (Code q0) x0 -> Code q0 r0) -> Code q0 r0 Source #

Generic1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26 t27 t28 :: Type -> Type) Source # 
Instance details

Defined in Staged.GHC.Generics.Instances

Associated Types

type Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26 t27 t28) :: (Type -> Type) -> k -> Type Source #

Methods

to1 :: forall (q0 :: Type -> Type) (x0 :: k0). Quote q0 => Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26 t27 t28) (Code q0) x0 -> Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, x0) Source #

from1 :: forall (q0 :: Type -> Type) (x0 :: k0) r0. Quote q0 => Code q0 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, x0) -> (Rep1 ((,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z t26 t27 t28) (Code q0) x0 -> Code q0 r0) -> Code q0 r0 Source #

TH Types

data Code (m :: Type -> Type) (a :: TYPE r) #

class Monad m => Quote (m :: Type -> Type) #

The Quote class implements the minimal interface which is necessary for desugaring quotations.

  • The Monad m superclass is needed to stitch together the different AST fragments.
  • newName is used when desugaring binding structures such as lambdas to generate fresh names.

Therefore the type of an untyped quotation in GHC is `Quote m => m Exp`

For many years the type of a quotation was fixed to be `Q Exp` but by more precisely specifying the minimal interface it enables the Exp to be extracted purely from the quotation without interacting with Q.

Minimal complete definition

newName

Instances

Instances details
Quote IO 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

newName :: String -> IO Name #

Quote Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

newName :: String -> Q Name #

Utilities

type family Translate (f :: k -> Type) :: (Type -> Type) -> k -> Type where ... Source #

Translate GHC.Generics Rep type into our Rep type.

Equations

Translate (M1 i c f) = M2 i c (Translate f) 
Translate (K1 R c) = K2 c 
Translate (f :+: g) = Translate f :++: Translate g 
Translate (f :*: g) = Translate f :**: Translate g 
Translate (Rec1 f) = Par2 :@@: f 
Translate Par1 = Par2 
Translate U1 = U2 
Translate V1 = V2 
Translate (f :.: g) = TranslateComp (Par2 :@@: f) g 
Translate x = TypeError ('Text "Translate error: " :<>: 'ShowType x)