ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Plugins

Description

This module is not used by GHC itself. Rather, it exports all of the functions and types you are likely to need when writing a plugin for GHC. So authors of plugins can probably get away simply with saying "import GHC.Plugins".

Particularly interesting modules for plugin writers include GHC.Core and GHC.Core.Opt.Monad.

Synopsis

Documentation

data OccName #

Instances

Instances details
Eq OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

Data OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

toConstr :: OccName -> Constr #

dataTypeOf :: OccName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

NFData OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccName -> () #

Uniquable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

getUnique :: OccName -> Unique #

Binary OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

put_ :: BinHandle -> OccName -> IO ()

put :: BinHandle -> OccName -> IO (Bin OccName)

get :: BinHandle -> IO OccName

Outputable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc

HasOccName OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

occName :: OccName -> OccName #

OutputableBndr OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

pprBndr :: BindingSite -> OccName -> SDoc

pprPrefixOcc :: OccName -> SDoc

pprInfixOcc :: OccName -> SDoc

bndrIsJoin_maybe :: OccName -> Maybe Int

data NameSpace #

Instances

Instances details
Eq NameSpace 
Instance details

Defined in GHC.Types.Name.Occurrence

Ord NameSpace 
Instance details

Defined in GHC.Types.Name.Occurrence

Binary NameSpace 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

put_ :: BinHandle -> NameSpace -> IO ()

put :: BinHandle -> NameSpace -> IO (Bin NameSpace)

get :: BinHandle -> IO NameSpace

extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a #

lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a #

mkFsEnv :: [(FastString, a)] -> FastStringEnv a #

alterOccEnv :: (Maybe elt -> Maybe elt) -> OccEnv elt -> OccName -> OccEnv elt #

extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a #

extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a #

extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b #

extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a #

filterOccEnv :: (elt -> Bool) -> OccEnv elt -> OccEnv elt #

foldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b #

mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b #

mkClsOccFS :: FastString -> OccName #

mkDataOccFS :: FastString -> OccName #

mkOccEnv :: [(OccName, a)] -> OccEnv a #

mkOccEnv_C :: (a -> a -> a) -> [(OccName, a)] -> OccEnv a #

mkOccNameFS :: NameSpace -> FastString -> OccName #

mkTcOccFS :: FastString -> OccName #

mkTyVarOccFS :: FastString -> OccName #

mkVarOccFS :: FastString -> OccName #

occEnvElts :: OccEnv a -> [a] #

parenSymOcc :: OccName -> SDoc -> SDoc #

plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a #

pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc #

pprOccName :: OccName -> SDoc #

unitOccEnv :: OccName -> a -> OccEnv a #

type FastStringEnv a = UniqFM FastString a #

class HasOccName name where #

Methods

occName :: name -> OccName #

Instances

Instances details
HasOccName RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

occName :: RdrName -> OccName #

HasOccName Name 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName #

HasOccName OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

occName :: OccName -> OccName #

HasOccName Var 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName #

HasOccName IfaceDecl 
Instance details

Defined in GHC.Iface.Syntax

Methods

occName :: IfaceDecl -> OccName #

HasOccName TcBinder 
Instance details

Defined in GHC.Tc.Types

Methods

occName :: TcBinder -> OccName #

HasOccName HoleFitCandidate 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

occName :: HoleFitCandidate -> OccName #

HasOccName IfaceClassOp 
Instance details

Defined in GHC.Iface.Syntax

Methods

occName :: IfaceClassOp -> OccName #

HasOccName IfaceConDecl 
Instance details

Defined in GHC.Iface.Syntax

Methods

occName :: IfaceConDecl -> OccName #

HasOccName name => HasOccName (IEWrappedName name) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

occName :: IEWrappedName name -> OccName #

data OccEnv a #

Instances

Instances details
Data a => Data (OccEnv a) 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

toConstr :: OccEnv a -> Constr #

dataTypeOf :: OccEnv a -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable a => Outputable (OccEnv a) 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc

type OccSet = UniqSet OccName #

type TidyOccEnv = UniqFM FastString Int #

data Name #

Instances

Instances details
Eq Name 
Instance details

Defined in GHC.Types.Name

Methods

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

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

Data Name 
Instance details

Defined in GHC.Types.Name

Methods

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

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

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Name 
Instance details

Defined in GHC.Types.Name

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

NFData Name 
Instance details

Defined in GHC.Types.Name

Methods

rnf :: Name -> () #

Uniquable Name 
Instance details

Defined in GHC.Types.Name

Methods

getUnique :: Name -> Unique #

Binary Name 
Instance details

Defined in GHC.Types.Name

Methods

put_ :: BinHandle -> Name -> IO ()

put :: BinHandle -> Name -> IO (Bin Name)

get :: BinHandle -> IO Name

Outputable Name 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: Name -> SDoc

NamedThing Name 
Instance details

Defined in GHC.Types.Name

HasOccName Name 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName #

OutputableBndr Name 
Instance details

Defined in GHC.Types.Name

Methods

pprBndr :: BindingSite -> Name -> SDoc

pprPrefixOcc :: Name -> SDoc

pprInfixOcc :: Name -> SDoc

bndrIsJoin_maybe :: Name -> Maybe Int

