th-desugar-1.12: Functions to desugar Template Haskell
Copyright(C) 2014 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TH.Desugar

Description

Desugars full Template Haskell syntax into a smaller core syntax for further processing.

Synopsis

Desugared data types

data DExp Source #

Corresponds to TH's Exp type. Note that DLamE takes names, not patterns.

Instances

Instances details
Eq DExp Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Data DExp Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DExp -> c DExp #

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

toConstr :: DExp -> Constr #

dataTypeOf :: DExp -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DExp Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DExp -> ShowS #

show :: DExp -> String #

showList :: [DExp] -> ShowS #

Generic DExp Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DExp :: Type -> Type #

Methods

from :: DExp -> Rep DExp x #

to :: Rep DExp x -> DExp #

Lift DExp Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DExp -> Q Exp #

liftTyped :: DExp -> Q (TExp DExp) #

Desugar Exp DExp Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

Methods

desugar :: DsMonad q => Exp -> q DExp Source #

sweeten :: DExp -> Exp Source #

type Rep DExp Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DExp = D1 ('MetaData "DExp" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (((C1 ('MetaCons "DVarE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "DConE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "DLitE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lit)) :+: (C1 ('MetaCons "DAppE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp)) :+: C1 ('MetaCons "DAppTypeE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType))))) :+: ((C1 ('MetaCons "DLamE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp)) :+: C1 ('MetaCons "DCaseE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DMatch]))) :+: (C1 ('MetaCons "DLetE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DLetDec]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp)) :+: (C1 ('MetaCons "DSigE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType)) :+: C1 ('MetaCons "DStaticE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp))))))

data DLetDec Source #

Declarations as used in a let statement.

Instances

Instances details
Eq DLetDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Data DLetDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DLetDec -> c DLetDec #

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

toConstr :: DLetDec -> Constr #

dataTypeOf :: DLetDec -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DLetDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DLetDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DLetDec :: Type -> Type #

Methods

from :: DLetDec -> Rep DLetDec x #

to :: Rep DLetDec x -> DLetDec #

Lift DLetDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DLetDec -> Q Exp #

liftTyped :: DLetDec -> Q (TExp DLetDec) #

type Rep DLetDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DPat Source #

Corresponds to TH's Pat type.

Instances

Instances details
Eq DPat Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Data DPat Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DPat -> c DPat #

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

toConstr :: DPat -> Constr #

dataTypeOf :: DPat -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DPat Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DPat -> ShowS #

show :: DPat -> String #

showList :: [DPat] -> ShowS #

Generic DPat Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DPat :: Type -> Type #

Methods

from :: DPat -> Rep DPat x #

to :: Rep DPat x -> DPat #

Lift DPat Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DPat -> Q Exp #

liftTyped :: DPat -> Q (TExp DPat) #

type Rep DPat Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DType Source #

Corresponds to TH's Type type, used to represent types and kinds.

Instances

Instances details
Eq DType Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Data DType Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DType -> c DType #

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

toConstr :: DType -> Constr #

dataTypeOf :: DType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DType Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DType -> ShowS #

show :: DType -> String #

showList :: [DType] -> ShowS #

Generic DType Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DType :: Type -> Type #

Methods

from :: DType -> Rep DType x #

to :: Rep DType x -> DType #

Lift DType Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DType -> Q Exp #

liftTyped :: DType -> Q (TExp DType) #

Desugar Type DType Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

Desugar Cxt DCxt Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

Methods

desugar :: DsMonad q => Cxt -> q DCxt Source #

sweeten :: DCxt -> Cxt Source #

type Rep DType Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DType = D1 ('MetaData "DType" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (((C1 ('MetaCons "DForallT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DForallTelescope) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType)) :+: C1 ('MetaCons "DConstrainedT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DCxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType))) :+: (C1 ('MetaCons "DAppT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType)) :+: (C1 ('MetaCons "DAppKindT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DKind)) :+: C1 ('MetaCons "DSigT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DKind))))) :+: ((C1 ('MetaCons "DVarT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "DConT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "DArrowT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DLitT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TyLit)) :+: C1 ('MetaCons "DWildCardT" 'PrefixI 'False) (U1 :: Type -> Type)))))

data DForallTelescope Source #

The type variable binders in a forall.

Constructors

DForallVis [DTyVarBndrUnit]

A visible forall (e.g., forall a -> {...}). These do not have any notion of specificity, so we use () as a placeholder value in the DTyVarBndrs.

DForallInvis [DTyVarBndrSpec]

An invisible forall (e.g., forall a {b} c -> {...}), where each binder has a Specificity.

Instances

Instances details
Eq DForallTelescope Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data DForallTelescope Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DForallTelescope -> c DForallTelescope #

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

toConstr :: DForallTelescope -> Constr #

dataTypeOf :: DForallTelescope -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DForallTelescope Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DForallTelescope Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DForallTelescope :: Type -> Type #

