th-desugar-1.9: 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

Contents

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
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 :: (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 :: * -> * #

Methods

from :: DExp -> Rep DExp x #

to :: Rep DExp x -> DExp #

Lift DExp # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DExp -> Q Exp #

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.9-9UPecqpFTe7J0l3WpXzg5W" 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
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 :: (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 :: * -> * #

Methods

from :: DLetDec -> Rep DLetDec x #

to :: Rep DLetDec x -> DLetDec #

Lift DLetDec # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DLetDec -> Q Exp #

type Rep DLetDec Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DPat Source #

Corresponds to TH's Pat type.

Instances
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 :: (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 :: * -> * #

Methods

from :: DPat -> Rep DPat x #

to :: Rep DPat x -> DPat #

Lift DPat # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DPat -> Q Exp #

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
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 :: (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 :: * -> * #

Methods

from :: DType -> Rep DType x #

to :: Rep DType x -> DType #

Lift DType # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DType -> Q Exp #

Desugar Type DType Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

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.9-9UPecqpFTe7J0l3WpXzg5W" False) (((C1 (MetaCons "DForallT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DTyVarBndr]) :*: (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 "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 :: * -> *)) :+: (C1 (MetaCons "DLitT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TyLit)) :+: C1 (MetaCons "DWildCardT" PrefixI False) (U1 :: * -> *))))

type DKind = DType Source #

Kinds are types.

type DCxt = [DPred] Source #

Corresponds to TH's Cxt

data DPred Source #

Corresponds to TH's Pred

Instances
Data DPred 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) -> DPred -> c DPred #

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

toConstr :: DPred -> Constr #

dataTypeOf :: DPred -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DPred Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DPred -> ShowS #

show :: DPred -> String #

showList :: [DPred] -> ShowS #

Generic DPred Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DPred :: * -> * #

Methods

from :: DPred -> Rep DPred x #

to :: Rep DPred x -> DPred #

Lift DPred # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DPred -> Q Exp #

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 DPred Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DTyVarBndr Source #

Corresponds to TH's TyVarBndr

Instances
Data DTyVarBndr 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 -> c DTyVarBndr #

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

toConstr :: DTyVarBndr -> Constr #

dataTypeOf :: DTyVarBndr -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DTyVarBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Generic DTyVarBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Associated Types

type Rep DTyVarBndr :: * -> * #

Lift DTyVarBndr # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DTyVarBndr -> Q Exp #

Desugar TyVarBndr DTyVarBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar

type Rep DTyVarBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DMatch Source #

Corresponds to TH's Match type.

Constructors