data OccName #

Instances

Instances details
Eq OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

Data OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

toConstr :: OccName -> Constr #

dataTypeOf :: OccName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

NFData OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccName -> () #

Uniquable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

getUnique :: OccName -> Unique #

Binary OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

put_ :: BinHandle -> OccName -> IO ()

put :: BinHandle -> OccName -> IO (Bin OccName)

get :: BinHandle -> IO OccName

Outputable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc

HasOccName OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

occName :: OccName -> OccName #

OutputableBndr OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

pprBndr :: BindingSite -> OccName -> SDoc

pprPrefixOcc :: OccName -> SDoc

pprInfixOcc :: OccName -> SDoc

bndrIsJoin_maybe :: OccName -> Maybe Int

data NameSpace #

Instances

Instances details
Eq NameSpace 
Instance details

Defined in GHC.Types.Name.Occurrence

Ord NameSpace 
Instance details

Defined in GHC.Types.Name.Occurrence

Binary NameSpace 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

put_ :: BinHandle -> NameSpace -> IO ()

put :: BinHandle -> NameSpace -> IO (Bin NameSpace)

get :: BinHandle -> IO NameSpace

extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a #

lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a #

mkFsEnv :: [(FastString, a)] -> FastStringEnv a #

getOccFS :: NamedThing a => a -> FastString #

isDynLinkName :: Platform -> Module -> Name -> Bool #

isWiredIn :: NamedThing thing => thing -> Bool #

mkSysTvName :: Unique -> FastString -> Name #

mkSystemVarName :: Unique -> FastString -> Name #

nameModule :: HasDebugCallStack => Name -> Module #

pprDefinedAt :: Name -> SDoc #

pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc #

pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc #

pprNameDefnLoc :: Name -> SDoc #

pprPrefixName :: NamedThing a => a -> SDoc #

alterOccEnv :: (Maybe elt -> Maybe elt) -> OccEnv elt -> OccName -> OccEnv elt #

extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a #

extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a #

extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b #

extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a #

filterOccEnv :: (elt -> Bool) -> OccEnv elt -> OccEnv elt #

foldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b #

mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b #

mkClsOccFS :: FastString -> OccName #

mkDataOccFS :: FastString -> OccName #

mkOccEnv :: [(OccName, a)] -> OccEnv a #

mkOccEnv_C :: (a -> a -> a) -> [(OccName, a)] -> OccEnv a #

mkOccNameFS :: NameSpace -> FastString -> OccName #

mkTcOccFS :: FastString -> OccName #

mkTyVarOccFS :: FastString -> OccName #

mkVarOccFS :: FastString -> OccName #

occEnvElts :: OccEnv a -> [a] #

parenSymOcc :: OccName -> SDoc -> SDoc #

plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a #

pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc #

pprOccName :: OccName -> SDoc #

unitOccEnv :: OccName -> a -> OccEnv a #

type FastStringEnv a = UniqFM FastString a #

class NamedThing a where #

Minimal complete definition

getName

Methods

getOccName :: a -> OccName #

getName :: a -> Name #

Instances

Instances details
NamedThing Name 
Instance details

Defined in GHC.Types.Name

NamedThing TyThing 
Instance details

Defined in GHC.Types.TyThing

NamedThing Var 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

NamedThing TyCon 
Instance details

Defined in GHC.Core.TyCon

NamedThing Class 
Instance details

Defined in GHC.Core.Class

NamedThing DataCon 
Instance details

Defined in GHC.Core.DataCon

NamedThing ConLike 
Instance details

Defined in GHC.Core.ConLike

Methods

getOccName :: ConLike -> OccName #

getName :: ConLike -> Name #

NamedThing PatSyn 
Instance details

Defined in GHC.Core.PatSyn

Methods

getOccName :: PatSyn -> OccName #

getName :: PatSyn -> Name #

NamedThing IfaceDecl 
Instance details

Defined in GHC.Iface.Syntax

Methods

getOccName :: IfaceDecl -> OccName #

getName :: IfaceDecl -> Name #

NamedThing FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

NamedThing ClsInst 
Instance details

Defined in GHC.Core.InstEnv

NamedThing HoleFitCandidate 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

getOccName :: HoleFitCandidate -> OccName #

getName :: HoleFitCandidate -> Name #

NamedThing IfaceClassOp 
Instance details

Defined in GHC.Iface.Syntax

Methods

getOccName :: IfaceClassOp -> OccName #

getName :: IfaceClassOp -> Name #

NamedThing IfaceConDecl 
Instance details

Defined in GHC.Iface.Syntax

Methods

getOccName :: IfaceConDecl -> OccName #

getName :: IfaceConDecl -> Name #

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