Lift DForallTelescope Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DForallTelescope Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DForallTelescope = D1 ('MetaData "DForallTelescope" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (C1 ('MetaCons "DForallVis" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DTyVarBndrUnit])) :+: C1 ('MetaCons "DForallInvis" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DTyVarBndrSpec])))

type DKind = DType Source #

Kinds are types. Corresponds to TH's Kind

type DCxt = [DPred] Source #

Corresponds to TH's Cxt

type DPred = DType Source #

Predicates are types. Corresponds to TH's Pred

data DTyVarBndr flag Source #

Corresponds to TH's TyVarBndr

Constructors

DPlainTV Name flag 
DKindedTV Name flag DKind 

Instances

Instances details
Functor DTyVarBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Desugar TyVarBndrUnit DTyVarBndrUnit Source #

This instance monomorphizes the flag parameter of DTyVarBndr since pre-9.0 versions of GHC do not equip TyVarBndr with a flag type parameter. There is also a corresponding instance for TyVarBndrSpec/DTyVarBndrSpec.

Instance details

Defined in Language.Haskell.TH.Desugar

Desugar TyVarBndrSpec DTyVarBndrSpec Source #

This instance monomorphizes the flag parameter of DTyVarBndr since pre-9.0 versions of GHC do not equip TyVarBndr with a flag type parameter. There is also a corresponding instance for TyVarBndrUnit/DTyVarBndrUnit.

Instance details

Defined in Language.Haskell.TH.Desugar

Lift flag => Lift (DTyVarBndr flag :: Type) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DTyVarBndr flag -> Q Exp #

liftTyped :: DTyVarBndr flag -> Q (TExp (DTyVarBndr flag)) #

Eq flag => Eq (DTyVarBndr flag) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

(==) :: DTyVarBndr flag -> DTyVarBndr flag -> Bool #

(/=) :: DTyVarBndr flag -> DTyVarBndr flag -> Bool #

Data flag => Data (DTyVarBndr flag) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DTyVarBndr flag -> c (DTyVarBndr flag) #

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

toConstr :: DTyVarBndr flag -> Constr #

dataTypeOf :: DTyVarBndr flag -> DataType #

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

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

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

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

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

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

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

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

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

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

Show flag => Show (DTyVarBndr flag) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DTyVarBndr flag -> ShowS #

show :: DTyVarBndr flag -> String #

showList :: [DTyVarBndr flag] -> ShowS #

Generic (DTyVarBndr flag) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep (DTyVarBndr flag) :: Type -> Type #

Methods

from :: DTyVarBndr flag -> Rep (DTyVarBndr flag) x #

to :: Rep (DTyVarBndr flag) x -> DTyVarBndr flag #

type Rep (DTyVarBndr flag) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type DTyVarBndrSpec = DTyVarBndr Specificity Source #

Corresponds to TH's TyVarBndrSpec

type DTyVarBndrUnit = DTyVarBndr () Source #

Corresponds to TH's TyVarBndrUnit

data Specificity #

Determines how a TyVarBndr interacts with visible type application.

Constructors

SpecifiedSpec

a. Eligible for visible type application.

InferredSpec

{a}. Not eligible for visible type application.

Instances

Instances details
Eq Specificity 
Instance details

Defined in Language.Haskell.TH.Datatype.TyVarBndr

Data Specificity 
Instance details

Defined in Language.Haskell.TH.Datatype.TyVarBndr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Specificity -> c Specificity #

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

toConstr :: Specificity -> Constr #

dataTypeOf :: Specificity -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Specificity 
Instance details

Defined in Language.Haskell.TH.Datatype.TyVarBndr

Show Specificity 
Instance details

Defined in Language.Haskell.TH.Datatype.TyVarBndr

Generic Specificity 
Instance details

Defined in Language.Haskell.TH.Datatype.TyVarBndr

Associated Types

type Rep Specificity :: Type -> Type #

Lift Specificity Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Desugar TyVarBndrSpec DTyVarBndrSpec Source #

This instance monomorphizes the flag parameter of DTyVarBndr since pre-9.0 versions of GHC do not equip TyVarBndr with a flag type parameter. There is also a corresponding instance for TyVarBndrUnit/DTyVarBndrUnit.

Instance details

Defined in Language.Haskell.TH.Desugar

type Rep Specificity 
Instance details

Defined in Language.Haskell.TH.Datatype.TyVarBndr

type Rep Specificity = D1 ('MetaData "Specificity" "Language.Haskell.TH.Datatype.TyVarBndr" "th-abstraction-0.4.2.0-CPMLTlyMgmr6dbHxHL95CG" 'False) (C1 ('MetaCons "SpecifiedSpec" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InferredSpec" 'PrefixI 'False) (U1 :: Type -> Type))

data DMatch Source #

Corresponds to TH's Match type.

Constructors

DMatch DPat DExp 

Instances

Instances details
Eq DMatch Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Data DMatch Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DMatch -> c DMatch #

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

toConstr :: DMatch -> Constr #

dataTypeOf :: DMatch -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DMatch Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DMatch Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DMatch :: Type -> Type #

Methods

from :: DMatch -> Rep DMatch x #

to :: Rep DMatch x -> DMatch #

Lift DMatch Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DMatch -> Q Exp #

liftTyped :: DMatch -> Q (TExp DMatch) #

type Rep DMatch Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DMatch = D1 ('MetaData "DMatch" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (C1 ('MetaCons "DMatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DPat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp)))

data DClause Source #

Corresponds to TH's Clause type.

Constructors

DClause [DPat] DExp 

Instances

Instances details
Eq DClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Data DClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DClause -> c DClause #

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

toConstr :: DClause -> Constr #

dataTypeOf :: DClause -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DClause :: Type -> Type #

Methods

from :: DClause -> Rep DClause x #

to :: Rep DClause x -> DClause #

Lift DClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DClause -> Q Exp #

liftTyped :: DClause -> Q (TExp DClause) #

type Rep DClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DClause = D1 ('MetaData "DClause" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (C1 ('MetaCons "DClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DPat]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp)))

data DDec Source #

Corresponds to TH's Dec type.

Instances

Instances details
Eq DDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Data DDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DDec -> c DDec #

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

toConstr :: DDec -> Constr #

dataTypeOf :: DDec -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DDec -> ShowS #

show :: DDec -> String #

showList :: [DDec] -> ShowS #

Generic DDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DDec :: Type -> Type #

Methods

from :: DDec -> Rep DDec x #

to :: Rep DDec x -> DDec #

Lift DDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DDec -> Q Exp #

liftTyped :: DDec -> Q (TExp DDec) #

Desugar [Dec] [DDec] Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

Methods

desugar :: DsMonad q => [Dec] -> q [DDec] Source #

sweeten :: [DDec] -> [Dec] Source #

type Rep DDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DDec = D1 ('MetaData "DDec" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) ((((C1 ('MetaCons "DLetDec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DLetDec)) :+: C1 ('MetaCons "DDataD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NewOrData) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DCxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DTyVarBndrUnit]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DKind))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DCon]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DDerivClause]))))) :+: (C1 ('MetaCons "DTySynD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DTyVarBndrUnit]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType))) :+: C1 ('MetaCons "DClassD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DCxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DTyVarBndrUnit]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FunDep]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DDec])))))) :+: ((C1 ('MetaCons "DInstanceD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Overlap)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [DTyVarBndrUnit]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DCxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DDec])))) :+: C1 ('MetaCons "DForeignD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DForeign))) :+: (C1 ('MetaCons "DOpenTypeFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DTypeFamilyHead)) :+: C1 ('MetaCons "DClosedTypeFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DTypeFamilyHead) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DTySynEqn]))))) :+: (((C1 ('MetaCons "DDataFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DTyVarBndrUnit]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DKind)))) :+: C1 ('MetaCons "DDataInstD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NewOrData) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DCxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [DTyVarBndrUnit])))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DKind))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DCon]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DDerivClause]))))) :+: (C1 ('MetaCons "DTySynInstD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DTySynEqn)) :+: C1 ('MetaCons "DRoleAnnotD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Role])))) :+: ((C1 ('MetaCons "DStandaloneDerivD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DDerivStrategy)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [DTyVarBndrUnit]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DCxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType))) :+: C1 ('MetaCons "DDefaultSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType))) :+: (C1 ('MetaCons "DPatSynD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynArgs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DPatSynDir) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DPat))) :+: (C1 ('MetaCons "DPatSynSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DPatSynType)) :+: C1 ('MetaCons "DKiSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DKind)))))))

data DDerivClause Source #

Corresponds to TH's DerivClause type.

Instances

Instances details
Eq DDerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data DDerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DDerivClause -> c DDerivClause #

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

toConstr :: DDerivClause -> Constr #

dataTypeOf :: DDerivClause -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DDerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DDerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DDerivClause :: Type -> Type #

Lift DDerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DDerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DDerivClause = D1 ('MetaData "DDerivClause" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (C1 ('MetaCons "DDerivClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DDerivStrategy)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DCxt)))

data DDerivStrategy Source #

Corresponds to TH's DerivStrategy type.

Constructors

DStockStrategy

A "standard" derived instance

DAnyclassStrategy
-XDeriveAnyClass
DNewtypeStrategy
-XGeneralizedNewtypeDeriving
DViaStrategy DType
-XDerivingVia

Instances

Instances details
Eq DDerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data DDerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DDerivStrategy -> c DDerivStrategy #

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

toConstr :: DDerivStrategy -> Constr #

dataTypeOf :: DDerivStrategy -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DDerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DDerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DDerivStrategy :: Type -> Type #

Lift DDerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DDerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DDerivStrategy = D1 ('MetaData "DDerivStrategy" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) ((C1 ('MetaCons "DStockStrategy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DAnyclassStrategy" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DNewtypeStrategy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DViaStrategy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType))))

data DPatSynDir Source #

Corresponds to TH's PatSynDir type

Constructors

DUnidir
pattern P x {<-} p
DImplBidir
pattern P x {=} p
DExplBidir [DClause]
pattern P x {<-} p where P x = e

Instances

Instances details
Eq DPatSynDir Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data DPatSynDir Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DPatSynDir -> c DPatSynDir #

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

toConstr :: DPatSynDir -> Constr #

dataTypeOf :: DPatSynDir -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DPatSynDir Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DPatSynDir Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DPatSynDir :: Type -> Type #