DMatch DPat DExp 
Instances
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 :: (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 :: * -> * #

Methods

from :: DMatch -> Rep DMatch x #

to :: Rep DMatch x -> DMatch #

Lift DMatch # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DMatch -> Q Exp #

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.9-9UPecqpFTe7J0l3WpXzg5W" 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
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 :: (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 :: * -> * #

Methods

from :: DClause -> Rep DClause x #

to :: Rep DClause x -> DClause #

Lift DClause # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DClause -> Q Exp #

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.9-9UPecqpFTe7J0l3WpXzg5W" 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
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 :: (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 :: * -> * #

Methods

from :: DDec -> Rep DDec x #

to :: Rep DDec x -> DDec #

Lift DDec # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DDec -> Q Exp #

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.9-9UPecqpFTe7J0l3WpXzg5W" 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 [DTyVarBndr]) :*: 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 [DTyVarBndr]) :*: 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 [DTyVarBndr]) :*: (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 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 [DTyVarBndr]) :*: 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 Name))) :*: ((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 Name) :*: 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 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))))))

data DDerivClause Source #

Corresponds to TH's DerivClause type.

Instances
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 :: (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 :: * -> * #

Lift DDerivClause # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DDerivClause -> Q Exp #

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.9-9UPecqpFTe7J0l3WpXzg5W" 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
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 :: (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 :: * -> * #

Lift DDerivStrategy # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DDerivStrategy -> Q Exp #

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.9-9UPecqpFTe7J0l3WpXzg5W" False) ((C1 (MetaCons "DStockStrategy" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DAnyclassStrategy" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "DNewtypeStrategy" PrefixI False) (U1 :: * -> *) :+: 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
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 :: (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 :: * -> * #

Lift DPatSynDir # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DPatSynDir -> Q Exp #

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.9-9UPecqpFTe7J0l3WpXzg5W" False) (C1 (MetaCons "DUnidir" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "DImplBidir" PrefixI False) (U1 :: * -> *) :+: 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
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 :: (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 :: * -> * #

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 :: * -> *) :+: C1 (MetaCons "Overlapping" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Overlaps" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Incoherent" PrefixI False) (U1 :: * -> *)))

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
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 :: (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 :: * -> * #

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
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 :: (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 :: * -> * #

Lift NewOrData # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: NewOrData -> Q Exp #

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.9-9UPecqpFTe7J0l3WpXzg5W" False) (C1 (MetaCons "Newtype" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Data" PrefixI False) (U1 :: * -> *))

data DTypeFamilyHead Source #

Corresponds to TH's TypeFamilyHead type

Instances
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 :: (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 :: * -> * #

Lift DTypeFamilyHead # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DTypeFamilyHead -> Q Exp #

type Rep DTypeFamilyHead Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DFamilyResultSig Source #

Corresponds to TH's FamilyResultSig type

Instances
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 :: (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 :: * -> * #

Lift DFamilyResultSig # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DFamilyResultSig -> Q Exp #

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.9-9UPecqpFTe7J0l3WpXzg5W" False) (C1 (MetaCons "DNoSig" PrefixI False) (U1 :: * -> *) :+: (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 DTyVarBndr))))

data InjectivityAnn #

Injectivity annotation

Constructors

InjectivityAnn Name [Name] 
Instances
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 :: (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 :: * -> * #

Ppr InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Ppr

type Rep InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

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 [DTyVarBndr] DCxt Name DConFields DType

The GADT result type

Instances
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 :: (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 :: * -> * #

Methods

from :: DCon -> Rep DCon x #

to :: Rep DCon x -> DCon #

Lift DCon # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DCon -> Q Exp #

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
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 :: (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 :: * -> * #

Lift DConFields # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DConFields -> Q Exp #

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
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 :: (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 :: * -> * #

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
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 :: (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 :: * -> * #

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 :: * -> *) :+: (C1 (MetaCons "SourceNoUnpack" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SourceUnpack" PrefixI False) (U1 :: * -> *)))

data SourceStrictness #

Constructors

NoSourceStrictness
C a
SourceLazy
C {~}a
SourceStrict
C {!}a
Instances
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 :: (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 :: * -> * #

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 :: * -> *) :+: (C1 (MetaCons "SourceLazy" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SourceStrict" PrefixI False) (U1 :: * -> *)))

data DForeign Source #

Corresponds to TH's Foreign type.

Instances
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 :: (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 :: * -> * #

Methods

from :: DForeign -> Rep DForeign x #

to :: Rep DForeign x -> DForeign #

Lift DForeign # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DForeign -> Q Exp #

type Rep DForeign Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DPragma Source #

Corresponds to TH's Pragma type.

Instances
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 :: (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 :: * -> * #

Methods

from :: DPragma -> Rep DPragma x #

to :: Rep DPragma x -> DPragma #

Lift DPragma # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DPragma -> Q Exp #

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.9-9UPecqpFTe7J0l3WpXzg5W" 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 [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
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 :: (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 :: * -> * #

Lift DRuleBndr # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DRuleBndr -> Q Exp #

type Rep DRuleBndr Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

data DTySynEqn Source #

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

Constructors

DTySynEqn [DType] DType 
Instances
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 :: (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 :: * -> * #

Lift DTySynEqn # 
Instance details

Defined in Language.Haskell.TH.Desugar.Lift

Methods

lift :: DTySynEqn -> Q Exp #

type Rep DTySynEqn Source # 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

type Rep DTySynEqn = D1 (MetaData "DTySynEqn" "Language.Haskell.TH.Desugar.AST" "th-desugar-1.9-9UPecqpFTe7J0l3WpXzg5W" False) (C1 (MetaCons "DTySynEqn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DType]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DType)))

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
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 :: (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 :: * -> * #

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.9-9UPecqpFTe7J0l3WpXzg5W" 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
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 :: (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 :: * -> * #

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 :: * -> *) :+: C1 (MetaCons "RepresentationalR" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "PhantomR" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "InferR" PrefixI False) (U1 :: * -> *)))

data AnnTarget #

Instances
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 :: (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 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 :: * -> *) :+: (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 Type and Kind are type synonyms, but they desugar to different types.

Minimal complete definition

desugar, sweeten

Methods

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

sweeten :: ds -> th Source #

Instances
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 TyVarBndr DTyVarBndr 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] Source #

Desugar Decs that can appear in a let expression

dsTvb :: DsMonad q => TyVarBndr -> q DTyVarBndr Source #

Desugar a TyVarBndr

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

Desugar a Cxt

dsCon Source #

Arguments

:: DsMonad q 
=> [DTyVarBndr]

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

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

Desugar a DerivClause.

dsLetDec :: DsMonad q => Dec -> q [DLetDec] Source #

Desugar a single Dec, perhaps producing multiple DLetDecs

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 :: DsMonad q => [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 => 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.

The following definitions allow you to register a list of Decs to be used in reification queries.

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.

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 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.)

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 => DsMonad m where Source #

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

Minimal complete definition

localDeclarations

Methods

localDeclarations :: m [Dec] Source #

Produce a list of local declarations.

Instances
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 => DsMonad (DsM q) 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 => DsMonad (ReaderT r 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
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 #

fail :: String -> 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 => 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

Utility functions

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

Apply one DExp to a list of arguments

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

Apply one DType 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 ([TyVarBndr], [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 Source #

Arguments

:: Quasi q 
=> DType

the type of the argument

-> [DCon] 
-> q [DLetDec] 

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 [DConPa X1 [DVarPa field]] (DVarE field)
          , DClause [DConPa X2 [DVarPa field]] (DVarE field) ] ]

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

getRecordSelectors attempts to filter out "naughty" record selectors whose types mention existentially quantified type variables. But see the documentation for conExistentialTvbs for limitations to this approach.

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 :: DsMonad 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.

unravel :: DType -> ([DTyVarBndr], [DPred], [DType], DType) Source #

Decompose a function type into its type variables, its context, its argument types, and its result type.

conExistentialTvbs Source #

Arguments

:: DsMonad q 
=> DType

The type of the original data declaration

-> DCon 
-> q [DTyVarBndr] 

Returns all of a constructor's existentially quantified type variable binders.

Detecting the presence of existentially quantified type variables in the context of Template Haskell is quite involved. Here is an example that we will use to explain how this works:

data family Foo a b
data instance Foo (Maybe a) b where
  MkFoo :: forall x y z. x -> y -> z -> Foo (Maybe x) [z]

In MkFoo, x is universally quantified, whereas y and z are existentially quantified. Note that MkFoo desugars (in Core) to something like this:

data instance Foo (Maybe a) b where
  MkFoo :: forall a b y z. (b ~ [z]). a -> y -> z -> Foo (Maybe a) b

Here, we can see that a appears in the desugared return type (it is a simple alpha-renaming of x), so it is universally quantified. On the other hand, neither y nor z appear in the desugared return type, so they are existentially quantified.

This analysis would not have been possible without knowing what the original data declaration's type was (in this case, Foo (Maybe a) b), which is why we require it as an argument. Our algorithm for detecting existentially quantified variables is not too different from what was described above: we match the constructor's return type with the original data type, forming a substitution, and check which quantified variables are not part of the domain of the substitution.

Be warned: this may overestimate which variables are existentially quantified when kind variables are involved. For instance, consider this example:

data S k (a :: k)
data T a where
  MkT :: forall k (a :: k). { foo :: Proxy (a :: k), bar :: S k a } -> T a

Here, the kind variable k does not appear syntactically in the return type T a, so conExistentialTvbs would mistakenly flag k as existential.

There are various tricks we could employ to improve this, but ultimately, making this behave correctly with respect to PolyKinds 100% of the time would amount to performing kind inference in Template Haskell, which is quite difficult. For the sake of simplicity, we have decided to stick with a dumb-but-predictable syntactic check.

mkExtraDKindBinders :: DsMonad q => DKind -> q [DTyVarBndr] 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.

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

Take a list of DTypes, find their free variables, and sort them in reverse topological order to ensure that they are well scoped.

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

Extracting bound names

extractBoundNamesStmt :: Stmt -> Set Name Source #

Extract the names bound in a Stmt

extractBoundNamesDec :: Dec -> Set Name Source #

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

extractBoundNamesPat :: Pat -> Set Name Source #

Extract the names bound in a Pat