NamedThing (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getOccName :: CoAxiom br -> OccName #

getName :: CoAxiom br -> Name #

NamedThing tv => NamedThing (VarBndr tv flag) 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: VarBndr tv flag -> OccName #

getName :: VarBndr tv flag -> Name #

NamedThing (HsTyVarBndr flag GhcRn) 
Instance details

Defined in GHC.Hs.Type

Methods

getOccName :: HsTyVarBndr flag GhcRn -> OccName #

getName :: HsTyVarBndr flag GhcRn -> Name #

class HasOccName name where #

Methods

occName :: name -> OccName #

Instances

Instances details
HasOccName RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

occName :: RdrName -> OccName #

HasOccName Name 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName #

HasOccName OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

occName :: OccName -> OccName #

HasOccName Var 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName #

HasOccName IfaceDecl 
Instance details

Defined in GHC.Iface.Syntax

Methods

occName :: IfaceDecl -> OccName #

HasOccName TcBinder 
Instance details

Defined in GHC.Tc.Types

Methods

occName :: TcBinder -> OccName #

HasOccName HoleFitCandidate 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

occName :: HoleFitCandidate -> OccName #

HasOccName IfaceClassOp 
Instance details

Defined in GHC.Iface.Syntax

Methods

occName :: IfaceClassOp -> OccName #

HasOccName IfaceConDecl 
Instance details

Defined in GHC.Iface.Syntax

Methods

occName :: IfaceConDecl -> OccName #

HasOccName name => HasOccName (IEWrappedName name) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

occName :: IEWrappedName name -> OccName #

data OccEnv a #

Instances

Instances details
Data a => Data (OccEnv a) 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

toConstr :: OccEnv a -> Constr #

dataTypeOf :: OccEnv a -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable a => Outputable (OccEnv a) 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc

type OccSet = UniqSet OccName #

type TidyOccEnv = UniqFM FastString Int #

data Var #

Instances

Instances details
Eq Var 
Instance details

Defined in GHC.Types.Var

Methods

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

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

Data Var 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Var -> Constr #

dataTypeOf :: Var -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Var 
Instance details

Defined in GHC.Types.Var

Methods

compare :: Var -> Var -> Ordering #

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

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

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Uniquable Var 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique #

Outputable Var 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc

NamedThing Var 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

HasOccName Var 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName #

Eq (DeBruijn CoreExpr) 
Instance details

Defined in GHC.Core.Map

Methods

(==) :: DeBruijn CoreExpr -> DeBruijn CoreExpr -> Bool #

(/=) :: DeBruijn CoreExpr -> DeBruijn CoreExpr -> Bool #

Eq (DeBruijn CoreAlt) 
Instance details

Defined in GHC.Core.Map

Methods

(==) :: DeBruijn CoreAlt -> DeBruijn CoreAlt -> Bool #

(/=) :: DeBruijn CoreAlt -> DeBruijn CoreAlt -> Bool #

type Id = Var #

idDetails :: Id -> IdDetails #

idInfo :: HasDebugCallStack => Id -> IdInfo #

isId :: Var -> Bool #

setIdMult :: Id -> Mult -> Id #

updateIdTypeAndMultM :: Monad m => (Type -> m Type) -> Id -> m Id #

type InId = Id #

type InVar = Var #

type JoinId = Id #

type OutId = Id #

type OutVar = Var #

asJoinId :: Id -> JoinArity -> JoinId #

asJoinId_maybe :: Id -> Maybe JoinArity -> Id #

idArity :: Id -> Arity #

idCafInfo :: Id -> CafInfo #

idCallArity :: Id -> Arity #

idCoreRules :: Id -> [CoreRule] #

idCprInfo :: Id -> CprSig #

idDemandInfo :: Id -> Demand #

idFunRepArity :: Id -> RepArity #

idInlineActivation :: Id -> Activation #

idInlinePragma :: Id -> InlinePragma #

idJoinArity :: JoinId -> JoinArity #

idMult :: Id -> Mult #

idName :: Id -> Name #

idOccInfo :: Id -> OccInfo #

idOneShotInfo :: Id -> OneShotInfo #

idRuleMatchInfo :: Id -> RuleMatchInfo #

idSpecialisation :: Id -> RuleInfo #

idStateHackOneShotInfo :: Id -> OneShotInfo #

idStrictness :: Id -> StrictSig #

idType :: Id -> Kind #

idUnfolding :: Id -> Unfolding #

isFCallId_maybe :: Id -> Maybe ForeignCall #

isJoinId_maybe :: Var -> Maybe JoinArity #

isPrimOpId_maybe :: Id -> Maybe PrimOp #

maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id #

mkExportedLocalId :: IdDetails -> Name -> Type -> Id #

mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id #

mkLocalId :: HasDebugCallStack => Name -> Mult -> Type -> Id #

mkLocalIdWithInfo :: HasDebugCallStack => Name -> Mult -> Type -> IdInfo -> Id #

mkSysLocal :: FastString -> Unique -> Mult -> Type -> Id #

mkSysLocalM :: MonadUnique m => FastString -> Mult -> Type -> m Id #

mkSysLocalOrCoVar :: FastString -> Unique -> Mult -> Type -> Id #

mkSysLocalOrCoVarM :: MonadUnique m => FastString -> Mult -> Type -> m Id #

mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id #

mkWorkerId :: Unique -> Id -> Type -> Id #

modifyIdInfo :: HasDebugCallStack => (IdInfo -> IdInfo) -> Id -> Id #

modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> Id #

realIdUnfolding :: Id -> Unfolding #

recordSelectorTyCon :: Id -> RecSelParent #

recordSelectorTyCon_maybe :: Id -> Maybe RecSelParent #

scaleIdBy :: Mult -> Id -> Id #

setIdArity :: Id -> Arity -> Id #

setIdCafInfo :: Id -> CafInfo -> Id #

setIdCallArity :: Id -> Arity -> Id #

setIdCprInfo :: Id -> CprSig -> Id #

setIdDemandInfo :: Id -> Demand -> Id #

setIdInfo :: Id -> IdInfo -> Id #

setIdName :: Id -> Name -> Id #

setIdOccInfo :: Id -> OccInfo -> Id #

setIdOneShotInfo :: Id -> OneShotInfo -> Id #

setIdSpecialisation :: Id -> RuleInfo -> Id #

setIdStrictness :: Id -> StrictSig -> Id #

setIdType :: Id -> Type -> Id #

setIdUnfolding :: Id -> Unfolding -> Id #

setInlineActivation :: Id -> Activation -> Id #

setInlinePragma :: Id -> InlinePragma -> Id #

stateHackOneShot :: OneShotInfo #

transferPolyIdInfo :: Id -> [Var] -> Id -> Id #

typeOneShot :: Type -> OneShotInfo #

updOneShotInfo :: Id -> OneShotInfo -> Id #

type TvSubstEnv = TyVarEnv Type #

data InScopeSet #

Instances

Instances details
Outputable InScopeSet 
Instance details

Defined in GHC.Types.Var.Env

Methods

ppr :: InScopeSet -> SDoc

addInScopeSet :: Subst -> VarSet -> Subst #

cloneBndrs :: Subst -> UniqSupply -> [Var] -> (Subst, [Var]) #

cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) #