Lift DPatSynDir Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DPatSynDir Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DPatSynDir = D1 ('MetaData "DPatSynDir" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (C1 ('MetaCons "DUnidir" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DImplBidir" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DExplBidir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DClause]))))

type DPatSynType = DType Source #

Corresponds to TH's PatSynType type

data Overlap #

Varieties of allowed instance overlap.

Constructors

Overlappable

May be overlapped by more specific instances

Overlapping

May overlap a more general instance

Overlaps

Both Overlapping and Overlappable

Incoherent

Both Overlappable and Overlappable, and pick an arbitrary one if multiple choices are available.

Instances

Instances details
Eq Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

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

Data Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Overlap -> c Overlap #

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

toConstr :: Overlap -> Constr #

dataTypeOf :: Overlap -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type #

Methods

from :: Overlap -> Rep Overlap x #

to :: Rep Overlap x -> Overlap #

type Rep Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Overlap = D1 ('MetaData "Overlap" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "Overlappable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Overlapping" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Overlaps" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Incoherent" 'PrefixI 'False) (U1 :: Type -> Type)))

data PatSynArgs #

A pattern synonym's argument type.

Constructors

PrefixPatSyn [Name]
pattern P {x y z} = p
InfixPatSyn Name Name
pattern {x P y} = p
RecordPatSyn [Name]
pattern P { {x,y,z} } = p

Instances

Instances details
Eq PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Data PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynArgs -> c PatSynArgs #

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

toConstr :: PatSynArgs -> Constr #

dataTypeOf :: PatSynArgs -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Show PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type #

Ppr PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Ppr

Methods

ppr :: PatSynArgs -> Doc #

ppr_list :: [PatSynArgs] -> Doc #

type Rep PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

data NewOrData Source #

Is it a newtype or a data type?

Constructors

Newtype 
Data 

Instances

Instances details
Eq NewOrData Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data NewOrData Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewOrData -> c NewOrData #

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

toConstr :: NewOrData -> Constr #

dataTypeOf :: NewOrData -> DataType #

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

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

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

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

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

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

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

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

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

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

Show NewOrData Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic NewOrData Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep NewOrData :: Type -> Type #

Lift NewOrData Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep NewOrData Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep NewOrData = D1 ('MetaData "NewOrData" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (C1 ('MetaCons "Newtype" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Data" 'PrefixI 'False) (U1 :: Type -> Type))

data DTypeFamilyHead Source #

Corresponds to TH's TypeFamilyHead type

Instances

Instances details
Eq DTypeFamilyHead Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data DTypeFamilyHead Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DTypeFamilyHead -> c DTypeFamilyHead #

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

toConstr :: DTypeFamilyHead -> Constr #

dataTypeOf :: DTypeFamilyHead -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DTypeFamilyHead Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DTypeFamilyHead Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DTypeFamilyHead :: Type -> Type #

Lift DTypeFamilyHead Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DTypeFamilyHead Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DFamilyResultSig Source #

Corresponds to TH's FamilyResultSig type

Instances

Instances details
Eq DFamilyResultSig Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data DFamilyResultSig Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DFamilyResultSig -> c DFamilyResultSig #

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

toConstr :: DFamilyResultSig -> Constr #

dataTypeOf :: DFamilyResultSig -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DFamilyResultSig Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DFamilyResultSig Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DFamilyResultSig :: Type -> Type #

Lift DFamilyResultSig Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DFamilyResultSig Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DFamilyResultSig = D1 ('MetaData "DFamilyResultSig" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (C1 ('MetaCons "DNoSig" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DKindSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DKind)) :+: C1 ('MetaCons "DTyVarSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DTyVarBndrUnit))))

data InjectivityAnn #

Injectivity annotation

Constructors

InjectivityAnn Name [Name] 

Instances

Instances details
Eq InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Data InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn -> c InjectivityAnn #

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

toConstr :: InjectivityAnn -> Constr #

dataTypeOf :: InjectivityAnn -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Show InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: Type -> Type #

Ppr InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Ppr

type Rep InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep InjectivityAnn = D1 ('MetaData "InjectivityAnn" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "InjectivityAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])))

data DCon Source #

Corresponds to TH's Con type. Unlike Con, all DCons reflect GADT syntax. This is beneficial for th-desugar's since it means that all data type declarations can support explicit return kinds, so one does not need to represent them with something like Maybe DKind, since Haskell98-style data declaration syntax isn't used. Accordingly, there are some differences between DCon and Con to keep in mind:

  • Unlike ForallC, where the meaning of the TyVarBndrs changes depending on whether it's followed by GadtC/RecGadtC or not, the meaning of the DTyVarBndrs in a DCon is always the same: it is the list of universally and existentially quantified type variables. Note that it is not guaranteed that one set of type variables will appear before the other.
  • A DCon always has an explicit return type.

Constructors

DCon [DTyVarBndrSpec] DCxt Name DConFields DType

The GADT result type

Instances

Instances details
Eq DCon Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Data DCon Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DCon -> c DCon #

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

toConstr :: DCon -> Constr #

dataTypeOf :: DCon -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DCon Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DCon -> ShowS #

show :: DCon -> String #

showList :: [DCon] -> ShowS #

Generic DCon Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DCon :: Type -> Type #

Methods

from :: DCon -> Rep DCon x #

to :: Rep DCon x -> DCon #

Lift DCon Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DCon -> Q Exp #

liftTyped :: DCon -> Q (TExp DCon) #

type Rep DCon Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DConFields Source #

A list of fields either for a standard data constructor or a record data constructor.

Instances

Instances details
Eq DConFields Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data DConFields Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DConFields -> c DConFields #

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

toConstr :: DConFields -> Constr #

dataTypeOf :: DConFields -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DConFields Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DConFields Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DConFields :: Type -> Type #

Lift DConFields Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DConFields Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type DDeclaredInfix = Bool Source #

True if a constructor is declared infix. For normal ADTs, this means that is was written in infix style. For example, both of the constructors below are declared infix.

data Infix = Int Infix Int | Int :*: Int

Whereas neither of these constructors are declared infix:

data Prefix = Prefix Int Int | (:+:) Int Int

For GADTs, detecting whether a constructor is declared infix is a bit trickier, as one cannot write a GADT constructor "infix-style" like one can for normal ADT constructors. GHC considers a GADT constructor to be declared infix if it meets the following three criteria:

  1. Its name uses operator syntax (e.g., (:*:)).
  2. It has exactly two fields (without record syntax).
  3. It has a programmer-specified fixity declaration.

For example, in the following GADT:

infixl 5 :**:, :&&:, :^^:, ActuallyPrefix
data InfixGADT a where
  (:**:) :: Int -> b -> InfixGADT (Maybe b) -- Only this one is infix
  ActuallyPrefix :: Char -> Bool -> InfixGADT Double
  (:&&:) :: { infixGADT1 :: b, infixGADT2 :: Int } -> InfixGADT b :: Int -> Int -> Int -> InfixGADT Int
  (:!!:) :: Char -> Char -> InfixGADT Char

Only the (:**:) constructor is declared infix. The other constructors are not declared infix, because:

  • ActuallyPrefix does not use operator syntax (criterion 1).
  • (:&&:) uses record syntax (criterion 2).
  • (:^^:) does not have exactly two fields (criterion 2).
  • (:!!:) does not have a programmer-specified fixity declaration (criterion 3).

type DBangType = (Bang, DType) Source #

Corresponds to TH's BangType type.

type DVarBangType = (Name, Bang, DType) Source #

Corresponds to TH's VarBangType type.

data Bang #

Constructors

Bang SourceUnpackedness SourceStrictness
C { {-# UNPACK #-} !}a

Instances

Instances details
Eq Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

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

Data Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bang -> c Bang #

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

toConstr :: Bang -> Constr #

dataTypeOf :: Bang -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

compare :: Bang -> Bang -> Ordering #

(<) :: Bang -> Bang -> Bool #

(<=) :: Bang -> Bang -> Bool #

(>) :: Bang -> Bang -> Bool #

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

max :: Bang -> Bang -> Bang #

min :: Bang -> Bang -> Bang #

Show Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Bang -> ShowS #

show :: Bang -> String #

showList :: [Bang] -> ShowS #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: Type -> Type #

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Ppr Bang 
Instance details

Defined in Language.Haskell.TH.Ppr

Methods

ppr :: Bang -> Doc #

ppr_list :: [Bang] -> Doc #

type Rep Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

data SourceUnpackedness #

Constructors

NoSourceUnpackedness
C a
SourceNoUnpack
C { {-# NOUNPACK #-} } a
SourceUnpack
C { {-# UNPACK #-} } a

Instances

Instances details
Eq SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Data SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

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 
Instance details

Defined in Language.Haskell.TH.Syntax

Show SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Ppr SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Ppr

type Rep SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep SourceUnpackedness = D1 ('MetaData "SourceUnpackedness" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "NoSourceUnpackedness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceNoUnpack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceUnpack" 'PrefixI 'False) (U1 :: Type -> Type)))

data SourceStrictness #

Constructors

NoSourceStrictness
C a
SourceLazy
C {~}a
SourceStrict
C {!}a

Instances

Instances details
Eq SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Data SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

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 
Instance details

Defined in Language.Haskell.TH.Syntax

Show SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: Type -> Type #

Ppr SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Ppr

type Rep SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep SourceStrictness = D1 ('MetaData "SourceStrictness" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "NoSourceStrictness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceStrict" 'PrefixI 'False) (U1 :: Type -> Type)))

data DForeign Source #

Corresponds to TH's Foreign type.

Instances

Instances details
Eq DForeign Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data DForeign Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DForeign -> c DForeign #

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

toConstr :: DForeign -> Constr #

dataTypeOf :: DForeign -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DForeign Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DForeign Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DForeign :: Type -> Type #

Methods

from :: DForeign -> Rep DForeign x #

to :: Rep DForeign x -> DForeign #

Lift DForeign Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DForeign Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DPragma Source #

Corresponds to TH's Pragma type.

Instances

Instances details
Eq DPragma Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Data DPragma Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DPragma -> c DPragma #

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

toConstr :: DPragma -> Constr #

dataTypeOf :: DPragma -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DPragma Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DPragma Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DPragma :: Type -> Type #

Methods

from :: DPragma -> Rep DPragma x #

to :: Rep DPragma x -> DPragma #

Lift DPragma Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DPragma -> Q Exp #

liftTyped :: DPragma -> Q (TExp DPragma) #

type Rep DPragma Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DPragma = D1 ('MetaData "DPragma" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) ((C1 ('MetaCons "DInlineP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Inline)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RuleMatch) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases))) :+: (C1 ('MetaCons "DSpecialiseP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Inline)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases))) :+: C1 ('MetaCons "DSpecialiseInstP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType)))) :+: ((C1 ('MetaCons "DRuleP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [DTyVarBndrUnit])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DRuleBndr]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases)))) :+: C1 ('MetaCons "DAnnP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnTarget) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DExp))) :+: (C1 ('MetaCons "DLineP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "DCompleteP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name))))))

data DRuleBndr Source #

Corresponds to TH's RuleBndr type.

Instances

Instances details
Eq DRuleBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data DRuleBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DRuleBndr -> c DRuleBndr #

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

toConstr :: DRuleBndr -> Constr #

dataTypeOf :: DRuleBndr -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DRuleBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DRuleBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DRuleBndr :: Type -> Type #

Lift DRuleBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DRuleBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DRuleBndr = D1 ('MetaData "DRuleBndr" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (C1 ('MetaCons "DRuleVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "DTypedRuleVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType)))

data DTySynEqn Source #

Corresponds to TH's TySynEqn type (to store type family equations).

Instances

Instances details
Eq DTySynEqn Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Data DTySynEqn Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DTySynEqn -> c DTySynEqn #

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

toConstr :: DTySynEqn -> Constr #

dataTypeOf :: DTySynEqn -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DTySynEqn Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DTySynEqn Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DTySynEqn :: Type -> Type #

Lift DTySynEqn Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DTySynEqn Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DInfo Source #

Corresponds to TH's Info type.

Constructors

DTyConI DDec (Maybe [DInstanceDec]) 
DVarI Name DType (Maybe Name)

The Maybe Name stores the name of the enclosing definition (datatype, for a data constructor; class, for a method), if any

DTyVarI Name DKind 
DPrimTyConI Name Int Bool

The Int is the arity; the Bool is whether this tycon is unlifted.

DPatSynI Name DPatSynType 

Instances

Instances details
Eq DInfo Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

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

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

Data DInfo Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DInfo -> c DInfo #

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

toConstr :: DInfo -> Constr #

dataTypeOf :: DInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DInfo Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DInfo -> ShowS #

show :: DInfo -> String #

showList :: [DInfo] -> ShowS #

Generic DInfo Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DInfo :: Type -> Type #

Methods

from :: DInfo -> Rep DInfo x #

to :: Rep DInfo x -> DInfo #

type Rep DInfo Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DInfo = D1 ('MetaData "DInfo" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) ((C1 ('MetaCons "DTyConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DDec) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [DInstanceDec]))) :+: C1 ('MetaCons "DVarI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name))))) :+: (C1 ('MetaCons "DTyVarI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DKind)) :+: (C1 ('MetaCons "DPrimTyConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: C1 ('MetaCons "DPatSynI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DPatSynType)))))