deShadowBinds :: CoreProgram -> CoreProgram #

delBndrs :: Subst -> [Var] -> Subst #

extendIdSubst :: Subst -> Id -> CoreExpr -> Subst #

extendIdSubstList :: Subst -> [(Id, CoreExpr)] -> Subst #

extendSubst :: Subst -> Var -> CoreArg -> Subst #

extendSubstList :: Subst -> [(Var, CoreArg)] -> Subst #

lookupIdSubst :: HasDebugCallStack => Subst -> Id -> CoreExpr #

mkOpenSubst :: InScopeSet -> [(Var, CoreArg)] -> Subst #

substBind :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind) #

substBindSC :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind) #

substBndrs :: Subst -> [Var] -> (Subst, [Var]) #

substDVarSet :: Subst -> DVarSet -> DVarSet #

substExpr :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr #

substExprSC :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr #

substIdInfo :: Subst -> Id -> IdInfo -> Maybe IdInfo #

substRecBndrs :: Subst -> [Id] -> (Subst, [Id]) #

substRulesForImportedIds :: Subst -> [CoreRule] -> [CoreRule] #

substSpec :: Subst -> Id -> RuleInfo -> RuleInfo #

substTickish :: Subst -> Tickish Id -> Tickish Id #

substUnfolding :: Subst -> Unfolding -> Unfolding #

substUnfoldingSC :: Subst -> Unfolding -> Unfolding #

type IdSubstEnv = IdEnv CoreExpr #

data Subst #

Instances

Instances details
Outputable Subst 
Instance details

Defined in GHC.Core.Subst

Methods

ppr :: Subst -> SDoc

closeOverKinds :: TyCoVarSet -> TyCoVarSet #

closeOverKindsDSet :: DTyVarSet -> DTyVarSet #

coVarsOfType :: Type -> CoVarSet #

coVarsOfTypes :: [Type] -> CoVarSet #

tyCoFVsBndr :: TyCoVarBinder -> FV -> FV #

tyCoFVsVarBndr :: Var -> FV -> FV #

tyCoFVsVarBndrs :: [Var] -> FV -> FV #

tyCoVarsOfType :: Type -> TyCoVarSet #

tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet #

tyCoVarsOfTypes :: [Type] -> TyCoVarSet #

foldTyCo :: Monoid a => TyCoFolder env a -> env -> (Type -> a, [Type] -> a, Coercion -> a, [Coercion] -> a) #

mkInvisForAllTys :: [InvisTVBinder] -> Type -> Type #

substTysWith :: [TyVar] -> [Type] -> [Type] -> [Type] #

zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv #

zipTCvSubst :: HasDebugCallStack => [TyCoVar] -> [Type] -> TCvSubst #

zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> TCvSubst #

zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv #

tidyFreeTyCoVars :: TidyEnv -> [TyCoVar] -> TidyEnv #

tidyKind :: TidyEnv -> Kind -> Kind #

tidyOpenKind :: TidyEnv -> Kind -> (TidyEnv, Kind) #

tidyOpenTyCoVar :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) #

tidyOpenTyCoVars :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) #

tidyOpenType :: TidyEnv -> Type -> (TidyEnv, Type) #

tidyOpenTypes :: TidyEnv -> [Type] -> (TidyEnv, [Type]) #

tidyTyCoVarBinder :: TidyEnv -> VarBndr TyCoVar vis -> (TidyEnv, VarBndr TyCoVar vis) #

tidyTyCoVarBinders :: TidyEnv -> [VarBndr TyCoVar vis] -> (TidyEnv, [VarBndr TyCoVar vis]) #

tidyTyCoVarOcc :: TidyEnv -> TyCoVar -> TyCoVar #

tidyType :: TidyEnv -> Type -> Type #

tidyTypes :: TidyEnv -> [Type] -> [Type] #

tidyVarBndr :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) #

tidyVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) #

pattern Many :: Mult #

pattern One :: Mult #

applyTysX :: [TyVar] -> Type -> [Type] -> Type #

buildSynTyCon :: Name -> [KnotTied TyConBinder] -> Kind -> [Role] -> KnotTied Type -> TyCon #

coAxNthLHS :: forall (br :: BranchFlag). CoAxiom br -> Int -> Type #

eqType :: Type -> Type -> Bool #

eqTypeX :: RnEnv2 -> Type -> Type -> Bool #

eqTypes :: [Type] -> [Type] -> Bool #

eqVarBndrs :: RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 #

getRuntimeRep :: HasDebugCallStack => Type -> Type #

getRuntimeRep_maybe :: HasDebugCallStack => Type -> Maybe Type #

isLiftedType_maybe :: HasDebugCallStack => Type -> Maybe Bool #

isLitTy :: Type -> Maybe TyLit #

isPredTy :: HasDebugCallStack => Type -> Bool #

isStrLitTy :: Type -> Maybe FastString #

isStrictType :: HasDebugCallStack => Type -> Bool #

isUnliftedType :: HasDebugCallStack => Type -> Bool #

isValidJoinPointType :: JoinArity -> Type -> Bool #

kindRep :: HasDebugCallStack => Kind -> Type #

kindRep_maybe :: HasDebugCallStack => Kind -> Maybe Type #

linear :: a -> Scaled a #

mapTyCo :: Monad m => TyCoMapper () m -> (Type -> m Type, [Type] -> m [Type], Coercion -> m Coercion, [Coercion] -> m [Coercion]) #

mapTyCoX :: Monad m => TyCoMapper env m -> (env -> Type -> m Type, env -> [Type] -> m [Type], env -> Coercion -> m Coercion, env -> [Coercion] -> m [Coercion]) #

mkAppTys :: Type -> [Type] -> Type #

mkScaled :: Mult -> a -> Scaled a #

mkStrLitTy :: FastString -> Type #

mkTyConBindersPreferAnon :: [TyVar] -> TyCoVarSet -> [TyConBinder] #

nonDetCmpTypeX :: RnEnv2 -> Type -> Type -> Ordering #

nonDetCmpTypesX :: RnEnv2 -> [Type] -> [Type] -> Ordering #

partitionInvisibles :: [(a, ArgFlag)] -> ([a], [a]) #

piResultTy :: HasDebugCallStack => Type -> Type -> Type #

piResultTys :: HasDebugCallStack => Type -> [Type] -> Type #

repSplitAppTy_maybe :: HasDebugCallStack => Type -> Maybe (Type, Type) #

repSplitAppTys :: HasDebugCallStack => Type -> (Type, [Type]) #

repSplitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #

scaledSet :: Scaled a -> b -> Scaled b #

seqType :: Type -> () #

seqTypes :: [Type] -> () #

splitForAllTysInvis :: Type -> ([InvisTVBinder], Type) #

splitForAllTysReq :: Type -> ([ReqTVBinder], Type) #

splitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #

splitVisVarsOfType :: Type -> Pair TyCoVarSet #

splitVisVarsOfTypes :: [Type] -> Pair TyCoVarSet #

tcTypeKind :: HasDebugCallStack => Type -> Kind #

tyBinderType :: TyBinder -> Type #

tyConBindersTyCoBinders :: [TyConBinder] -> [TyCoBinder] #

tyConsOfType :: Type -> UniqSet TyCon #

tymult :: a -> Scaled a #

typeKind :: HasDebugCallStack => Type -> Kind #

binderArgFlag :: VarBndr tv argf -> argf #

binderType :: VarBndr TyCoVar argf -> Type #

binderVar :: VarBndr tv argf -> tv #

binderVars :: [VarBndr tv argf] -> [tv] #

mkTyCoVarBinder :: vis -> TyCoVar -> VarBndr TyCoVar vis #

mkTyCoVarBinders :: vis -> [TyCoVar] -> [VarBndr TyCoVar vis] #

mkTyVarBinder :: vis -> TyVar -> VarBndr TyVar vis #

mkTyVarBinders :: vis -> [TyVar] -> [VarBndr TyVar vis] #

tyVarSpecToBinders :: [VarBndr a Specificity] -> [VarBndr a ArgFlag] #

type Kind = Type #

type KnotTied ty = ty #

type Mult = Type #

type PredType = Type #

data Scaled a #

Instances

Instances details
Data a => Data (Scaled a) 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Scaled a -> Constr #

dataTypeOf :: Scaled a -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable a => Outputable (Scaled a) 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Scaled a -> SDoc

data TyCoBinder #

Instances

Instances details
Data TyCoBinder 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: TyCoBinder -> Constr #

dataTypeOf :: TyCoBinder -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable TyCoBinder 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: TyCoBinder -> SDoc

data TyCoFolder env a #

Constructors

TyCoFolder 

Fields

data Type #

Instances

Instances details
Data Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Type -> SDoc

Eq (DeBruijn Type) 
Instance details