type DInstanceDec Source #

Arguments

 = DDec

Guaranteed to be an instance declaration

data Role #

Role annotations

Constructors

NominalR
nominal
RepresentationalR
representational
PhantomR
phantom
InferR
_

Instances

Instances details
Eq Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

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

Data Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role #

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

toConstr :: Role -> Constr #

dataTypeOf :: Role -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

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

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

Show Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role :: Type -> Type #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Ppr Role 
Instance details

Defined in Language.Haskell.TH.Ppr

Methods

ppr :: Role -> Doc #

ppr_list :: [Role] -> Doc #

type Rep Role 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Role = D1 ('MetaData "Role" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "NominalR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RepresentationalR" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PhantomR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InferR" 'PrefixI 'False) (U1 :: Type -> Type)))

data AnnTarget #

Instances

Instances details
Eq AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Data AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnTarget -> c AnnTarget #

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

toConstr :: AnnTarget -> Constr #

dataTypeOf :: AnnTarget -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Show AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type #

type Rep AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep AnnTarget = D1 ('MetaData "AnnTarget" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "ModuleAnnotation" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeAnnotation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "ValueAnnotation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))))

The Desugar class

class Desugar th ds | ds -> th where Source #

This class relates a TH type with its th-desugar type and allows conversions back and forth. The functional dependency goes only one way because we define the following instances on old versions of GHC:

instance Desugar TyVarBndrSpec DTyVarBndrSpec
instance Desugar TyVarBndrUnit DTyVarBndrUnit

Prior to GHC 9.0, TyVarBndrSpec and TyVarBndrUnit are simply type synonyms for TyVarBndr, so making the functional dependencies bidirectional would cause these instances to be rejected.

Methods

desugar :: DsMonad q => th -> q ds Source #

sweeten :: ds -> th Source #

Instances

Instances details
Desugar Exp DExp Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

Methods

desugar :: DsMonad q => Exp -> q DExp Source #

sweeten :: DExp -> Exp Source #

Desugar Type DType Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

Desugar Cxt DCxt Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

Methods

desugar :: DsMonad q => Cxt -> q DCxt Source #

sweeten :: DCxt -> Cxt Source #

Desugar TyVarBndrUnit DTyVarBndrUnit Source #

This instance monomorphizes the flag parameter of DTyVarBndr since pre-9.0 versions of GHC do not equip TyVarBndr with a flag type parameter. There is also a corresponding instance for TyVarBndrSpec/DTyVarBndrSpec.

Instance details

Defined in Language.Haskell.TH.Desugar

Desugar TyVarBndrSpec DTyVarBndrSpec Source #

This instance monomorphizes the flag parameter of DTyVarBndr since pre-9.0 versions of GHC do not equip TyVarBndr with a flag type parameter. There is also a corresponding instance for TyVarBndrUnit/DTyVarBndrUnit.

Instance details

Defined in Language.Haskell.TH.Desugar

Desugar TypeArg DTypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

Desugar [Dec] [DDec] Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

Methods

desugar :: DsMonad q => [Dec] -> q [DDec] Source #

sweeten :: [DDec] -> [Dec] Source #

Main desugaring functions

dsExp :: DsMonad q => Exp -> q DExp Source #

Desugar an expression

dsDecs :: DsMonad q => [Dec] -> q [DDec] Source #

Desugar arbitrary Decs

dsType :: DsMonad q => Type -> q DType Source #

Desugar a type

dsInfo :: DsMonad q => Info -> q DInfo Source #

Desugar Info

dsPatOverExp :: DsMonad q => Pat -> DExp -> q (DPat, DExp) Source #

Desugar a pattern, along with processing a (desugared) expression that is the entire scope of the variables bound in the pattern.

dsPatsOverExp :: DsMonad q => [Pat] -> DExp -> q ([DPat], DExp) Source #

Desugar multiple patterns. Like dsPatOverExp.

dsPatX :: DsMonad q => Pat -> q (DPat, [(Name, DExp)]) Source #

Desugar a pattern, returning a list of (Name, DExp) pairs of extra variables that must be bound within the scope of the pattern

dsLetDecs :: DsMonad q => [Dec] -> q ([DLetDec], DExp -> DExp) Source #

Desugar Decs that can appear in a let expression. See the documentation for dsLetDec for an explanation of what the return type represents.

dsTvb :: DsMonad q => flag -> TyVarBndr -> q (DTyVarBndr flag) Source #

Desugar a TyVarBndr with a particular flag.

dsCxt :: DsMonad q => Cxt -> q DCxt Source #

Desugar a Cxt

dsCon Source #

Arguments

:: DsMonad q 
=> [DTyVarBndrUnit]

The universally quantified type variables (used if desugaring a non-GADT constructor).

-> DType

The original data declaration's type (used if desugaring a non-GADT constructor).

-> Con 
-> q [DCon] 

Desugar a single Con.

Because we always desugar Cons to GADT syntax (see the documentation for DCon), it is not always possible to desugar with just a Con alone. For instance, we must desugar:

data Foo a = forall b. MkFoo b

To this:

data Foo a :: Type where
  MkFoo :: forall a b. b -> Foo a

If our only argument was forall b. MkFoo b, it would be somewhat awkward to figure out (1) what the set of universally quantified type variables ([a]) was, and (2) what the return type (Foo a) was. For this reason, we require passing these as arguments. (If we desugar an actual GADT constructor, these arguments are ignored.)

dsForeign :: DsMonad q => Foreign -> q DForeign Source #

Desugar a Foreign.

dsPragma :: DsMonad q => Pragma -> q DPragma Source #

Desugar a Pragma.

dsRuleBndr :: DsMonad q => RuleBndr -> q DRuleBndr Source #

Desugar a RuleBndr.

Secondary desugaring functions

type PatM q = WriterT [(Name, DExp)] q Source #

Desugaring a pattern also returns the list of variables bound in as-patterns and the values they should be bound to. This variables must be brought into scope in the "body" of the pattern.

dsPred :: DsMonad q => Pred -> q DCxt Source #

Desugar a Pred, flattening any internal tuples

dsPat :: DsMonad q => Pat -> PatM q DPat Source #

Desugar a pattern.

dsDec :: DsMonad q => Dec -> q [DDec] Source #

Desugar a single Dec, perhaps producing multiple DDecs

dsDataDec :: DsMonad q => NewOrData -> Cxt -> Name -> [TyVarBndrUnit] -> Maybe Kind -> [Con] -> [DerivingClause] -> q [DDec] Source #

Desugar a DataD or NewtypeD.

type DerivingClause = DerivClause Source #

A backwards-compatible type synonym for the thing representing a single derived class in a deriving clause. (This is a DerivClause, Pred, or Name depending on the GHC version.)

dsDerivClause :: DsMonad q => DerivingClause -> q DDerivClause Source #

Desugar a DerivingClause.

dsLetDec :: DsMonad q => Dec -> q ([DLetDec], DExp -> DExp) Source #

Desugar a single Dec that can appear in a let expression. This produces the following output:

  • One or more DLetDecs (a single Dec can produce multiple DLetDecs in the event of a value declaration that binds multiple things by way of pattern matching.
  • A function of type DExp -> DExp, which should be applied to the expression immediately following the DLetDecs. This function prepends binding forms for any implicit params that were bound in the argument Dec. (If no implicit params are bound, this is simply the id function.)

For instance, if the argument to dsLetDec is the ?x = 42 part of this expression:

let { ?x = 42 } in ?x

Then the output is:

  • let new_x_val = 42
  • \z -> bindIP @"x" new_x_val z

This way, the expression let { new_x_val = 42 } in bindIP @"x" new_x_val (ip @"x") can be formed. The implicit param binders always come after all the other DLetDecs to support parallel assignment of implicit params.

dsMatches Source #

Arguments

:: DsMonad q 
=> Name

Name of the scrutinee, which must be a bare var

-> [Match]

Matches of the case statement

-> q [DMatch] 

Desugar a list of matches for a case statement

dsBody Source #

Arguments

:: DsMonad q 
=> Body

body to desugar

-> [Dec]

"where" declarations

-> DExp

what to do if the guards don't match

-> q DExp 

Desugar a Body

dsGuards Source #

Arguments

:: DsMonad q 
=> [(Guard, Exp)]

Guarded expressions

-> DExp

What to do if none of the guards match

-> q DExp 

Desugar guarded expressions

dsDoStmts :: forall q. DsMonad q => Maybe ModName -> [Stmt] -> q DExp Source #

Desugar the Stmts in a do expression

dsComp :: DsMonad q => [Stmt] -> q DExp Source #

Desugar the Stmts in a list or monad comprehension

dsClauses Source #

Arguments

:: DsMonad q 
=> Name

Name of the function

-> [Clause]

Clauses to desugar

-> q [DClause] 

Desugar clauses to a function definition

dsBangType :: DsMonad q => BangType -> q DBangType Source #

Desugar a BangType (or a StrictType, if you're old-fashioned)

dsVarBangType :: DsMonad q => VarBangType -> q DVarBangType Source #

Desugar a VarBangType (or a VarStrictType, if you're old-fashioned)

dsTypeFamilyHead :: DsMonad q => TypeFamilyHead -> q DTypeFamilyHead Source #

Desugar a TypeFamilyHead

dsFamilyResultSig :: DsMonad q => FamilyResultSig -> q DFamilyResultSig Source #

Desugar a FamilyResultSig

dsPatSynDir :: DsMonad q => Name -> PatSynDir -> q DPatSynDir Source #

Desugar a PatSynDir. (Available only with GHC 8.2+)

Converting desugared AST back to TH AST

Expanding type synonyms

expand :: (DsMonad q, Data a) => a -> q a Source #

Expand all type synonyms and type families in the desugared abstract syntax tree provided, where type family simplification is on a "best effort" basis. Normally, the first parameter should have a type like DExp or DLetDec.

expandType :: DsMonad q => DType -> q DType Source #

Expands all type synonyms in a desugared type. Also expands open type family applications. (In GHCs before 7.10, this part does not work if there are any variables.) Attempts to expand closed type family applications, but aborts the moment it spots anything strange, like a nested type family application or type variable.

Reification

reifyWithWarning :: (Quasi q, MonadFail q) => Name -> q Info Source #

Reify a declaration, warning the user about splices if the reify fails. The warning says that reification can fail if you try to reify a type in the same splice as it is declared.

Local reification

template-haskell reification functions like reify and qReify, as well as th-desugar's reifyWithWarning, only look through declarations that either (1) have already been typechecked in the current module, or (2) are in scope because of imports. We refer to this as global reification. Sometimes, however, you may wish to reify declarations that have been quoted but not yet been typechecked, such as in the following example:

example :: IO ()
example = putStrLn
  $(do decs <- [d| data Foo = MkFoo |]
       info <- reify (mkName "Foo")
       stringE $ pprint info)

Because Foo only exists in a TH quote, it is not available globally. As a result, the call to reify (mkName "Foo") will fail.

To make this sort of example possible, th-desugar extends global reification with local reification. A function that performs local reification (such as dsReify, reifyWithLocals, or similar functions that have a DsMonad context) looks through both typechecked (or imported) declarations and quoted declarations that are currently in scope. One can add quoted declarations in the current scope by using the withLocalDeclarations function. Here is an example of how to repair the example above using withLocalDeclarations:

example2 :: IO ()
example2 = putStrLn
  $(do decs <- [d| data Foo = MkFoo |]
       info <- withLocalDeclarations decs $
                 reifyWithLocals (mkName "Foo")
       stringE $ pprint info)

Note that withLocalDeclarations should only be used to add quoted declarations with names that are not duplicates of existing global or local declarations. Adding duplicate declarations through withLocalDeclarations is undefined behavior and should be avoided. This is unlikely to happen if you are only using withLocalDeclarations in conjunction with TH quotes, however. For instance, this is not an example of duplicate declarations:

data T = MkT1

$(do decs <- [d| data T = MkT2 |]
     info <- withLocalDeclarations decs ...
     ...)

The quoted data T = MkT2 does not conflict with the top-level data T = Mk1 since declaring a data type within TH quotes gives it a fresh, unique name that distinguishes it from any other data types already in scope.

withLocalDeclarations :: DsMonad q => [Dec] -> DsM q a -> q a Source #

Add a list of declarations to be considered when reifying local declarations.

dsReify :: DsMonad q => Name -> q (Maybe DInfo) Source #

Like reify, but safer and desugared. Uses local declarations where available.

dsReifyType :: DsMonad q => Name -> q (Maybe DType) Source #

Like reifyType, but safer and desugared. Uses local declarations where available.

reifyWithLocals_maybe :: DsMonad q => Name -> q (Maybe Info) Source #

Like reify from Template Haskell, but looks also in any not-yet-typechecked declarations. To establish this list of not-yet-typechecked declarations, use withLocalDeclarations. Returns Nothing if reification fails. Note that no inferred type information is available from local declarations; bottoms may be used if necessary.

reifyWithLocals :: DsMonad q => Name -> q Info Source #

Like reifyWithLocals_maybe, but throws an exception upon failure, warning the user about separating splices.

reifyFixityWithLocals :: DsMonad q => Name -> q (Maybe Fixity) Source #

Like reifyWithLocals_maybe, but for fixities. Note that a return value of Nothing might mean that the name is not in scope, or it might mean that the name has no assigned fixity. (Use reifyWithLocals_maybe if you really need to tell the difference.)

reifyTypeWithLocals_maybe :: DsMonad q => Name -> q (Maybe Type) Source #

Like reifyWithLocals_maybe but for types and kinds. Note that a return value of Nothing might mean that the name is not in scope, or it might mean that the full type of the name cannot be determined. (Use reifyWithLocals_maybe if you really need to tell the difference.)

reifyTypeWithLocals :: DsMonad q => Name -> q Type Source #

Like reifyTypeWithLocals_maybe, but throws an exception upon failure, warning the user about separating splices.

lookupValueNameWithLocals :: DsMonad q => String -> q (Maybe Name) Source #

Like lookupValueName from Template Haskell, but looks also in Names of not-yet-typechecked declarations. To establish this list of not-yet-typechecked declarations, use withLocalDeclarations. Returns Nothing if no value with the same name can be found.

lookupTypeNameWithLocals :: DsMonad q => String -> q (Maybe Name) Source #

Like lookupTypeName from Template Haskell, but looks also in Names of not-yet-typechecked declarations. To establish this list of not-yet-typechecked declarations, use withLocalDeclarations. Returns Nothing if no type with the same name can be found.

mkDataNameWithLocals :: DsMonad q => String -> q Name Source #

Like TH's lookupValueName, but if this name is not bound, then we assume it is declared in the current module.

Unlike mkDataName, this also consults the local declarations in scope when determining if the name is currently bound.

mkTypeNameWithLocals :: DsMonad q => String -> q Name Source #

Like TH's lookupTypeName, but if this name is not bound, then we assume it is declared in the current module.

Unlike mkTypeName, this also consults the local declarations in scope when determining if the name is currently bound.

reifyNameSpace :: DsMonad q => Name -> q (Maybe NameSpace) Source #

Determines a Name's NameSpace. If the NameSpace is attached to the Name itself (i.e., it is unambiguous), then that NameSpace is immediately returned. Otherwise, reification is used to lookup up the NameSpace (consulting local declarations if necessary).

Note that if a Name lives in two different NameSpaces (which can genuinely happen--for instance, mkName "==", where == is both a function and a type family), then this function will simply return whichever NameSpace is discovered first via reification. If you wish to find a Name in a particular NameSpace, use the lookupValueNameWithLocals or lookupTypeNameWithLocals functions.

class (Quasi m, MonadFail m) => DsMonad m where Source #

A DsMonad stores some list of declarations that should be considered in scope. DsM is the prototypical inhabitant of DsMonad.

Methods

localDeclarations :: m [Dec] Source #

Produce a list of local declarations.

Instances

Instances details
DsMonad IO Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

DsMonad Q Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

(Quasi q, MonadFail q) => DsMonad (DsM q) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

DsMonad m => DsMonad (ReaderT r m) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

DsMonad m => DsMonad (StateT s m) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

(DsMonad m, Monoid w) => DsMonad (WriterT w m) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

(DsMonad m, Monoid w) => DsMonad (RWST r w s m) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

Methods

localDeclarations :: RWST r w s m [Dec] Source #

data DsM q a Source #

A convenient implementation of the DsMonad class. Use by calling withLocalDeclarations.

Instances

Instances details
MonadTrans DsM Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

Methods

lift :: Monad m => m a -> DsM m a #

Monad q => Monad (DsM q) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

Methods

(>>=) :: DsM q a -> (a -> DsM q b) -> DsM q b #

(>>) :: DsM q a -> DsM q b -> DsM q b #

return :: a -> DsM q a #

Functor q => Functor (DsM q) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

Methods

fmap :: (a -> b) -> DsM q a -> DsM q b #

(<$) :: a -> DsM q b -> DsM q a #

MonadFail q => MonadFail (DsM q) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

Methods

fail :: String -> DsM q a #

Applicative q => Applicative (DsM q) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

Methods

pure :: a -> DsM q a #

(<*>) :: DsM q (a -> b) -> DsM q a -> DsM q b #

liftA2 :: (a -> b -> c) -> DsM q a -> DsM q b -> DsM q c #

(*>) :: DsM q a -> DsM q b -> DsM q b #

(<*) :: DsM q a -> DsM q b -> DsM q a #

MonadIO q => MonadIO (DsM q) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

Methods

liftIO :: IO a -> DsM q a #

Quasi q => Quasi (DsM q) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

(Quasi q, MonadFail q) => DsMonad (DsM q) Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Reify

Nested pattern flattening

scExp :: DsMonad q => DExp -> q DExp Source #

Remove all nested pattern-matches within this expression. This also removes all DTildePas and DBangPas. After this is run, every pattern is guaranteed to be either a DConPa with bare variables as arguments, a DLitPa, or a DWildPa.

scLetDec :: DsMonad q => DLetDec -> q DLetDec Source #

Like scExp, but for a DLetDec.

Capture-avoiding substitution and utilities

Free variable calculation

fvDType :: DType -> OSet Name Source #

Compute the free variables of a DType.

extractBoundNamesDPat :: DPat -> OSet Name Source #

Extract the term variables bound by a DPat.

This does not extract any type variables bound by pattern signatures.

Utility functions

applyDExp :: DExp -> [DExp] -> DExp Source #

Apply one DExp to a list of arguments

dPatToDExp :: DPat -> DExp Source #

Convert a DPat to a DExp. Fails on DWildP.

removeWilds :: DsMonad q => DPat -> q DPat Source #

Remove all wildcards from a pattern, replacing any wildcard with a fresh variable

getDataD Source #

Arguments

:: DsMonad q 
=> String

Print this out on failure

-> Name

Name of the datatype (data or newtype) of interest

-> q ([TyVarBndrUnit], [Con]) 

Extract the TyVarBndrs and constructors given the Name of a type

dataConNameToDataName :: DsMonad q => Name -> q Name Source #

From the name of a data constructor, retrive the datatype definition it is a part of.

dataConNameToCon :: DsMonad q => Name -> q Con Source #

From the name of a data constructor, retrieve its definition as a Con

nameOccursIn :: Data a => Name -> a -> Bool Source #

Check if a name occurs anywhere within a TH tree.

allNamesIn :: Data a => a -> [Name] Source #

Extract all Names mentioned in a TH tree.

flattenDValD :: Quasi q => DLetDec -> q [DLetDec] Source #

If the declaration passed in is a DValD, creates new, equivalent declarations such that the DPat in all DValDs is just a plain DVarPa. Other declarations are passed through unchanged. Note that the declarations that come out of this function are rather less efficient than those that come in: they have many more pattern matches.

getRecordSelectors :: DsMonad q => [DCon] -> q [DLetDec] Source #

Produces DLetDecs representing the record selector functions from the provided DCons.

Note that if the same record selector appears in multiple constructors, getRecordSelectors will return only one binding for that selector. For example, if you had:

data X = X1 {y :: Symbol} | X2 {y :: Symbol}

Then calling getRecordSelectors on [X1, X2] will return:

[ DSigD y (DAppT (DAppT DArrowT (DConT X)) (DConT Symbol))
, DFunD y [ DClause [DConP X1 [DVarP field]] (DVarE field)
          , DClause [DConP X2 [DVarP field]] (DVarE field) ] ]

instead of returning one binding for X1 and another binding for X2.

getRecordSelectors does not attempt to filter out "naughty" record selectors—that is, records whose field types mention existentially quantified type variables that do not appear in the constructor's return type. Here is an example of a naughty record selector:

data Some :: (Type -> Type) -> Type where
  MkSome :: { getSome :: f a } -> Some f

GHC itself will not allow the use of getSome as a top-level function due to its type f a mentioning the existential variable a, but getRecordSelectors will return it nonetheless. Ultimately, this design choice is a practical one, as detecting which type variables are existential in Template Haskell is difficult in the general case.

mkTypeName :: Quasi q => String -> q Name Source #

Like TH's lookupTypeName, but if this name is not bound, then we assume it is declared in the current module.

mkDataName :: Quasi q => String -> q Name Source #

Like TH's lookupDataName, but if this name is not bound, then we assume it is declared in the current module.

newUniqueName :: Quasi q => String -> q Name Source #

Like newName, but even more unique (unique across different splices), and with unique nameBases. Precondition: the string is a valid Haskell alphanumeric identifier (could be upper- or lower-case).

mkTupleDExp :: [DExp] -> DExp Source #

Make a tuple DExp from a list of DExps. Avoids using a 1-tuple.

mkTupleDPat :: [DPat] -> DPat Source #

Make a tuple DPat from a list of DPats. Avoids using a 1-tuple.

maybeDLetE :: [DLetDec] -> DExp -> DExp Source #

If decs is non-empty, delcare them in a let:

maybeDCaseE :: String -> DExp -> [DMatch] -> DExp Source #

If matches is non-empty, make a case statement; otherwise make an error statement

mkDLamEFromDPats :: Quasi q => [DPat] -> DExp -> q DExp Source #

Convert a list of DPat arguments and a DExp body into a DLamE. This is needed since DLamE takes a list of Names for its bound variables instead of DPats, so some reorganization is needed.

tupleDegree_maybe :: String -> Maybe Int Source #

Extract the degree of a tuple

tupleNameDegree_maybe :: Name -> Maybe Int Source #

Extract the degree of a tuple name

unboxedSumDegree_maybe :: String -> Maybe Int Source #

Extract the degree of an unboxed sum

unboxedSumNameDegree_maybe :: Name -> Maybe Int Source #

Extract the degree of an unboxed sum name

unboxedTupleDegree_maybe :: String -> Maybe Int Source #

Extract the degree of an unboxed tuple

unboxedTupleNameDegree_maybe :: Name -> Maybe Int Source #

Extract the degree of an unboxed tuple name

strictToBang :: Bang -> Bang Source #

Convert a Strict to a Bang in GHCs 7.x. This is just the identity operation in GHC 8.x, which has no Strict. (This is included in GHC 8.x only for good Haddocking.)

isTypeKindName :: Name -> Bool Source #

Returns True if the argument Name is that of Type (or * or , to support older GHCs).

typeKindName :: Name Source #

The Name of:

  1. The kind Type, on GHC 8.0 or later.
  2. The kind * on older GHCs.

bindIP :: forall name a r. a -> (IP name a => r) -> r Source #

Get an implicit param constraint (IP name a, which is the desugared form of (?name :: a)) from an explicit value.

This function is only available with GHC 8.0 or later.

mkExtraDKindBinders :: forall q. DsMonad q => DKind -> q [DTyVarBndrUnit] Source #

Create new kind variable binder names corresponding to the return kind of a data type. This is useful when you have a data type like:

data Foo :: forall k. k -> Type -> Type where ...

But you want to be able to refer to the type Foo a b. mkExtraDKindBinders will take the kind forall k. k -> Type -> Type, discover that is has two visible argument kinds, and return as a result two new kind variable binders [a :: k, b :: Type], where a and b are fresh type variable names.

This expands kind synonyms if necessary.

changeDTVFlags :: newFlag -> [DTyVarBndr oldFlag] -> [DTyVarBndr newFlag] Source #

Set the flag in a list of DTyVarBndrs. This is often useful in contexts where one needs to re-use a list of DTyVarBndrs from one flag setting to another flag setting. For example, in order to re-use the DTyVarBndrs bound by a DDataD in a DForallT, one can do the following:

case x of
  DDataD _ _ _ tvbs _ _ _ ->
    DForallT (DForallInvis (changeDTVFlags SpecifiedSpec tvbs)) ...

toposortTyVarsOf :: [DType] -> [DTyVarBndrUnit] Source #

Take a list of DTypes, find their free variables, and sort them in reverse topological order to ensure that they are well scoped. In other words, the free variables are ordered such that:

  1. Whenever an explicit kind signature of the form (A :: K) is encountered, the free variables of K will always appear to the left of the free variables of A in the returned result.
  2. The constraint in (1) notwithstanding, free variables will appear in left-to-right order of their original appearance.

On older GHCs, this takes measures to avoid returning explicitly bound kind variables, which was not possible before TypeInType.

FunArgs and VisFunArg

data FunArgs Source #

The list of arguments in a function Type.

Constructors

FANil

No more arguments.

FAForalls ForallTelescope FunArgs

A series of foralled type variables followed by a dot (if ForallInvis) or an arrow (if ForallVis). For example, the type variables a1 ... an in forall a1 ... an. r.

FACxt Cxt FunArgs

A series of constraint arguments followed by =>. For example, the (c1, ..., cn) in (c1, ..., cn) => r.

FAAnon Type FunArgs

An anonymous argument followed by an arrow. For example, the a in a -> r.

Instances

Instances details
Eq FunArgs Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Methods

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

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

Data FunArgs Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunArgs -> c FunArgs #

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

toConstr :: FunArgs -> Constr #

dataTypeOf :: FunArgs -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FunArgs Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Lift FunArgs Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: FunArgs -> Q Exp #

liftTyped :: FunArgs -> Q (TExp FunArgs) #

data ForallTelescope Source #

The type variable binders in a forall. This is not used by the TH AST itself, but this is used as an intermediate data type in FAForalls.

Constructors

ForallVis [TyVarBndrUnit]

A visible forall (e.g., forall a -> {...}). These do not have any notion of specificity, so we use () as a placeholder value in the TyVarBndrs.

ForallInvis [TyVarBndrSpec]

An invisible forall (e.g., forall a {b} c -> {...}), where each binder has a Specificity.

Instances

Instances details
Eq ForallTelescope Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Data ForallTelescope Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForallTelescope -> c ForallTelescope #

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

toConstr :: ForallTelescope -> Constr #

dataTypeOf :: ForallTelescope -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ForallTelescope Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Lift ForallTelescope Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

data VisFunArg Source #

A visible function argument type (i.e., one that must be supplied explicitly in the source code). This is in contrast to invisible arguments (e.g., the c in c => r), which are instantiated without the need for explicit user input.

Constructors

VisFADep TyVarBndrUnit

A visible forall (e.g., forall a -> a).

VisFAAnon Type

An anonymous argument followed by an arrow (e.g., a -> r).

Instances

Instances details
Eq VisFunArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Data VisFunArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VisFunArg -> c VisFunArg #

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

toConstr :: VisFunArg -> Constr #

dataTypeOf :: VisFunArg -> DataType #

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

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

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

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

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

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

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

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

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

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

Show VisFunArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Lift VisFunArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

filterVisFunArgs :: FunArgs -> [VisFunArg] Source #

Filter the visible function arguments from a list of FunArgs.

ravelType :: FunArgs -> Type -> Type Source #

Reconstruct an arrow Type from its argument and result types.

unravelType :: Type -> (FunArgs, Type) Source #

Decompose a function Type into its arguments (the FunArgs) and its result type (the 'Type).

DFunArgs and DVisFunArg

data DFunArgs Source #

The list of arguments in a function DType.

Constructors

DFANil

No more arguments.

DFAForalls DForallTelescope DFunArgs

A series of foralled type variables followed by a dot (if ForallInvis) or an arrow (if ForallVis). For example, the type variables a1 ... an in forall a1 ... an. r.

DFACxt DCxt DFunArgs

A series of constraint arguments followed by =>. For example, the (c1, ..., cn) in (c1, ..., cn) => r.

DFAAnon DType DFunArgs

An anonymous argument followed by an arrow. For example, the a in a -> r.

Instances

Instances details
Eq DFunArgs Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Data DFunArgs Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DFunArgs -> c DFunArgs #

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

toConstr :: DFunArgs -> Constr #

dataTypeOf :: DFunArgs -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DFunArgs Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Generic DFunArgs Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Associated Types

type Rep DFunArgs :: Type -> Type #

Methods

from :: DFunArgs -> Rep DFunArgs x #

to :: Rep DFunArgs x -> DFunArgs #

Lift DFunArgs Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DFunArgs Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

data DVisFunArg Source #

A visible function argument type (i.e., one that must be supplied explicitly in the source code). This is in contrast to invisible arguments (e.g., the c in c => r), which are instantiated without the need for explicit user input.

Constructors

DVisFADep DTyVarBndrUnit

A visible forall (e.g., forall a -> a).

DVisFAAnon DType

An anonymous argument followed by an arrow (e.g., a -> r).

Instances

Instances details
Eq DVisFunArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Data DVisFunArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DVisFunArg -> c DVisFunArg #

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

toConstr :: DVisFunArg -> Constr #

dataTypeOf :: DVisFunArg -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DVisFunArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Generic DVisFunArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Associated Types

type Rep DVisFunArg :: Type -> Type #

Lift DVisFunArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

type Rep DVisFunArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

type Rep DVisFunArg = D1 ('MetaData "DVisFunArg" "Language.Haskell.TH.Desugar.Core" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (C1 ('MetaCons "DVisFADep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DTyVarBndrUnit)) :+: C1 ('MetaCons "DVisFAAnon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType)))

filterDVisFunArgs :: DFunArgs -> [DVisFunArg] Source #

Filter the visible function arguments from a list of DFunArgs.

ravelDType :: DFunArgs -> DType -> DType Source #

Reconstruct an arrow DType from its argument and result types.

unravelDType :: DType -> (DFunArgs, DType) Source #

Decompose a function DType into its arguments (the DFunArgs) and its result type (the 'DType).

TypeArg

data TypeArg Source #

An argument to a type, either a normal type (TANormal) or a visible kind application (TyArg).

TypeArg is useful when decomposing an application of a Type to its arguments (e.g., in unfoldType).

Constructors

TANormal Type 
TyArg Kind 

Instances

Instances details
Eq TypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Methods

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

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

Data TypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeArg -> c TypeArg #

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

toConstr :: TypeArg -> Constr #

dataTypeOf :: TypeArg -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Lift TypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: TypeArg -> Q Exp #

liftTyped :: TypeArg -> Q (TExp TypeArg) #

Desugar TypeArg DTypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

applyType :: Type -> [TypeArg] -> Type Source #

Apply one Type to a list of arguments.

filterTANormals :: [TypeArg] -> [Type] Source #

Filter the normal type arguments from a list of TypeArgs.

unfoldType :: Type -> (Type, [TypeArg]) Source #

Decompose an applied type into its individual components. For example, this:

Proxy @Type Char

would be unfolded to this:

(ConT ''Proxy, [TyArg (ConT ''Type), TANormal (ConT ''Char)])

DTypeArg

data DTypeArg Source #

An argument to a type, either a normal type (DTANormal) or a visible kind application (DTyArg).

DTypeArg does not appear directly in the th-desugar AST, but it is useful when decomposing an application of a DType to its arguments.

Constructors

DTANormal DType 
DTyArg DKind 

Instances

Instances details
Eq DTypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Data DTypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DTypeArg -> c DTypeArg #

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

toConstr :: DTypeArg -> Constr #

dataTypeOf :: DTypeArg -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DTypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Generic DTypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Associated Types

type Rep DTypeArg :: Type -> Type #

Methods

from :: DTypeArg -> Rep DTypeArg x #

to :: Rep DTypeArg x -> DTypeArg #

Lift DTypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Desugar TypeArg DTypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

type Rep DTypeArg Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

type Rep DTypeArg = D1 ('MetaData "DTypeArg" "Language.Haskell.TH.Desugar.Core" "th-desugar-1.12-FDXV98g2eeNHgrppiv8b4s" 'False) (C1 ('MetaCons "DTANormal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DType)) :+: C1 ('MetaCons "DTyArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DKind)))

applyDType :: DType -> [DTypeArg] -> DType Source #

Apply one DType to a list of arguments

filterDTANormals :: [DTypeArg] -> [DType] Source #

Filter the normal type arguments from a list of DTypeArgs.

unfoldDType :: DType -> (DType, [DTypeArg]) Source #

Decompose an applied type into its individual components. For example, this:

Proxy @Type Char

would be unfolded to this:

(DConT ''Proxy, [DTyArg (DConT ''Type), DTANormal (DConT ''Char)])

Extracting bound names

extractBoundNamesStmt :: Stmt -> OSet Name Source #

Extract the names bound in a Stmt

extractBoundNamesDec :: Dec -> OSet Name Source #

Extract the names bound in a Dec that could appear in a let expression.

extractBoundNamesPat :: Pat -> OSet Name Source #

Extract the names bound in a Pat