Defined in GHC.Core.Map

Methods

(==) :: DeBruijn Type -> DeBruijn Type -> Bool #

(/=) :: DeBruijn Type -> DeBruijn Type -> Bool #

data TCvSubst #

Instances

Instances details
Outputable TCvSubst 
Instance details

Defined in GHC.Core.TyCo.Subst

Methods

ppr :: TCvSubst -> SDoc

type TvSubstEnv = TyVarEnv Type #

data TyCoMapper env (m :: Type -> Type) #

Constructors

TyCoMapper 

Fields

data AnonArgFlag #

Constructors

VisArg 
InvisArg 

Instances

Instances details
Eq AnonArgFlag 
Instance details

Defined in GHC.Types.Var

Data AnonArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: AnonArgFlag -> Constr #

dataTypeOf :: AnonArgFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AnonArgFlag 
Instance details

Defined in GHC.Types.Var

Binary AnonArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

put_ :: BinHandle -> AnonArgFlag -> IO ()

put :: BinHandle -> AnonArgFlag -> IO (Bin AnonArgFlag)

get :: BinHandle -> IO AnonArgFlag

Outputable AnonArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: AnonArgFlag -> SDoc

data ArgFlag #

Bundled Patterns

pattern Specified :: ArgFlag 
pattern Inferred :: ArgFlag 

Instances

Instances details
Eq ArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

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

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

Data ArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: ArgFlag -> Constr #

dataTypeOf :: ArgFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ArgFlag 
Instance details

Defined in GHC.Types.Var

Binary ArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

put_ :: BinHandle -> ArgFlag -> IO ()

put :: BinHandle -> ArgFlag -> IO (Bin ArgFlag)

get :: BinHandle -> IO ArgFlag

Outputable ArgFlag 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: ArgFlag -> SDoc

Outputable tv => Outputable (VarBndr tv ArgFlag) 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv ArgFlag -> SDoc

data Specificity #

Instances

Instances details
Eq Specificity 
Instance details

Defined in GHC.Types.Var

Data Specificity 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Specificity -> Constr #

dataTypeOf :: Specificity -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Specificity 
Instance details

Defined in GHC.Types.Var

Binary Specificity 
Instance details

Defined in GHC.Types.Var

Methods

put_ :: BinHandle -> Specificity -> IO ()

put :: BinHandle -> Specificity -> IO (Bin Specificity)

get :: BinHandle -> IO Specificity

OutputableBndrFlag Specificity 
Instance details

Defined in GHC.Hs.Type

Methods

pprTyVarBndr :: forall (p :: Pass). OutputableBndrId p => HsTyVarBndr Specificity (GhcPass p) -> SDoc

Outputable tv => Outputable (VarBndr tv Specificity) 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv Specificity -> SDoc

type TyCoVar = Id #

type TyVar = Var #

type TyVarBinder = VarBndr TyVar ArgFlag #

data Var #

Instances

Instances details
Eq Var 
Instance details

Defined in GHC.Types.Var

Methods

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

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

Data Var 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Var -> Constr #

dataTypeOf :: Var -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Var 
Instance details

Defined in GHC.Types.Var

Methods

compare :: Var -> Var -> Ordering #

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

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

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Uniquable Var 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique #

Outputable Var 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc

NamedThing Var 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

HasOccName Var 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName #

Eq (DeBruijn CoreExpr) 
Instance details

Defined in GHC.Core.Map

Methods

(==) :: DeBruijn CoreExpr -> DeBruijn CoreExpr -> Bool #

(/=) :: DeBruijn CoreExpr -> DeBruijn CoreExpr -> Bool #

Eq (DeBruijn CoreAlt) 
Instance details

Defined in GHC.Core.Map

Methods

(==) :: DeBruijn CoreAlt -> DeBruijn CoreAlt -> Bool #

(/=) :: DeBruijn CoreAlt -> DeBruijn CoreAlt -> Bool #

pickLR :: LeftOrRight -> (a, a) -> a #

data LeftOrRight #

Constructors

CLeft 
CRight 

Instances

Instances details
Eq LeftOrRight 
Instance details

Defined in GHC.Types.Basic

Data LeftOrRight 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

toConstr :: LeftOrRight -> Constr #

dataTypeOf :: LeftOrRight -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary LeftOrRight 
Instance details

Defined in GHC.Types.Basic

Methods

put_ :: BinHandle -> LeftOrRight -> IO ()

put :: BinHandle -> LeftOrRight -> IO (Bin LeftOrRight)

get :: BinHandle -> IO LeftOrRight

Outputable LeftOrRight 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: LeftOrRight -> SDoc

type TyCoVar = Id #

data Var #

Instances

Instances details
Eq Var 
Instance details

Defined in GHC.Types.Var

Methods

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

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

Data Var 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Var -> Constr #

dataTypeOf :: Var -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Var 
Instance details

Defined in GHC.Types.Var

Methods

compare :: Var -> Var -> Ordering #

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

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

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Uniquable Var 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique #

Outputable Var 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc

NamedThing Var 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

HasOccName Var 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName #

Eq (DeBruijn CoreExpr) 
Instance details

Defined in GHC.Core.Map

Methods

(==) :: DeBruijn CoreExpr -> DeBruijn CoreExpr -> Bool #

(/=) :: DeBruijn CoreExpr -> DeBruijn CoreExpr -> Bool #

Eq (DeBruijn CoreAlt) 
Instance details

Defined in GHC.Core.Map

Methods

(==) :: DeBruijn CoreAlt -> DeBruijn CoreAlt -> Bool #

(/=) :: DeBruijn CoreAlt -> DeBruijn CoreAlt -> Bool #

type CoVar = Id #

data Coercion #

Instances

Instances details
Data Coercion 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Coercion -> Constr #

dataTypeOf :: Coercion -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable Coercion 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Coercion -> SDoc

Eq (DeBruijn Coercion) 
Instance details

Defined in GHC.Core.Map

Methods

(==) :: DeBruijn Coercion -> DeBruijn Coercion -> Bool #

(/=) :: DeBruijn Coercion -> DeBruijn Coercion -> Bool #

data CoercionHole #

Instances

Instances details
Data CoercionHole 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: CoercionHole -> Constr #

dataTypeOf :: CoercionHole -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable CoercionHole 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: CoercionHole -> SDoc

data Role #

Instances

Instances details
Eq Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

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

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

Data Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

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

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

toConstr :: Role -> Constr #

dataTypeOf :: Role -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

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 #

Binary Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

put_ :: BinHandle -> Role -> IO ()

put :: BinHandle -> Role -> IO (Bin Role)

get :: BinHandle -> IO Role

Outputable Role 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: Role -> SDoc

coVarKindsTypesRole :: HasDebugCallStack => CoVar -> (Kind, Kind, Type, Type, Role) #

coVarTypes :: HasDebugCallStack => CoVar -> Pair Type #

coercionKinds :: [Coercion] -> Pair [Type] #

decomposeCo :: Arity -> Coercion -> [Role] -> [Coercion] #

decomposeFunCo :: HasDebugCallStack => Role -> Coercion -> (CoercionN, Coercion, Coercion) #

decomposePiCos :: HasDebugCallStack => CoercionN -> Pair Type -> [Type] -> ([CoercionN], CoercionN) #

eqCoercionX :: RnEnv2 -> Coercion -> Coercion -> Bool #

etaExpandCoAxBranch :: CoAxBranch -> ([TyVar], [Type], Type) #

liftCoSubst :: HasDebugCallStack => Role -> LiftingContext -> Type -> Coercion #

liftCoSubstWithEx :: Role -> [TyVar] -> [Coercion] -> [TyCoVar] -> [Type] -> (Type -> Coercion, [Type]) #

ltRole :: Role -> Role -> Bool #

mkAxInstCo :: forall (br :: BranchFlag). Role -> CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Coercion #

mkAxInstLHS :: forall (br :: BranchFlag). CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Type #

mkAxInstRHS :: forall (br :: BranchFlag). CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Type #

mkAxiomInstCo :: CoAxiom Branched -> BranchIndex -> [Coercion] -> Coercion #

mkAxiomRuleCo :: CoAxiomRule -> [Coercion] -> Coercion #

mkGReflCo :: Role -> Type -> MCoercionN -> Coercion #

mkNthCo :: HasDebugCallStack => Role -> Int -> Coercion -> Coercion #

mkTyConAppCo :: HasDebugCallStack => Role -> TyCon -> [Coercion] -> Coercion #

mkUnbranchedAxInstCo :: Role -> CoAxiom Unbranched -> [Type] -> [Coercion] -> Coercion #

mkUnbranchedAxInstLHS :: CoAxiom Unbranched -> [Type] -> [Coercion] -> Type #

mkUnbranchedAxInstRHS :: CoAxiom Unbranched -> [Type] -> [Coercion] -> Type #

nthRole :: Role -> TyCon -> Int -> Role #

pprCoAxBranch :: TyCon -> CoAxBranch -> SDoc #

pprCoAxBranchLHS :: TyCon -> CoAxBranch -> SDoc #

pprCoAxBranchUser :: TyCon -> CoAxBranch -> SDoc #

pprCoAxiom :: forall (br :: BranchFlag). CoAxiom br -> SDoc #

seqCo :: Coercion -> () #

simplifyArgsWorker :: [TyCoBinder] -> Kind -> TyCoVarSet -> [Role] -> [(Type, Coercion)] -> ([Type], [Coercion], CoercionN) #

tidyCoAxBndrsForUser :: TidyEnv -> [Var] -> (TidyEnv, [Var]) #

topNormaliseTypeX :: NormaliseStepper ev -> (ev -> ev -> ev) -> Type -> Maybe (ev, Type) #

coVarsOfCo :: Coercion -> CoVarSet #

tyCoVarsOfCo :: Coercion -> TyCoVarSet #

tyCoVarsOfCoDSet :: Coercion -> DTyCoVarSet #

tyCoVarsOfCos :: [Coercion] -> TyCoVarSet #

pprCo :: Coercion -> SDoc #

tidyCo :: TidyEnv -> Coercion -> Coercion #

tidyCos :: TidyEnv -> [Coercion] -> [Coercion] #

type LiftCoEnv = VarEnv Coercion #

data LiftingContext #

Constructors

LC TCvSubst LiftCoEnv 

Instances

Instances details
Outputable LiftingContext 
Instance details

Defined in GHC.Core.Coercion

Methods

ppr :: LiftingContext -> SDoc

data NormaliseStepResult ev #

Constructors

NS_Done 
NS_Abort 
NS_Step RecTcChecker Type ev 

type NormaliseStepper ev = RecTcChecker -> TyCon -> [Type] -> NormaliseStepResult ev #

data BlockSubstFlag #

Instances

Instances details
Outputable BlockSubstFlag 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: BlockSubstFlag -> SDoc

data MCoercion #

Constructors

MRefl 
MCo Coercion 

Instances

Instances details
Data MCoercion 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: MCoercion -> Constr #

dataTypeOf :: MCoercion -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable MCoercion 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: MCoercion -> SDoc

data UnivCoProvenance #

Instances

Instances details
Data UnivCoProvenance 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: UnivCoProvenance -> Constr #

dataTypeOf :: UnivCoProvenance -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable UnivCoProvenance 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: UnivCoProvenance -> SDoc

type CvSubstEnv = CoVarEnv Coercion #

class Uniquable a where #

Methods

getUnique :: a -> Unique #

Instances

Instances details
Uniquable Int 
Instance details

Defined in GHC.Types.Unique

Methods

getUnique :: Int -> Unique #

Uniquable Unique 
Instance details

Defined in GHC.Types.Unique

Methods

getUnique :: Unique -> Unique #

Uniquable Module 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Module -> Unique #

Uniquable Name 
Instance details

Defined in GHC.Types.Name

Methods

getUnique :: Name -> Unique #

Uniquable FastString 
Instance details

Defined in GHC.Types.Unique

Methods

getUnique :: FastString -> Unique #

Uniquable ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Uniquable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

getUnique :: OccName -> Unique #

Uniquable UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: UnitId -> Unique #

Uniquable Var 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique #

Uniquable TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

getUnique :: TyCon -> Unique #

Uniquable Class 
Instance details

Defined in GHC.Core.Class

Methods

getUnique :: Class -> Unique #

Uniquable DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

getUnique :: DataCon -> Unique #

Uniquable CoAxiomRule 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getUnique :: CoAxiomRule -> Unique #

Uniquable EvBindsVar 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

getUnique :: EvBindsVar -> Unique #

Uniquable ConLike 
Instance details

Defined in GHC.Core.ConLike

Methods

getUnique :: ConLike -> Unique #

Uniquable PatSyn 
Instance details

Defined in GHC.Core.PatSyn

Methods

getUnique :: PatSyn -> Unique #

Uniquable LocalReg 
Instance details

Defined in GHC.Cmm.Expr

Methods

getUnique :: LocalReg -> Unique #

Uniquable Label 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

getUnique :: Label -> Unique #

Uniquable RealReg 
Instance details

Defined in GHC.Platform.Reg

Methods

getUnique :: RealReg -> Unique #

Uniquable Reg 
Instance details

Defined in GHC.Platform.Reg

Methods

getUnique :: Reg -> Unique #

Uniquable VirtualReg 
Instance details

Defined in GHC.Platform.Reg

Methods

getUnique :: VirtualReg -> Unique #

Uniquable RegClass 
Instance details

Defined in GHC.Platform.Reg.Class

Methods

getUnique :: RegClass -> Unique #

Uniquable Reg Source #

so we can put regs in UniqSets

Instance details

Defined in GHC.CmmToAsm.Reg.Graph.Base

Methods

getUnique :: Reg -> Unique #

Uniquable PackageId 
Instance details

Defined in GHC.Unit.Info

Methods

getUnique :: PackageId -> Unique #

Uniquable PackageName 
Instance details

Defined in GHC.Unit.Info

Methods

getUnique :: PackageName -> Unique #

Uniquable unit => Uniquable (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Definite unit -> Unique #

IsUnitId u => Uniquable (GenUnit u) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: GenUnit u -> Unique #

Uniquable unit => Uniquable (Indefinite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Indefinite unit -> Unique #

Uniquable (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getUnique :: CoAxiom br -> Unique #

data Unique #

Instances

Instances details
Eq Unique 
Instance details

Defined in GHC.Types.Unique

Methods

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

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

Show Unique 
Instance details

Defined in GHC.Types.Unique

Uniquable Unique 
Instance details

Defined in GHC.Types.Unique

Methods

getUnique :: Unique -> Unique #

Outputable Unique 
Instance details

Defined in GHC.Types.Unique

Methods

ppr :: Unique -> SDoc

Getting Names

thNameToGhcName :: Name -> CoreM (Maybe Name) Source #

Attempt to convert a Template Haskell name to one that GHC can understand. Original TH names such as those you get when you use the 'foo syntax will be translated to their equivalent GHC name exactly. Qualified or unqualified TH names will be dynamically bound to names in the module being compiled, if possible. Exact TH names will be bound to the name they represent, exactly.

Orphan instances

MonadThings CoreM Source # 
Instance details

Methods

lookupThing :: Name -> CoreM TyThing

lookupId :: Name -> CoreM Id

lookupDataCon :: Name -> CoreM DataCon

lookupTyCon :: Name -> CoreM TyCon