Safe Haskell | Ignore |
---|---|
Language | GHC2021 |
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
- module GHC.Driver.Plugins
- module GHC.Types.Name.Reader
- data NameSpace
- data OccName
- class HasOccName name where
- type FastStringEnv a = UniqFM FastString a
- type TidyOccEnv = UniqFM FastString Int
- data OccSet
- data OccEnv a
- mkOccName :: NameSpace -> String -> OccName
- isSymOcc :: OccName -> Bool
- mkVarOccFS :: FastString -> OccName
- emptyFsEnv :: FastStringEnv a
- extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a
- lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a
- mkFsEnv :: [(FastString, a)] -> FastStringEnv a
- tcName :: NameSpace
- clsName :: NameSpace
- tcClsName :: NameSpace
- dataName :: NameSpace
- srcDataName :: NameSpace
- tvName :: NameSpace
- fieldName :: FastString -> NameSpace
- isDataConNameSpace :: NameSpace -> Bool
- isTcClsNameSpace :: NameSpace -> Bool
- isTvNameSpace :: NameSpace -> Bool
- isVarNameSpace :: NameSpace -> Bool
- isTermVarOrFieldNameSpace :: NameSpace -> Bool
- isValNameSpace :: NameSpace -> Bool
- isFieldNameSpace :: NameSpace -> Bool
- pprNameSpace :: NameSpace -> SDoc
- pprNonVarNameSpace :: NameSpace -> SDoc
- pprNameSpaceBrief :: NameSpace -> SDoc
- pprOccName :: IsLine doc => OccName -> doc
- occNameMangledFS :: OccName -> FastString
- mkOccNameFS :: NameSpace -> FastString -> OccName
- mkVarOcc :: String -> OccName
- mkRecFieldOcc :: FastString -> String -> OccName
- mkRecFieldOccFS :: FastString -> FastString -> OccName
- varToRecFieldOcc :: HasDebugCallStack => FastString -> OccName -> OccName
- recFieldToVarOcc :: HasDebugCallStack => OccName -> OccName
- mkDataOcc :: String -> OccName
- mkDataOccFS :: FastString -> OccName
- mkTyVarOcc :: String -> OccName
- mkTyVarOccFS :: FastString -> OccName
- mkTcOcc :: String -> OccName
- mkTcOccFS :: FastString -> OccName
- mkClsOcc :: String -> OccName
- mkClsOccFS :: FastString -> OccName
- demoteOccName :: OccName -> Maybe OccName
- demoteOccTvName :: OccName -> Maybe OccName
- promoteOccName :: OccName -> Maybe OccName
- emptyOccEnv :: OccEnv a
- unitOccEnv :: OccName -> a -> OccEnv a
- extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a
- extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a
- lookupOccEnv :: OccEnv a -> OccName -> Maybe a
- lookupOccEnv_AllNameSpaces :: OccEnv a -> OccName -> [a]
- lookupOccEnv_WithFields :: OccEnv a -> OccName -> [a]
- lookupFieldsOccEnv :: OccEnv a -> FastString -> [a]
- mkOccEnv :: [(OccName, a)] -> OccEnv a
- mkOccEnv_C :: (a -> a -> a) -> [(OccName, a)] -> OccEnv a
- elemOccEnv :: OccName -> OccEnv a -> Bool
- nonDetFoldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b
- nonDetOccEnvElts :: OccEnv a -> [a]
- plusOccEnv :: OccEnv a -> OccEnv a -> OccEnv a
- plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a
- mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b
- mapMaybeOccEnv :: (a -> Maybe b) -> OccEnv a -> OccEnv b
- extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b
- delFromOccEnv :: OccEnv a -> OccName -> OccEnv a
- delListFromOccEnv :: OccEnv a -> [OccName] -> OccEnv a
- filterOccEnv :: (a -> Bool) -> OccEnv a -> OccEnv a
- alterOccEnv :: (Maybe a -> Maybe a) -> OccEnv a -> OccName -> OccEnv a
- intersectOccEnv_C :: (a -> b -> c) -> OccEnv a -> OccEnv b -> OccEnv c
- minusOccEnv :: OccEnv a -> OccEnv b -> OccEnv a
- minusOccEnv_C :: (a -> b -> Maybe a) -> OccEnv a -> OccEnv b -> OccEnv a
- minusOccEnv_C_Ns :: (UniqFM NameSpace a -> UniqFM NameSpace b -> UniqFM NameSpace a) -> OccEnv a -> OccEnv b -> OccEnv a
- pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc
- strictMapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b
- forceOccEnv :: (a -> ()) -> OccEnv a -> ()
- emptyOccSet :: OccSet
- unitOccSet :: OccName -> OccSet
- mkOccSet :: [OccName] -> OccSet
- extendOccSet :: OccSet -> OccName -> OccSet
- extendOccSetList :: OccSet -> [OccName] -> OccSet
- unionOccSets :: OccSet -> OccSet -> OccSet
- unionManyOccSets :: [OccSet] -> OccSet
- elemOccSet :: OccName -> OccSet -> Bool
- isEmptyOccSet :: OccSet -> Bool
- occNameString :: OccName -> String
- setOccNameSpace :: NameSpace -> OccName -> OccName
- isVarOcc :: OccName -> Bool
- isTvOcc :: OccName -> Bool
- isTcOcc :: OccName -> Bool
- isFieldOcc :: OccName -> Bool
- fieldOcc_maybe :: OccName -> Maybe FastString
- isValOcc :: OccName -> Bool
- isDataOcc :: OccName -> Bool
- isDataSymOcc :: OccName -> Bool
- parenSymOcc :: OccName -> SDoc -> SDoc
- startsWithUnderscore :: OccName -> Bool
- isUnderscore :: OccName -> Bool
- isDerivedOccName :: OccName -> Bool
- isDefaultMethodOcc :: OccName -> Bool
- isTypeableBindOcc :: OccName -> Bool
- mkDataConWrapperOcc :: OccName -> OccName
- mkWorkerOcc :: OccName -> OccName
- mkMatcherOcc :: OccName -> OccName
- mkBuilderOcc :: OccName -> OccName
- mkDefaultMethodOcc :: OccName -> OccName
- mkClassOpAuxOcc :: OccName -> OccName
- mkDictOcc :: OccName -> OccName
- mkIPOcc :: OccName -> OccName
- mkSpecOcc :: OccName -> OccName
- mkForeignExportOcc :: OccName -> OccName
- mkRepEqOcc :: OccName -> OccName
- mkClassDataConOcc :: OccName -> OccName
- mkNewTyCoOcc :: OccName -> OccName
- mkInstTyCoOcc :: OccName -> OccName
- mkEqPredCoOcc :: OccName -> OccName
- mkCon2TagOcc :: OccName -> OccName
- mkTag2ConOcc :: OccName -> OccName
- mkMaxTagOcc :: OccName -> OccName
- mkDataTOcc :: OccName -> OccName
- mkDataCOcc :: OccName -> OccName
- mkTyConRepOcc :: OccName -> OccName
- mkGenR :: OccName -> OccName
- mkGen1R :: OccName -> OccName
- mkDataConWorkerOcc :: OccName -> OccName
- mkSuperDictAuxOcc :: Int -> OccName -> OccName
- mkSuperDictSelOcc :: Int -> OccName -> OccName
- mkLocalOcc :: Unique -> OccName -> OccName
- mkInstTyTcOcc :: String -> OccSet -> OccName
- mkDFunOcc :: String -> Bool -> OccSet -> OccName
- mkMethodOcc :: OccName -> OccName
- emptyTidyOccEnv :: TidyOccEnv
- initTidyOccEnv :: [OccName] -> TidyOccEnv
- delTidyOccEnvList :: TidyOccEnv -> [FastString] -> TidyOccEnv
- avoidClashesOccEnv :: TidyOccEnv -> [OccName] -> TidyOccEnv
- tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName)
- mainOcc :: OccName
- ppMainFn :: OccName -> SDoc
- data NameSpace
- data Name
- data OccName
- class HasOccName name where
- class NamedThing a where
- getOccName :: a -> OccName
- getName :: a -> Name
- type FastStringEnv a = UniqFM FastString a
- type TidyOccEnv = UniqFM FastString Int
- data OccSet
- data OccEnv a
- data BuiltInSyntax
- mkOccName :: NameSpace -> String -> OccName
- nameModule :: HasDebugCallStack => Name -> Module
- pprName :: IsLine doc => Name -> doc
- isSymOcc :: OccName -> Bool
- mkVarOccFS :: FastString -> OccName
- isFieldName :: Name -> Bool
- tidyNameOcc :: Name -> OccName -> Name
- nameOccName :: Name -> OccName
- setNameUnique :: Name -> Unique -> Name
- nameUnique :: Name -> Unique
- emptyFsEnv :: FastStringEnv a
- extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a
- lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a
- mkFsEnv :: [(FastString, a)] -> FastStringEnv a
- tcName :: NameSpace
- clsName :: NameSpace
- tcClsName :: NameSpace
- dataName :: NameSpace
- srcDataName :: NameSpace
- tvName :: NameSpace
- fieldName :: FastString -> NameSpace
- isDataConNameSpace :: NameSpace -> Bool
- isTcClsNameSpace :: NameSpace -> Bool
- isTvNameSpace :: NameSpace -> Bool
- isVarNameSpace :: NameSpace -> Bool
- isTermVarOrFieldNameSpace :: NameSpace -> Bool
- isValNameSpace :: NameSpace -> Bool
- isFieldNameSpace :: NameSpace -> Bool
- pprNameSpace :: NameSpace -> SDoc
- pprNonVarNameSpace :: NameSpace -> SDoc
- pprNameSpaceBrief :: NameSpace -> SDoc
- pprOccName :: IsLine doc => OccName -> doc
- occNameMangledFS :: OccName -> FastString
- mkOccNameFS :: NameSpace -> FastString -> OccName
- mkVarOcc :: String -> OccName
- mkRecFieldOcc :: FastString -> String -> OccName
- mkRecFieldOccFS :: FastString -> FastString -> OccName
- varToRecFieldOcc :: HasDebugCallStack => FastString -> OccName -> OccName
- recFieldToVarOcc :: HasDebugCallStack => OccName -> OccName
- mkDataOcc :: String -> OccName
- mkDataOccFS :: FastString -> OccName
- mkTyVarOcc :: String -> OccName
- mkTyVarOccFS :: FastString -> OccName
- mkTcOcc :: String -> OccName
- mkTcOccFS :: FastString -> OccName
- mkClsOcc :: String -> OccName
- mkClsOccFS :: FastString -> OccName
- demoteOccName :: OccName -> Maybe OccName
- demoteOccTvName :: OccName -> Maybe OccName
- promoteOccName :: OccName -> Maybe OccName
- emptyOccEnv :: OccEnv a
- unitOccEnv :: OccName -> a -> OccEnv a
- extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a
- extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a
- lookupOccEnv :: OccEnv a -> OccName -> Maybe a
- lookupOccEnv_AllNameSpaces :: OccEnv a -> OccName -> [a]
- lookupOccEnv_WithFields :: OccEnv a -> OccName -> [a]
- lookupFieldsOccEnv :: OccEnv a -> FastString -> [a]
- mkOccEnv :: [(OccName, a)] -> OccEnv a
- mkOccEnv_C :: (a -> a -> a) -> [(OccName, a)] -> OccEnv a
- elemOccEnv :: OccName -> OccEnv a -> Bool
- nonDetFoldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b
- nonDetOccEnvElts :: OccEnv a -> [a]
- plusOccEnv :: OccEnv a -> OccEnv a -> OccEnv a
- plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a
- mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b
- mapMaybeOccEnv :: (a -> Maybe b) -> OccEnv a -> OccEnv b
- extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b
- delFromOccEnv :: OccEnv a -> OccName -> OccEnv a
- delListFromOccEnv :: OccEnv a -> [OccName] -> OccEnv a
- filterOccEnv :: (a -> Bool) -> OccEnv a -> OccEnv a
- alterOccEnv :: (Maybe a -> Maybe a) -> OccEnv a -> OccName -> OccEnv a
- intersectOccEnv_C :: (a -> b -> c) -> OccEnv a -> OccEnv b -> OccEnv c
- minusOccEnv :: OccEnv a -> OccEnv b -> OccEnv a
- minusOccEnv_C :: (a -> b -> Maybe a) -> OccEnv a -> OccEnv b -> OccEnv a
- minusOccEnv_C_Ns :: (UniqFM NameSpace a -> UniqFM NameSpace b -> UniqFM NameSpace a) -> OccEnv a -> OccEnv b -> OccEnv a
- pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc
- strictMapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b
- forceOccEnv :: (a -> ()) -> OccEnv a -> ()
- emptyOccSet :: OccSet
- unitOccSet :: OccName -> OccSet
- mkOccSet :: [OccName] -> OccSet
- extendOccSet :: OccSet -> OccName -> OccSet
- extendOccSetList :: OccSet -> [OccName] -> OccSet
- unionOccSets :: OccSet -> OccSet -> OccSet
- unionManyOccSets :: [OccSet] -> OccSet
- elemOccSet :: OccName -> OccSet -> Bool
- isEmptyOccSet :: OccSet -> Bool
- occNameString :: OccName -> String
- setOccNameSpace :: NameSpace -> OccName -> OccName
- isVarOcc :: OccName -> Bool
- isTvOcc :: OccName -> Bool
- isTcOcc :: OccName -> Bool
- isFieldOcc :: OccName -> Bool
- fieldOcc_maybe :: OccName -> Maybe FastString
- isValOcc :: OccName -> Bool
- isDataOcc :: OccName -> Bool
- isDataSymOcc :: OccName -> Bool
- parenSymOcc :: OccName -> SDoc -> SDoc
- startsWithUnderscore :: OccName -> Bool
- isUnderscore :: OccName -> Bool
- isDerivedOccName :: OccName -> Bool
- isDefaultMethodOcc :: OccName -> Bool
- isTypeableBindOcc :: OccName -> Bool
- mkDataConWrapperOcc :: OccName -> OccName
- mkWorkerOcc :: OccName -> OccName
- mkMatcherOcc :: OccName -> OccName
- mkBuilderOcc :: OccName -> OccName
- mkDefaultMethodOcc :: OccName -> OccName
- mkClassOpAuxOcc :: OccName -> OccName
- mkDictOcc :: OccName -> OccName
- mkIPOcc :: OccName -> OccName
- mkSpecOcc :: OccName -> OccName
- mkForeignExportOcc :: OccName -> OccName
- mkRepEqOcc :: OccName -> OccName
- mkClassDataConOcc :: OccName -> OccName
- mkNewTyCoOcc :: OccName -> OccName
- mkInstTyCoOcc :: OccName -> OccName
- mkEqPredCoOcc :: OccName -> OccName
- mkCon2TagOcc :: OccName -> OccName
- mkTag2ConOcc :: OccName -> OccName
- mkMaxTagOcc :: OccName -> OccName
- mkDataTOcc :: OccName -> OccName
- mkDataCOcc :: OccName -> OccName
- mkTyConRepOcc :: OccName -> OccName
- mkGenR :: OccName -> OccName
- mkGen1R :: OccName -> OccName
- mkDataConWorkerOcc :: OccName -> OccName
- mkSuperDictAuxOcc :: Int -> OccName -> OccName
- mkSuperDictSelOcc :: Int -> OccName -> OccName
- mkLocalOcc :: Unique -> OccName -> OccName
- mkInstTyTcOcc :: String -> OccSet -> OccName
- mkDFunOcc :: String -> Bool -> OccSet -> OccName
- mkMethodOcc :: OccName -> OccName
- emptyTidyOccEnv :: TidyOccEnv
- initTidyOccEnv :: [OccName] -> TidyOccEnv
- delTidyOccEnvList :: TidyOccEnv -> [FastString] -> TidyOccEnv
- avoidClashesOccEnv :: TidyOccEnv -> [OccName] -> TidyOccEnv
- tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName)
- mainOcc :: OccName
- ppMainFn :: OccName -> SDoc
- nameNameSpace :: Name -> NameSpace
- nameSrcLoc :: Name -> SrcLoc
- nameSrcSpan :: Name -> SrcSpan
- isWiredInName :: Name -> Bool
- isWiredIn :: NamedThing thing => thing -> Bool
- wiredInNameTyThing_maybe :: Name -> Maybe TyThing
- isBuiltInSyntax :: Name -> Bool
- isTupleTyConName :: Name -> Bool
- isSumTyConName :: Name -> Bool
- isUnboxedTupleDataConLikeName :: Name -> Bool
- isExternalName :: Name -> Bool
- isInternalName :: Name -> Bool
- isHoleName :: Name -> Bool
- isDynLinkName :: Platform -> Module -> Name -> Bool
- nameModule_maybe :: Name -> Maybe Module
- namePun_maybe :: Name -> Maybe FastString
- nameIsLocalOrFrom :: Module -> Name -> Bool
- nameIsExternalOrFrom :: Module -> Name -> Bool
- nameIsHomePackage :: Module -> Name -> Bool
- nameIsHomePackageImport :: Module -> Name -> Bool
- nameIsFromExternalPackage :: HomeUnit -> Name -> Bool
- isTyVarName :: Name -> Bool
- isTyConName :: Name -> Bool
- isDataConName :: Name -> Bool
- isValName :: Name -> Bool
- isVarName :: Name -> Bool
- isSystemName :: Name -> Bool
- mkInternalName :: Unique -> OccName -> SrcSpan -> Name
- mkClonedInternalName :: Unique -> Name -> Name
- mkDerivedInternalName :: (OccName -> OccName) -> Unique -> Name -> Name
- mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name
- mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name
- mkSystemName :: Unique -> OccName -> Name
- mkSystemNameAt :: Unique -> OccName -> SrcSpan -> Name
- mkSystemVarName :: Unique -> FastString -> Name
- mkSysTvName :: Unique -> FastString -> Name
- mkFCallName :: Unique -> FastString -> Name
- setNameLoc :: Name -> SrcSpan -> Name
- localiseName :: Name -> Name
- stableNameCmp :: Name -> Name -> Ordering
- pprFullName :: Module -> Name -> SDoc
- pprTickyName :: Module -> Name -> SDoc
- pprNameUnqualified :: Name -> SDoc
- pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc
- pprDefinedAt :: Name -> SDoc
- pprNameDefnLoc :: Name -> SDoc
- nameStableString :: Name -> String
- getSrcLoc :: NamedThing a => a -> SrcLoc
- getSrcSpan :: NamedThing a => a -> SrcSpan
- getOccString :: NamedThing a => a -> String
- getOccFS :: NamedThing a => a -> FastString
- pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc
- pprPrefixName :: NamedThing a => a -> SDoc
- module GHC.Types.Var
- type Id = Var
- data JoinPointHood
- data Var
- type OutId = Id
- type OutVar = Var
- type InId = Id
- type InVar = Var
- type JoinId = Id
- type IdUnfoldingFun = Id -> Unfolding
- idName :: Id -> Name
- idInfo :: HasDebugCallStack => Id -> IdInfo
- idDetails :: Id -> IdDetails
- globaliseId :: Id -> Id
- updateIdTypeButNotMult :: (Type -> Type) -> Id -> Id
- updateIdTypeAndMult :: (Type -> Type) -> Id -> Id
- updateIdTypeAndMultM :: Monad m => (Type -> m Type) -> Id -> m Id
- setIdMult :: Id -> Mult -> Id
- isId :: Var -> Bool
- isLocalId :: Var -> Bool
- isGlobalId :: Var -> Bool
- isExportedId :: Var -> Bool
- idUnique :: Id -> Unique
- idType :: Id -> Kind
- idMult :: Id -> Mult
- idScaledType :: Id -> Scaled Type
- scaleIdBy :: Mult -> Id -> Id
- scaleVarBy :: Mult -> Var -> Var
- setIdName :: Id -> Name -> Id
- setIdUnique :: Id -> Unique -> Id
- setIdType :: Id -> Type -> Id
- localiseId :: Id -> Id
- setIdInfo :: Id -> IdInfo -> Id
- modifyIdInfo :: HasDebugCallStack => (IdInfo -> IdInfo) -> Id -> Id
- maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id
- mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id
- mkVanillaGlobal :: Name -> Type -> Id
- mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id
- mkLocalId :: HasDebugCallStack => Name -> Mult -> Type -> Id
- mkLocalCoVar :: Name -> Type -> CoVar
- mkLocalIdOrCoVar :: Name -> Mult -> Type -> Id
- mkLocalIdWithInfo :: HasDebugCallStack => Name -> Mult -> Type -> IdInfo -> Id
- mkExportedLocalId :: IdDetails -> Name -> Type -> Id
- mkExportedVanillaId :: Name -> Type -> Id
- mkSysLocal :: FastString -> Unique -> Mult -> Type -> Id
- mkSysLocalOrCoVar :: FastString -> Unique -> Mult -> Type -> Id
- mkSysLocalM :: MonadUnique m => FastString -> Mult -> Type -> m Id
- mkSysLocalOrCoVarM :: MonadUnique m => FastString -> Mult -> Type -> m Id
- mkUserLocal :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id
- mkUserLocalOrCoVar :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id
- mkWorkerId :: Unique -> Id -> Type -> Id
- mkTemplateLocal :: Int -> Type -> Id
- mkScaledTemplateLocal :: Int -> Scaled Type -> Id
- mkTemplateLocals :: [Type] -> [Id]
- mkTemplateLocalsNum :: Int -> [Type] -> [Id]
- recordSelectorTyCon :: Id -> RecSelParent
- recordSelectorTyCon_maybe :: Id -> Maybe RecSelParent
- isRecordSelector :: Id -> Bool
- isDataConRecordSelector :: Id -> Bool
- isPatSynRecordSelector :: Id -> Bool
- isNaughtyRecordSelector :: Id -> Bool
- isClassOpId :: Id -> Bool
- isClassOpId_maybe :: Id -> Maybe Class
- isPrimOpId :: Id -> Bool
- isDFunId :: Id -> Bool
- isPrimOpId_maybe :: Id -> Maybe PrimOp
- isFCallId :: Id -> Bool
- isFCallId_maybe :: Id -> Maybe ForeignCall
- isDataConWorkId :: Id -> Bool
- isDataConWorkId_maybe :: Id -> Maybe DataCon
- isDataConWrapId :: Id -> Bool
- isDataConWrapId_maybe :: Id -> Maybe DataCon
- isDataConId_maybe :: Id -> Maybe DataCon
- isWorkerLikeId :: Id -> Bool
- isJoinId :: Var -> Bool
- idJoinPointHood :: Var -> JoinPointHood
- idDataCon :: Id -> DataCon
- hasNoBinding :: Id -> Bool
- isImplicitId :: Id -> Bool
- idIsFrom :: Module -> Id -> Bool
- isDeadBinder :: Id -> Bool
- idJoinArity :: JoinId -> JoinArity
- asJoinId :: Id -> JoinArity -> JoinId
- zapJoinId :: Id -> Id
- asJoinId_maybe :: Id -> JoinPointHood -> Id
- idArity :: Id -> Arity
- setIdArity :: Id -> Arity -> Id
- idCallArity :: Id -> Arity
- setIdCallArity :: Id -> Arity -> Id
- idFunRepArity :: Id -> RepArity
- isDeadEndId :: Var -> Bool
- idDmdSig :: Id -> DmdSig
- setIdDmdSig :: Id -> DmdSig -> Id
- idCprSig :: Id -> CprSig
- setIdCprSig :: Id -> CprSig -> Id
- zapIdDmdSig :: Id -> Id
- isStrictId :: Id -> Bool
- idTagSig_maybe :: Id -> Maybe TagSig
- idUnfolding :: IdUnfoldingFun
- noUnfoldingFun :: IdUnfoldingFun
- alwaysActiveUnfoldingFun :: IdUnfoldingFun
- whenActiveUnfoldingFun :: (Activation -> Bool) -> IdUnfoldingFun
- realIdUnfolding :: Id -> Unfolding
- setIdUnfolding :: Id -> Unfolding -> Id
- idDemandInfo :: Id -> Demand
- setIdDemandInfo :: Id -> Demand -> Id
- setIdTagSig :: Id -> TagSig -> Id
- setIdCbvMarks :: Id -> [CbvMark] -> Id
- idCbvMarks_maybe :: Id -> Maybe [CbvMark]
- idCbvMarkArity :: Id -> Arity
- asNonWorkerLikeId :: Id -> Id
- asWorkerLikeId :: Id -> Id
- setCaseBndrEvald :: StrictnessMark -> Id -> Id
- zapIdUnfolding :: Id -> Id
- idSpecialisation :: Id -> RuleInfo
- idCoreRules :: Id -> [CoreRule]
- idHasRules :: Id -> Bool
- setIdSpecialisation :: Id -> RuleInfo -> Id
- idCafInfo :: Id -> CafInfo
- setIdCafInfo :: Id -> CafInfo -> Id
- idLFInfo_maybe :: Id -> Maybe LambdaFormInfo
- setIdLFInfo :: Id -> LambdaFormInfo -> Id
- idOccInfo :: Id -> OccInfo
- setIdOccInfo :: Id -> OccInfo -> Id
- zapIdOccInfo :: Id -> Id
- idInlinePragma :: Id -> InlinePragma
- setInlinePragma :: Id -> InlinePragma -> Id
- modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> Id
- idInlineActivation :: Id -> Activation
- setInlineActivation :: Id -> Activation -> Id
- idRuleMatchInfo :: Id -> RuleMatchInfo
- isConLikeId :: Id -> Bool
- idOneShotInfo :: Id -> OneShotInfo
- setOneShotLambda :: Id -> Id
- clearOneShotLambda :: Id -> Id
- setIdOneShotInfo :: Id -> OneShotInfo -> Id
- updOneShotInfo :: Id -> OneShotInfo -> Id
- zapLamIdInfo :: Id -> Id
- zapFragileIdInfo :: Id -> Id
- zapIdDemandInfo :: Id -> Id
- zapIdUsageInfo :: Id -> Id
- zapIdUsageEnvInfo :: Id -> Id
- zapIdUsedOnceInfo :: Id -> Id
- zapIdTailCallInfo :: Id -> Id
- zapStableUnfolding :: Id -> Id
- transferPolyIdInfo :: Id -> [Var] -> Id -> Id
- module GHC.Types.Id.Info
- module GHC.Types.PkgQual
- module GHC.Core.Opt.Monad
- module GHC.Core.Opt.Pipeline.Types
- module GHC.Core.Opt.Stats
- module GHC.Core
- module GHC.Types.Literal
- module GHC.Core.DataCon
- module GHC.Core.Utils
- module GHC.Core.Make
- module GHC.Core.FVs
- data InScopeSet
- type TvSubstEnv = TyVarEnv Type
- type IdSubstEnv = IdEnv CoreExpr
- data Subst = Subst InScopeSet IdSubstEnv TvSubstEnv CvSubstEnv
- emptySubst :: Subst
- mkEmptySubst :: InScopeSet -> Subst
- isEmptySubst :: Subst -> Bool
- mkTCvSubst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> Subst
- getSubstInScope :: Subst -> InScopeSet
- setInScope :: Subst -> InScopeSet -> Subst
- isInScope :: Var -> Subst -> Bool
- zapSubst :: Subst -> Subst
- extendSubstInScope :: Subst -> Var -> Subst
- extendSubstInScopeList :: Subst -> [Var] -> Subst
- extendTCvSubst :: Subst -> TyCoVar -> Type -> Subst
- extendTvSubst :: Subst -> TyVar -> Type -> Subst
- extendTvSubstList :: Subst -> [(TyVar, Type)] -> Subst
- substTyUnchecked :: Subst -> Type -> Type
- substCo :: HasDebugCallStack => Subst -> Coercion -> Coercion
- extendIdSubst :: Subst -> Id -> CoreExpr -> Subst
- extendIdSubstWithClone :: Subst -> Id -> Id -> Subst
- extendIdSubstList :: Subst -> [(Id, CoreExpr)] -> Subst
- extendSubst :: Subst -> Var -> CoreArg -> Subst
- extendSubstWithVar :: Subst -> Var -> Var -> Subst
- extendSubstList :: Subst -> [(Var, CoreArg)] -> Subst
- lookupIdSubst :: HasDebugCallStack => Subst -> Id -> CoreExpr
- lookupIdSubst_maybe :: HasDebugCallStack => Subst -> Id -> Maybe CoreExpr
- delBndr :: Subst -> Var -> Subst
- delBndrs :: Subst -> [Var] -> Subst
- mkOpenSubst :: InScopeSet -> [(Var, CoreArg)] -> Subst
- substExprSC :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr
- substExpr :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr
- substBindSC :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind)
- substBind :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind)
- deShadowBinds :: CoreProgram -> CoreProgram
- substBndr :: Subst -> Var -> (Subst, Var)
- substBndrs :: Traversable f => Subst -> f Var -> (Subst, f Var)
- substRecBndrs :: Traversable f => Subst -> f Id -> (Subst, f Id)
- cloneIdBndr :: Subst -> UniqSupply -> Id -> (Subst, Id)
- cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id])
- cloneBndrs :: MonadUnique m => Subst -> [Var] -> m (Subst, [Var])
- cloneBndr :: Subst -> Unique -> Var -> (Subst, Var)
- cloneRecIdBndrs :: MonadUnique m => Subst -> [Id] -> m (Subst, [Id])
- substIdType :: Subst -> Id -> Id
- substIdInfo :: Subst -> Id -> IdInfo -> Maybe IdInfo
- substUnfoldingSC :: Subst -> Unfolding -> Unfolding
- substUnfolding :: Subst -> Unfolding -> Unfolding
- substIdOcc :: Subst -> Id -> Id
- substRuleInfo :: Subst -> Id -> RuleInfo -> RuleInfo
- substRulesForImportedIds :: Subst -> [CoreRule] -> [CoreRule]
- substDVarSet :: HasDebugCallStack => Subst -> DVarSet -> DVarSet
- substTickish :: Subst -> CoreTickish -> CoreTickish
- module GHC.Core.Rules
- module GHC.Types.Annotations
- module GHC.Driver.Session
- module GHC.Driver.Ppr
- module GHC.Unit.State
- module GHC.Unit.Module
- module GHC.Unit.Home
- data Type
- type Kind = Type
- data Specificity
- type TyCoVar = Id
- type TyVar = Var
- data Var
- data FunTyFlag
- data ForAllTyFlag where
- Invisible !Specificity
- Required
- pattern Specified :: ForAllTyFlag
- pattern Inferred :: ForAllTyFlag
- type ThetaType = [PredType]
- type RuntimeRepType = Type
- type PredType = Type
- type Mult = Type
- data Scaled a
- data PiTyBinder
- type TyVarBinder = VarBndr TyVar ForAllTyFlag
- type ForAllTyBinder = VarBndr TyCoVar ForAllTyFlag
- data TyCoFolder env a = TyCoFolder {
- tcf_view :: Type -> Maybe Type
- tcf_tyvar :: env -> TyVar -> a
- tcf_covar :: env -> CoVar -> a
- tcf_hole :: env -> CoercionHole -> a
- tcf_tycobinder :: env -> TyCoVar -> ForAllTyFlag -> env
- type KnotTied (ty :: k) = ty
- type FRRType = Type
- type KindOrType = Type
- type TvSubstEnv = TyVarEnv Type
- type IdSubstEnv = IdEnv CoreExpr
- data Subst = Subst InScopeSet IdSubstEnv TvSubstEnv CvSubstEnv
- type ErrorMsgType = Type
- data TyCoMapper env (m :: Type -> Type) = TyCoMapper {}
- pattern ManyTy :: Mult
- pattern OneTy :: Mult
- funResultTy :: HasDebugCallStack => Type -> Type
- mkFunTy :: HasDebugCallStack => FunTyFlag -> Mult -> Type -> Type -> Type
- splitTyConApp :: Type -> (TyCon, [Type])
- isAlgType :: Type -> Bool
- mkTyConTy :: TyCon -> Type
- typeLevity_maybe :: HasDebugCallStack => Type -> Maybe Levity
- expandTypeSynonyms :: Type -> Type
- mkForAllTy :: ForAllTyBinder -> Type -> Type
- liftedTypeKind :: Type
- unliftedTypeKind :: Type
- isVisibleForAllTyFlag :: ForAllTyFlag -> Bool
- isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool
- tyVarSpecToBinders :: [VarBndr a Specificity] -> [VarBndr a ForAllTyFlag]
- binderVar :: VarBndr tv argf -> tv
- binderVars :: [VarBndr tv argf] -> [tv]
- binderFlag :: VarBndr tv argf -> argf
- binderFlags :: [VarBndr tv argf] -> [argf]
- binderType :: VarBndr TyCoVar argf -> Type
- mkForAllTyBinder :: vis -> TyCoVar -> VarBndr TyCoVar vis
- mkTyVarBinder :: vis -> TyVar -> VarBndr TyVar vis
- mkForAllTyBinders :: vis -> [TyCoVar] -> [VarBndr TyCoVar vis]
- mkTyVarBinders :: vis -> [TyVar] -> [VarBndr TyVar vis]
- isInvisiblePiTyBinder :: PiTyBinder -> Bool
- isVisiblePiTyBinder :: PiTyBinder -> Bool
- isNamedPiTyBinder :: PiTyBinder -> Bool
- namedPiTyBinder_maybe :: PiTyBinder -> Maybe TyCoVar
- isAnonPiTyBinder :: PiTyBinder -> Bool
- anonPiTyBinderType_maybe :: PiTyBinder -> Maybe Type
- piTyBinderType :: PiTyBinder -> Type
- tyVarKind :: TyVar -> Kind
- isTyVar :: Var -> Bool
- chooseFunTyFlag :: HasDebugCallStack => Type -> Type -> FunTyFlag
- partitionInvisibleTypes :: TyCon -> [Type] -> ([Type], [Type])
- getLevity :: HasDebugCallStack => Type -> Type
- getTyVar_maybe :: Type -> Maybe TyVar
- tyConAppTyCon_maybe :: Type -> Maybe TyCon
- splitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type])
- isLiftedTypeKind :: Kind -> Bool
- isMultiplicityTy :: Type -> Bool
- isLevityTy :: Type -> Bool
- isRuntimeRepTy :: Type -> Bool
- rewriterView :: Type -> Maybe Type
- coreView :: Type -> Maybe Type
- typeTypeOrConstraint :: HasDebugCallStack => Type -> TypeOrConstraint
- typeKind :: HasDebugCallStack => Type -> Kind
- piResultTy :: HasDebugCallStack => Type -> Type -> Type
- mkCoercionTy :: Coercion -> Type
- mkTyConApp :: TyCon -> [Type] -> Type
- mkCastTy :: Type -> Coercion -> Type
- mkAppTy :: Type -> Type -> Type
- isCoercionTy :: Type -> Bool
- isPredTy :: HasDebugCallStack => Type -> Bool
- tyCoVarsOfType :: Type -> TyCoVarSet
- noFreeVarsOfType :: Type -> Bool
- mkTyVarTy :: TyVar -> Type
- mkTyVarTys :: [TyVar] -> [Type]
- mkInvisFunTy :: HasDebugCallStack => Type -> Type -> Type
- mkInvisFunTys :: HasDebugCallStack => [Type] -> Type -> Type
- mkVisFunTy :: HasDebugCallStack => Mult -> Type -> Type -> Type
- mkVisFunTyMany :: HasDebugCallStack => Type -> Type -> Type
- mkVisFunTysMany :: [Type] -> Type -> Type
- mkScaledFunTys :: HasDebugCallStack => [Scaled Type] -> Type -> Type
- mkForAllTys :: [ForAllTyBinder] -> Type -> Type
- mkInvisForAllTys :: [InvisTVBinder] -> Type -> Type
- mkPiTy :: HasDebugCallStack => PiTyBinder -> Type -> Type
- mkPiTys :: HasDebugCallStack => [PiTyBinder] -> Type -> Type
- tcMkVisFunTy :: Mult -> Type -> Type -> Type
- tcMkInvisFunTy :: TypeOrConstraint -> Type -> Type -> Type
- tcMkScaledFunTys :: [Scaled Type] -> Type -> Type
- foldTyCo :: Monoid a => TyCoFolder env a -> env -> (Type -> a, [Type] -> a, Coercion -> a, [Coercion] -> a)
- noView :: Type -> Maybe Type
- typeSize :: Type -> Int
- funTyFlagTyCon :: FunTyFlag -> TyCon
- tyCoVarsOfTypes :: [Type] -> TyCoVarSet
- coVarsOfType :: Type -> CoVarSet
- coVarsOfTypes :: [Type] -> CoVarSet
- closeOverKinds :: TyCoVarSet -> TyCoVarSet
- closeOverKindsList :: [TyVar] -> [TyVar]
- closeOverKindsDSet :: DTyVarSet -> DTyVarSet
- tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet
- tyCoFVsOfType :: Type -> FV
- tyCoFVsBndr :: ForAllTyBinder -> FV -> FV
- tyCoFVsVarBndrs :: [Var] -> FV -> FV
- tyCoFVsVarBndr :: Var -> FV -> FV
- anyFreeVarsOfType :: (TyCoVar -> Bool) -> Type -> Bool
- anyFreeVarsOfTypes :: (TyCoVar -> Bool) -> [Type] -> Bool
- scopedSort :: [TyCoVar] -> [TyCoVar]
- tyCoVarsOfTypeWellScoped :: Type -> [TyVar]
- tyCoVarsOfTypesWellScoped :: [Type] -> [TyVar]
- tyConsOfType :: Type -> UniqSet TyCon
- occCheckExpand :: [Var] -> Type -> Maybe Type
- emptyTvSubstEnv :: TvSubstEnv
- composeTCvSubst :: Subst -> Subst -> Subst
- emptySubst :: Subst
- mkEmptySubst :: InScopeSet -> Subst
- isEmptySubst :: Subst -> Bool
- isEmptyTCvSubst :: Subst -> Bool
- mkTCvSubst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> Subst
- getTvSubstEnv :: Subst -> TvSubstEnv
- getSubstInScope :: Subst -> InScopeSet
- setInScope :: Subst -> InScopeSet -> Subst
- getSubstRangeTyCoFVs :: Subst -> VarSet
- notElemSubst :: Var -> Subst -> Bool
- zapSubst :: Subst -> Subst
- extendSubstInScope :: Subst -> Var -> Subst
- extendSubstInScopeList :: Subst -> [Var] -> Subst
- extendSubstInScopeSet :: Subst -> VarSet -> Subst
- extendTCvSubst :: Subst -> TyCoVar -> Type -> Subst
- extendTCvSubstWithClone :: Subst -> TyCoVar -> TyCoVar -> Subst
- extendTvSubstWithClone :: Subst -> TyVar -> TyVar -> Subst
- extendCvSubst :: Subst -> CoVar -> Coercion -> Subst
- extendTvSubstAndInScope :: Subst -> TyVar -> Type -> Subst
- extendTCvSubstList :: Subst -> [Var] -> [Type] -> Subst
- unionSubst :: Subst -> Subst -> Subst
- zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> Subst
- zipTCvSubst :: HasDebugCallStack => [TyCoVar] -> [Type] -> Subst
- mkTvSubstPrs :: [(TyVar, Type)] -> Subst
- zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv
- zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv
- substTyWith :: HasDebugCallStack => [TyVar] -> [Type] -> Type -> Type
- substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type
- substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion
- substTysWith :: HasDebugCallStack => [TyVar] -> [Type] -> [Type] -> [Type]
- substTyAddInScope :: HasDebugCallStack => Subst -> Type -> Type
- substTyUnchecked :: Subst -> Type -> Type
- substScaledTy :: HasDebugCallStack => Subst -> Scaled Type -> Scaled Type
- substScaledTyUnchecked :: HasDebugCallStack => Subst -> Scaled Type -> Scaled Type
- substTys :: HasDebugCallStack => Subst -> [Type] -> [Type]
- substScaledTys :: HasDebugCallStack => Subst -> [Scaled Type] -> [Scaled Type]
- substTysUnchecked :: Subst -> [Type] -> [Type]
- substScaledTysUnchecked :: Subst -> [Scaled Type] -> [Scaled Type]
- substTheta :: HasDebugCallStack => Subst -> ThetaType -> ThetaType
- substThetaUnchecked :: Subst -> ThetaType -> ThetaType
- substTyVar :: Subst -> TyVar -> Type
- substTyVarToTyVar :: HasDebugCallStack => Subst -> TyVar -> TyVar
- substTyVars :: Subst -> [TyVar] -> [Type]
- lookupTyVar :: Subst -> TyVar -> Maybe Type
- substCo :: HasDebugCallStack => Subst -> Coercion -> Coercion
- substCoUnchecked :: Subst -> Coercion -> Coercion
- substTyVarBndr :: HasDebugCallStack => Subst -> TyVar -> (Subst, TyVar)
- substTyVarBndrs :: HasDebugCallStack => Subst -> [TyVar] -> (Subst, [TyVar])
- substVarBndr :: HasDebugCallStack => Subst -> TyCoVar -> (Subst, TyCoVar)
- substVarBndrs :: HasDebugCallStack => Subst -> [TyCoVar] -> (Subst, [TyCoVar])
- cloneTyVarBndr :: Subst -> TyVar -> Unique -> (Subst, TyVar)
- cloneTyVarBndrs :: Subst -> [TyVar] -> UniqSupply -> (Subst, [TyVar])
- substTyCoBndr :: Subst -> PiTyBinder -> (Subst, PiTyBinder)
- tidyVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar])
- tidyVarBndr :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar)
- tidyForAllTyBinder :: TidyEnv -> VarBndr TyCoVar vis -> (TidyEnv, VarBndr TyCoVar vis)
- tidyForAllTyBinders :: TidyEnv -> [VarBndr TyCoVar vis] -> (TidyEnv, [VarBndr TyCoVar vis])
- tidyFreeTyCoVars :: TidyEnv -> [TyCoVar] -> TidyEnv
- tidyOpenTyCoVars :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar])
- tidyOpenTyCoVar :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar)
- tidyTyCoVarOcc :: TidyEnv -> TyCoVar -> TyCoVar
- tidyTypes :: TidyEnv -> [Type] -> [Type]
- tidyType :: TidyEnv -> Type -> Type
- tidyOpenTypes :: TidyEnv -> [Type] -> (TidyEnv, [Type])
- tidyOpenType :: TidyEnv -> Type -> (TidyEnv, Type)
- tidyTopType :: Type -> Type
- coreFullView :: Type -> Type
- kindRep :: HasDebugCallStack => Kind -> RuntimeRepType
- kindRep_maybe :: HasDebugCallStack => Kind -> Maybe RuntimeRepType
- isUnliftedTypeKind :: Kind -> Bool
- pickyIsLiftedTypeKind :: Kind -> Bool
- kindBoxedRepLevity_maybe :: Type -> Maybe Levity
- isLiftedRuntimeRep :: RuntimeRepType -> Bool
- isUnliftedRuntimeRep :: RuntimeRepType -> Bool
- isLiftedLevity :: Type -> Bool
- isUnliftedLevity :: Type -> Bool
- isRuntimeRepVar :: TyVar -> Bool
- isLevityVar :: TyVar -> Bool
- isMultiplicityVar :: TyVar -> Bool
- splitRuntimeRep_maybe :: RuntimeRepType -> Maybe (TyCon, [Type])
- isBoxedRuntimeRep :: RuntimeRepType -> Bool
- runtimeRepLevity_maybe :: RuntimeRepType -> Maybe Levity
- levityType_maybe :: LevityType -> Maybe Levity
- 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])
- getTyVar :: HasDebugCallStack => Type -> TyVar
- repGetTyVar_maybe :: Type -> Maybe TyVar
- isTyVarTy :: Type -> Bool
- getCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN)
- mkAppTys :: Type -> [Type] -> Type
- splitAppTy_maybe :: Type -> Maybe (Type, Type)
- splitAppTy :: Type -> (Type, Type)
- splitAppTyNoView_maybe :: HasDebugCallStack => Type -> Maybe (Type, Type)
- tcSplitAppTyNoView_maybe :: Type -> Maybe (Type, Type)
- splitAppTys :: HasDebugCallStack => Type -> (Type, [Type])
- splitAppTysNoView :: HasDebugCallStack => Type -> (Type, [Type])
- mkNumLitTy :: Integer -> Type
- isNumLitTy :: Type -> Maybe Integer
- mkStrLitTy :: FastString -> Type
- isStrLitTy :: Type -> Maybe FastString
- mkCharLitTy :: Char -> Type
- isCharLitTy :: Type -> Maybe Char
- isLitTy :: Type -> Maybe TyLit
- userTypeError_maybe :: Type -> Maybe ErrorMsgType
- deepUserTypeError_maybe :: Type -> Maybe ErrorMsgType
- pprUserTypeErrorTy :: ErrorMsgType -> SDoc
- funTyConAppTy_maybe :: FunTyFlag -> Type -> Type -> Type -> Maybe (TyCon, [Type])
- tyConAppFunTy_maybe :: HasDebugCallStack => TyCon -> [Type] -> Maybe Type
- tyConAppFunCo_maybe :: HasDebugCallStack => Role -> TyCon -> [Coercion] -> Maybe Coercion
- mkFunctionType :: HasDebugCallStack => Mult -> Type -> Type -> Type
- mkScaledFunctionTys :: [Scaled Type] -> Type -> Type
- splitFunTy :: Type -> (Mult, Type, Type)
- splitFunTy_maybe :: Type -> Maybe (FunTyFlag, Mult, Type, Type)
- splitFunTys :: Type -> ([Scaled Type], Type)
- funArgTy :: HasDebugCallStack => Type -> Type
- piResultTys :: HasDebugCallStack => Type -> [Type] -> Type
- applyTysX :: HasDebugCallStack => [TyVar] -> Type -> [Type] -> Type
- tyConAppTyConPicky_maybe :: Type -> Maybe TyCon
- tyConAppTyCon :: HasDebugCallStack => Type -> TyCon
- tyConAppArgs_maybe :: Type -> Maybe [Type]
- tyConAppArgs :: HasCallStack => Type -> [Type]
- splitTyConAppNoView_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type])
- tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type])
- tcSplitTyConApp :: Type -> (TyCon, [Type])
- newTyConInstRhs :: TyCon -> [Type] -> Type
- splitCastTy_maybe :: Type -> Maybe (Type, Coercion)
- isCoercionTy_maybe :: Type -> Maybe Coercion
- stripCoercionTy :: Type -> Coercion
- tyConBindersPiTyBinders :: [TyConBinder] -> [PiTyBinder]
- mkTyCoForAllTy :: TyCoVar -> ForAllTyFlag -> Type -> Type
- mkTyCoForAllTys :: [ForAllTyBinder] -> Type -> Type
- mkTyCoInvForAllTy :: TyCoVar -> Type -> Type
- mkInfForAllTy :: TyVar -> Type -> Type
- mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type
- mkInfForAllTys :: [TyVar] -> Type -> Type
- mkSpecForAllTy :: TyVar -> Type -> Type
- mkSpecForAllTys :: [TyVar] -> Type -> Type
- mkVisForAllTys :: [TyVar] -> Type -> Type
- mkTyConBindersPreferAnon :: [TyVar] -> TyCoVarSet -> [TyConBinder]
- splitForAllForAllTyBinders :: Type -> ([ForAllTyBinder], Type)
- splitForAllTyCoVars :: Type -> ([TyCoVar], Type)
- splitForAllTyVars :: Type -> ([TyVar], Type)
- splitForAllReqTyBinders :: Type -> ([ReqTyBinder], Type)
- splitForAllInvisTyBinders :: Type -> ([InvisTyBinder], Type)
- isForAllTy :: Type -> Bool
- isForAllTy_ty :: Type -> Bool
- isForAllTy_invis_ty :: Type -> Bool
- isForAllTy_co :: Type -> Bool
- isPiTy :: Type -> Bool
- isFunTy :: Type -> Bool
- splitForAllTyCoVar :: Type -> (TyCoVar, Type)
- dropForAlls :: Type -> Type
- splitForAllForAllTyBinder_maybe :: Type -> Maybe (ForAllTyBinder, Type)
- splitForAllTyCoVar_maybe :: Type -> Maybe (TyCoVar, Type)
- splitForAllTyVar_maybe :: Type -> Maybe (TyVar, Type)
- splitForAllCoVar_maybe :: Type -> Maybe (CoVar, Type)
- splitPiTy_maybe :: Type -> Maybe (PiTyBinder, Type)
- splitPiTy :: Type -> (PiTyBinder, Type)
- splitPiTys :: Type -> ([PiTyBinder], Type)
- getRuntimeArgTys :: Type -> [(Scaled Type, FunTyFlag)]
- invisibleTyBndrCount :: Type -> Int
- splitInvisPiTys :: Type -> ([PiTyBinder], Type)
- splitInvisPiTysN :: Int -> Type -> ([PiTyBinder], Type)
- filterOutInvisibleTypes :: TyCon -> [Type] -> [Type]
- filterOutInferredTypes :: TyCon -> [Type] -> [Type]
- partitionInvisibles :: [(a, ForAllTyFlag)] -> ([a], [a])
- tyConForAllTyFlags :: TyCon -> [Type] -> [ForAllTyFlag]
- appTyForAllTyFlags :: Type -> [Type] -> [ForAllTyFlag]
- isTauTy :: Type -> Bool
- isAtomicTy :: Type -> Bool
- mkFamilyTyConApp :: TyCon -> [Type] -> Type
- coAxNthLHS :: forall (br :: BranchFlag). CoAxiom br -> Int -> Type
- isFamFreeTy :: Type -> Bool
- buildSynTyCon :: Name -> [KnotTied TyConBinder] -> Kind -> [Role] -> KnotTied Type -> TyCon
- typeLevity :: HasDebugCallStack => Type -> Levity
- isUnliftedType :: HasDebugCallStack => Type -> Bool
- mightBeLiftedType :: Type -> Bool
- definitelyLiftedType :: Type -> Bool
- mightBeUnliftedType :: Type -> Bool
- definitelyUnliftedType :: Type -> Bool
- isBoxedType :: Type -> Bool
- isRuntimeRepKindedTy :: Type -> Bool
- dropRuntimeRepArgs :: [Type] -> [Type]
- getRuntimeRep :: HasDebugCallStack => Type -> RuntimeRepType
- isUnboxedTupleType :: Type -> Bool
- isUnboxedSumType :: Type -> Bool
- isDataFamilyAppType :: Type -> Bool
- isStrictType :: HasDebugCallStack => Type -> Bool
- isTerminatingType :: HasDebugCallStack => Type -> Bool
- isCoVarType :: Type -> Bool
- isPrimitiveType :: Type -> Bool
- isValidJoinPointType :: JoinArity -> Type -> Bool
- seqType :: Type -> ()
- seqTypes :: [Type] -> ()
- sORTKind_maybe :: Kind -> Maybe (TypeOrConstraint, Type)
- isTYPEorCONSTRAINT :: Kind -> Bool
- tyConIsTYPEorCONSTRAINT :: TyCon -> Bool
- isConstraintLikeKind :: Kind -> Bool
- isConstraintKind :: Kind -> Bool
- tcIsLiftedTypeKind :: Kind -> Bool
- tcIsBoxedTypeKind :: Kind -> Bool
- isTypeLikeKind :: Kind -> Bool
- returnsConstraintKind :: Kind -> Bool
- typeHasFixedRuntimeRep :: HasDebugCallStack => Type -> Bool
- isFixedRuntimeRepKind :: HasDebugCallStack => Kind -> Bool
- isConcreteType :: Type -> Bool
- tyConAppNeedsKindSig :: Bool -> TyCon -> Int -> Bool
- unrestricted :: a -> Scaled a
- linear :: a -> Scaled a
- tymult :: a -> Scaled a
- irrelevantMult :: Scaled a -> a
- mkScaled :: Mult -> a -> Scaled a
- scaledSet :: Scaled a -> b -> Scaled b
- isManyTy :: Mult -> Bool
- isOneTy :: Mult -> Bool
- isLinearType :: Type -> Bool
- mkTYPEapp :: RuntimeRepType -> Type
- mkTYPEapp_maybe :: RuntimeRepType -> Maybe Type
- mkCONSTRAINTapp :: RuntimeRepType -> Type
- mkCONSTRAINTapp_maybe :: RuntimeRepType -> Maybe Type
- mkBoxedRepApp_maybe :: LevityType -> Maybe Type
- mkTupleRepApp_maybe :: Type -> Maybe Type
- typeOrConstraintKind :: TypeOrConstraint -> RuntimeRepType -> Kind
- module GHC.Core.TyCon
- data Coercion
- data Role
- type TyCoVar = Id
- data Var
- type MCoercionN = MCoercion
- type CoercionN = Coercion
- data MCoercion
- data UnivCoProvenance
- data CoSel
- data FunSel
- data LeftOrRight
- type CoVar = Id
- data CoercionHole = CoercionHole {}
- type MCoercionR = MCoercion
- type CoercionP = Coercion
- type CoercionR = Coercion
- type CvSubstEnv = CoVarEnv Coercion
- type LiftCoEnv = VarEnv Coercion
- data LiftingContext = LC Subst LiftCoEnv
- data NormaliseStepResult ev
- = NS_Done
- | NS_Abort
- | NS_Step RecTcChecker Type ev
- type NormaliseStepper ev = RecTcChecker -> TyCon -> [Type] -> NormaliseStepResult ev
- pprCo :: Coercion -> SDoc
- pickLR :: LeftOrRight -> (a, a) -> a
- mkCoVar :: Name -> Type -> CoVar
- isCoVar :: Var -> Bool
- topNormaliseNewType_maybe :: Type -> Maybe (Coercion, Type)
- coercionType :: Coercion -> Type
- coercionRKind :: Coercion -> Type
- coercionLKind :: Coercion -> Type
- coercionKind :: Coercion -> Pair Type
- seqCo :: Coercion -> ()
- mkCoercionType :: Role -> Type -> Type -> Type
- coVarRole :: CoVar -> Role
- coVarKindsTypesRole :: HasDebugCallStack => CoVar -> (Kind, Kind, Type, Type, Role)
- decomposePiCos :: HasDebugCallStack => CoercionN -> Pair Type -> [Type] -> ([CoercionN], CoercionN)
- isReflexiveCo :: Coercion -> Bool
- isReflCo :: Coercion -> Bool
- isGReflCo :: Coercion -> Bool
- funRole :: Role -> FunSel -> Role
- mkAxiomRuleCo :: CoAxiomRule -> [Coercion] -> Coercion
- mkProofIrrelCo :: Role -> CoercionN -> Coercion -> Coercion -> Coercion
- mkSubCo :: HasDebugCallStack => Coercion -> Coercion
- mkKindCo :: Coercion -> Coercion
- mkNomReflCo :: Type -> Coercion
- mkGReflCo :: Role -> Type -> MCoercionN -> Coercion
- mkInstCo :: Coercion -> CoercionN -> Coercion
- mkLRCo :: LeftOrRight -> Coercion -> Coercion
- mkSelCo :: HasDebugCallStack => CoSel -> Coercion -> Coercion
- mkTransCo :: Coercion -> Coercion -> Coercion
- mkSymCo :: Coercion -> Coercion
- mkUnivCo :: UnivCoProvenance -> Role -> Type -> Type -> Coercion
- mkPhantomCo :: Coercion -> Type -> Type -> Coercion
- mkAxiomInstCo :: CoAxiom Branched -> BranchIndex -> [Coercion] -> Coercion
- mkCoVarCo :: CoVar -> Coercion
- mkFunCo2 :: Role -> FunTyFlag -> FunTyFlag -> CoercionN -> Coercion -> Coercion -> Coercion
- mkNakedFunCo :: Role -> FunTyFlag -> CoercionN -> Coercion -> Coercion -> Coercion
- mkFunCo :: Role -> FunTyFlag -> CoercionN -> Coercion -> Coercion -> Coercion
- mkForAllCo :: HasDebugCallStack => TyCoVar -> ForAllTyFlag -> ForAllTyFlag -> CoercionN -> Coercion -> Coercion
- mkAppCo :: Coercion -> Coercion -> Coercion
- mkTyConAppCo :: HasDebugCallStack => Role -> TyCon -> [Coercion] -> Coercion
- mkReflCo :: Role -> Type -> Coercion
- coHoleCoVar :: CoercionHole -> CoVar
- setCoHoleCoVar :: CoercionHole -> CoVar -> CoercionHole
- coercionSize :: Coercion -> Int
- tyCoVarsOfCo :: Coercion -> TyCoVarSet
- tyCoVarsOfCos :: [Coercion] -> TyCoVarSet
- coVarsOfCo :: Coercion -> CoVarSet
- tyCoVarsOfCoDSet :: Coercion -> DTyCoVarSet
- tyCoFVsOfCo :: Coercion -> FV
- tyCoFVsOfCos :: [Coercion] -> FV
- anyFreeVarsOfCo :: (TyCoVar -> Bool) -> Coercion -> Bool
- emptyCvSubstEnv :: CvSubstEnv
- getCvSubstEnv :: Subst -> CvSubstEnv
- extendTvSubstAndInScope :: Subst -> TyVar -> Type -> Subst
- substCoWith :: HasDebugCallStack => [TyVar] -> [Type] -> Coercion -> Coercion
- substCos :: HasDebugCallStack => Subst -> [Coercion] -> [Coercion]
- substCoVar :: Subst -> CoVar -> Coercion
- substCoVars :: Subst -> [CoVar] -> [Coercion]
- lookupCoVar :: Subst -> Var -> Maybe Coercion
- substCoVarBndr :: HasDebugCallStack => Subst -> CoVar -> (Subst, CoVar)
- tidyCo :: TidyEnv -> Coercion -> Coercion
- tidyCos :: TidyEnv -> [Coercion] -> [Coercion]
- pprParendCo :: Coercion -> SDoc
- coVarName :: CoVar -> Name
- setCoVarUnique :: CoVar -> Unique -> CoVar
- setCoVarName :: CoVar -> Name -> CoVar
- etaExpandCoAxBranch :: CoAxBranch -> ([TyVar], [Type], Type)
- pprCoAxiom :: forall (br :: BranchFlag). CoAxiom br -> SDoc
- pprCoAxBranchUser :: TyCon -> CoAxBranch -> SDoc
- pprCoAxBranchLHS :: TyCon -> CoAxBranch -> SDoc
- pprCoAxBranch :: TyCon -> CoAxBranch -> SDoc
- tidyCoAxBndrsForUser :: TidyEnv -> [Var] -> (TidyEnv, [Var])
- coToMCo :: Coercion -> MCoercion
- checkReflexiveMCo :: MCoercion -> MCoercion
- isGReflMCo :: MCoercion -> Bool
- mkTransMCo :: MCoercion -> MCoercion -> MCoercion
- mkTransMCoL :: MCoercion -> Coercion -> MCoercion
- mkTransMCoR :: Coercion -> MCoercion -> MCoercion
- mkSymMCo :: MCoercion -> MCoercion
- mkCastTyMCo :: Type -> MCoercion -> Type
- mkPiMCos :: [Var] -> MCoercion -> MCoercion
- mkFunResMCo :: Id -> MCoercionR -> MCoercionR
- mkGReflLeftMCo :: Role -> Type -> MCoercionN -> Coercion
- mkGReflRightMCo :: Role -> Type -> MCoercionN -> Coercion
- mkCoherenceRightMCo :: Role -> Type -> MCoercionN -> Coercion -> Coercion
- isReflMCo :: MCoercion -> Bool
- decomposeCo :: Arity -> Coercion -> Infinite Role -> [Coercion]
- decomposeFunCo :: HasDebugCallStack => Coercion -> (CoercionN, Coercion, Coercion)
- getCoVar_maybe :: Coercion -> Maybe CoVar
- multToCo :: Mult -> Coercion
- splitAppCo_maybe :: Coercion -> Maybe (Coercion, Coercion)
- splitFunCo_maybe :: Coercion -> Maybe (Coercion, Coercion)
- splitForAllCo_maybe :: Coercion -> Maybe (TyCoVar, ForAllTyFlag, ForAllTyFlag, Coercion, Coercion)
- splitForAllCo_ty_maybe :: Coercion -> Maybe (TyVar, ForAllTyFlag, ForAllTyFlag, Coercion, Coercion)
- splitForAllCo_co_maybe :: Coercion -> Maybe (CoVar, ForAllTyFlag, ForAllTyFlag, Coercion, Coercion)
- coVarLType :: HasDebugCallStack => CoVar -> Type
- coVarRType :: HasDebugCallStack => CoVar -> Type
- coVarTypes :: HasDebugCallStack => CoVar -> Pair Type
- coVarKind :: CoVar -> Type
- mkRuntimeRepCo :: HasDebugCallStack => Coercion -> Coercion
- isReflCoVar_maybe :: Var -> Maybe Coercion
- isGReflCo_maybe :: Coercion -> Maybe (Type, Role)
- isReflCo_maybe :: Coercion -> Maybe (Type, Role)
- isReflexiveCo_maybe :: Coercion -> Maybe (Type, Role)
- mkRepReflCo :: Type -> Coercion
- mkFunCoNoFTF :: HasDebugCallStack => Role -> CoercionN -> Coercion -> Coercion -> Coercion
- mkAppCos :: Coercion -> [Coercion] -> Coercion
- mkHomoForAllCos :: [ForAllTyBinder] -> Coercion -> Coercion
- mkNakedForAllCo :: TyVar -> ForAllTyFlag -> ForAllTyFlag -> CoercionN -> Coercion -> Coercion
- mkCoVarCos :: [CoVar] -> [Coercion]
- mkAxInstCo :: forall (br :: BranchFlag). Role -> CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Coercion
- mkUnbranchedAxInstCo :: Role -> CoAxiom Unbranched -> [Type] -> [Coercion] -> Coercion
- mkAxInstRHS :: forall (br :: BranchFlag). CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Type
- mkUnbranchedAxInstRHS :: CoAxiom Unbranched -> [Type] -> [Coercion] -> Type
- mkAxInstLHS :: forall (br :: BranchFlag). CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Type
- mkUnbranchedAxInstLHS :: CoAxiom Unbranched -> [Type] -> [Coercion] -> Type
- mkHoleCo :: CoercionHole -> Coercion
- getNthFun :: FunSel -> a -> a -> a -> a
- mkGReflRightCo :: Role -> Type -> CoercionN -> Coercion
- mkGReflLeftCo :: Role -> Type -> CoercionN -> Coercion
- mkCoherenceLeftCo :: Role -> Type -> CoercionN -> Coercion -> Coercion
- mkCoherenceRightCo :: Role -> Type -> CoercionN -> Coercion -> Coercion
- downgradeRole :: Role -> Role -> Coercion -> Coercion
- setNominalRole_maybe :: Role -> Coercion -> Maybe CoercionN
- tyConRolesX :: Role -> TyCon -> Infinite Role
- tyConRoleListX :: Role -> TyCon -> [Role]
- tyConRolesRepresentational :: TyCon -> Infinite Role
- tyConRoleListRepresentational :: TyCon -> [Role]
- tyConRole :: Role -> TyCon -> Int -> Role
- ltRole :: Role -> Role -> Bool
- promoteCoercion :: HasDebugCallStack => Coercion -> CoercionN
- castCoercionKind2 :: Coercion -> Role -> Type -> Type -> CoercionN -> CoercionN -> Coercion
- castCoercionKind1 :: Coercion -> Role -> Type -> Type -> CoercionN -> Coercion
- castCoercionKind :: Coercion -> CoercionN -> CoercionN -> Coercion
- mkPiCos :: Role -> [Var] -> Coercion -> Coercion
- mkPiCo :: Role -> Var -> Coercion -> Coercion
- mkFunResCo :: Role -> Id -> Coercion -> Coercion
- mkCoCast :: Coercion -> CoercionR -> Coercion
- instNewTyCon_maybe :: TyCon -> [Type] -> Maybe (Type, Coercion)
- composeSteppers :: NormaliseStepper ev -> NormaliseStepper ev -> NormaliseStepper ev
- unwrapNewTypeStepper :: NormaliseStepper Coercion
- topNormaliseTypeX :: NormaliseStepper ev -> (ev -> ev -> ev) -> Type -> Maybe (ev, Type)
- eqCoercion :: Coercion -> Coercion -> Bool
- eqCoercionX :: RnEnv2 -> Coercion -> Coercion -> Bool
- liftCoSubstWithEx :: Role -> [TyVar] -> [Coercion] -> [TyCoVar] -> [Type] -> (Type -> Coercion, [Type])
- liftCoSubstWith :: Role -> [TyCoVar] -> [Coercion] -> Type -> Coercion
- liftCoSubst :: HasDebugCallStack => Role -> LiftingContext -> Type -> Coercion
- emptyLiftingContext :: InScopeSet -> LiftingContext
- mkSubstLiftingContext :: Subst -> LiftingContext
- extendLiftingContext :: LiftingContext -> TyCoVar -> Coercion -> LiftingContext
- extendLiftingContextCvSubst :: LiftingContext -> CoVar -> Coercion -> LiftingContext
- extendLiftingContextAndInScope :: LiftingContext -> TyCoVar -> Coercion -> LiftingContext
- zapLiftingContext :: LiftingContext -> LiftingContext
- substForAllCoBndrUsingLC :: Bool -> (Coercion -> Coercion) -> LiftingContext -> TyCoVar -> Coercion -> (LiftingContext, TyCoVar, Coercion)
- liftCoSubstTyVar :: LiftingContext -> Role -> TyVar -> Maybe Coercion
- liftCoSubstVarBndrUsing :: (r -> CoercionN) -> (LiftingContext -> Type -> r) -> LiftingContext -> TyCoVar -> (LiftingContext, TyCoVar, r)
- isMappedByLC :: TyCoVar -> LiftingContext -> Bool
- substLeftCo :: LiftingContext -> Coercion -> Coercion
- substRightCo :: LiftingContext -> Coercion -> Coercion
- swapLiftCoEnv :: LiftCoEnv -> LiftCoEnv
- lcSubstLeft :: LiftingContext -> Subst
- lcSubstRight :: LiftingContext -> Subst
- liftEnvSubstLeft :: Subst -> LiftCoEnv -> Subst
- liftEnvSubstRight :: Subst -> LiftCoEnv -> Subst
- lcLookupCoVar :: LiftingContext -> CoVar -> Maybe Coercion
- lcInScopeSet :: LiftingContext -> InScopeSet
- coercionKinds :: [Coercion] -> Pair [Type]
- coercionKindRole :: Coercion -> (Pair Type, Role)
- getNthFromType :: HasDebugCallStack => CoSel -> Type -> Type
- coercionRole :: Coercion -> Role
- mkPrimEqPred :: Type -> Type -> Type
- mkReprPrimEqPred :: Type -> Type -> Type
- mkPrimEqPredRole :: Role -> Type -> Type -> PredType
- mkNomPrimEqPred :: Kind -> Type -> Type -> Type
- buildCoercion :: Type -> Type -> CoercionN
- hasCoercionHoleTy :: Type -> Bool
- hasCoercionHoleCo :: Coercion -> Bool
- hasThisCoercionHoleTy :: Type -> CoercionHole -> Bool
- setCoHoleType :: CoercionHole -> Type -> CoercionHole
- module GHC.Builtin.Types
- module GHC.Driver.Env
- module GHC.Types.Basic
- module GHC.Types.Var.Set
- module GHC.Types.Var.Env
- module GHC.Types.Name.Set
- module GHC.Types.Name.Env
- data Unique
- class Uniquable a where
- module GHC.Types.Unique.Set
- module GHC.Types.Unique.FM
- module GHC.Data.FiniteMap
- module GHC.Utils.Misc
- module GHC.Serialized
- module GHC.Types.SrcLoc
- module GHC.Utils.Outputable
- module GHC.Utils.Panic
- module GHC.Types.Unique.Supply
- module GHC.Data.FastString
- module GHC.Tc.Errors.Hole.FitTypes
- module GHC.Tc.Errors.Hole.Plugin
- module GHC.Unit.Module.ModGuts
- module GHC.Unit.Module.ModSummary
- module GHC.Unit.Module.ModIface
- module GHC.Types.Meta
- module GHC.Types.SourceError
- type PsError = PsMessage
- type PsWarning = PsMessage
- data Messages e
- data HsParsedModule
- thNameToGhcName :: Name -> CoreM (Maybe Name)
- thNameToGhcNameIO :: NameCache -> Name -> IO (Maybe Name)
Documentation
module GHC.Driver.Plugins
module GHC.Types.Name.Reader
Instances
NFData NameSpace | |
Defined in GHC.Types.Name.Occurrence | |
Uniquable NameSpace | |
Defined in GHC.Types.Name.Occurrence | |
Binary NameSpace | |
Eq NameSpace | |
Ord NameSpace | |
Defined in GHC.Types.Name.Occurrence |
Occurrence Name
In this context that means: "classified (i.e. as a type name, value name, etc) but not qualified and not yet resolved"
Instances
Data OccName | |
Defined in GHC.Types.Name.Occurrence 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 # | |
NFData OccName | |
Defined in GHC.Types.Name.Occurrence | |
HasOccName OccName | |
Defined in GHC.Types.Name.Occurrence | |
Binary OccName | |
Outputable OccName | |
Defined in GHC.Types.Name.Occurrence | |
OutputableBndr OccName | |
Defined in GHC.Types.Name.Occurrence pprBndr :: BindingSite -> OccName -> SDoc # pprPrefixOcc :: OccName -> SDoc # pprInfixOcc :: OccName -> SDoc # | |
Eq OccName | |
Ord OccName | |
class HasOccName name where #
Other names in the compiler add additional information to an OccName. This class provides a consistent way to access the underlying OccName.
Instances
HasOccName IfaceClassOp | |
Defined in GHC.Iface.Syntax occName :: IfaceClassOp -> OccName # | |
HasOccName IfaceConDecl | |
Defined in GHC.Iface.Syntax occName :: IfaceConDecl -> OccName # | |
HasOccName IfaceDecl | |
Defined in GHC.Iface.Syntax | |
HasOccName HoleFitCandidate | |
Defined in GHC.Tc.Errors.Hole.FitTypes occName :: HoleFitCandidate -> OccName # | |
HasOccName TcBinder | |
Defined in GHC.Tc.Types.BasicTypes | |
HasOccName FieldLabel | |
Defined in GHC.Types.FieldLabel occName :: FieldLabel -> OccName # | |
HasOccName Name | |
Defined in GHC.Types.Name | |
HasOccName OccName | |
Defined in GHC.Types.Name.Occurrence | |
HasOccName RdrName | |
Defined in GHC.Types.Name.Reader | |
HasOccName Var | |
Defined in GHC.Types.Var | |
HasOccName (GlobalRdrEltX info) | |
Defined in GHC.Types.Name.Reader occName :: GlobalRdrEltX info -> OccName # |
type FastStringEnv a = UniqFM FastString a #
A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why it's not deterministic and why it matters. Use DFastStringEnv if the set eventually gets converted into a list or folded over in a way where the order changes the generated code.
type TidyOccEnv = UniqFM FastString Int #
A map keyed on OccName
. See Note [OccEnv].
Instances
Functor OccEnv | |
NFData a => NFData (OccEnv a) | |
Defined in GHC.Types.Name.Occurrence | |
Outputable a => Outputable (OccEnv a) | |
Defined in GHC.Types.Name.Occurrence |
Test if the OccName
is that for any operator (whether
it is a data constructor or variable or whatever)
mkVarOccFS :: FastString -> OccName #
emptyFsEnv :: FastStringEnv a #
extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a #
lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a #
mkFsEnv :: [(FastString, a)] -> FastStringEnv a #
fieldName :: FastString -> NameSpace #
isDataConNameSpace :: NameSpace -> Bool #
isTcClsNameSpace :: NameSpace -> Bool #
isTvNameSpace :: NameSpace -> Bool #
isVarNameSpace :: NameSpace -> Bool #
isTermVarOrFieldNameSpace :: NameSpace -> Bool #
Is this a term variable or field name namespace?
isValNameSpace :: NameSpace -> Bool #
isFieldNameSpace :: NameSpace -> Bool #
pprNameSpace :: NameSpace -> SDoc #
pprNonVarNameSpace :: NameSpace -> SDoc #
pprNameSpaceBrief :: NameSpace -> SDoc #
pprOccName :: IsLine doc => OccName -> doc #
occNameMangledFS :: OccName -> FastString #
Mangle field names to avoid duplicate symbols.
See Note [Mangling OccNames].
mkOccNameFS :: NameSpace -> FastString -> OccName #
mkRecFieldOcc :: FastString -> String -> OccName #
mkRecFieldOccFS :: FastString -> FastString -> OccName #
varToRecFieldOcc :: HasDebugCallStack => FastString -> OccName -> OccName #
recFieldToVarOcc :: HasDebugCallStack => OccName -> OccName #
mkDataOccFS :: FastString -> OccName #
mkTyVarOcc :: String -> OccName #
mkTyVarOccFS :: FastString -> OccName #
mkTcOccFS :: FastString -> OccName #
mkClsOccFS :: FastString -> OccName #
demoteOccName :: OccName -> Maybe OccName #
demoteOccTvName :: OccName -> Maybe OccName #
promoteOccName :: OccName -> Maybe OccName #
emptyOccEnv :: OccEnv a #
The empty OccEnv
.
unitOccEnv :: OccName -> a -> OccEnv a #
A singleton OccEnv
.
extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a #
lookupOccEnv_AllNameSpaces :: OccEnv a -> OccName -> [a] #
lookupOccEnv_WithFields :: OccEnv a -> OccName -> [a] #
Lookup an element in an OccEnv
, looking in the record field
namespace for a variable.
lookupFieldsOccEnv :: OccEnv a -> FastString -> [a] #
Look up all the record fields that match with the given FastString
in an OccEnv
.
elemOccEnv :: OccName -> OccEnv a -> Bool #
Compute whether there is a value keyed by the given OccName
.
nonDetFoldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b #
Fold over an OccEnv
. Non-deterministic, unless the folding function
is commutative (i.e. a1
for all f
( a2 f
b ) == a2 f
( a1 f
b )a1
, a2
, b
).
nonDetOccEnvElts :: OccEnv a -> [a] #
Obtain the elements of an OccEnv
.
The resulting order is non-deterministic.
plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a #
Union of two OccEnv
s with a combining function.
filterOccEnv :: (a -> Bool) -> OccEnv a -> OccEnv a #
Filter out all elements in an OccEnv
using a predicate.
alterOccEnv :: (Maybe a -> Maybe a) -> OccEnv a -> OccName -> OccEnv a #
Alter an OccEnv
, adding or removing an element at the given key.
intersectOccEnv_C :: (a -> b -> c) -> OccEnv a -> OccEnv b -> OccEnv c #
minusOccEnv :: OccEnv a -> OccEnv b -> OccEnv a #
minusOccEnv_C :: (a -> b -> Maybe a) -> OccEnv a -> OccEnv b -> OccEnv a #
Alters (replaces or removes) those elements of the first OccEnv
that are
mentioned in the second OccEnv
.
Same idea as differenceWith
.
minusOccEnv_C_Ns :: (UniqFM NameSpace a -> UniqFM NameSpace b -> UniqFM NameSpace a) -> OccEnv a -> OccEnv b -> OccEnv a #
strictMapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b #
Map over an OccEnv
strictly.
forceOccEnv :: (a -> ()) -> OccEnv a -> () #
Force an OccEnv
with the provided function.
emptyOccSet :: OccSet #
unitOccSet :: OccName -> OccSet #
extendOccSet :: OccSet -> OccName -> OccSet #
extendOccSetList :: OccSet -> [OccName] -> OccSet #
unionOccSets :: OccSet -> OccSet -> OccSet #
unionManyOccSets :: [OccSet] -> OccSet #
elemOccSet :: OccName -> OccSet -> Bool #
isEmptyOccSet :: OccSet -> Bool #
occNameString :: OccName -> String #
setOccNameSpace :: NameSpace -> OccName -> OccName #
isFieldOcc :: OccName -> Bool #
fieldOcc_maybe :: OccName -> Maybe FastString #
Value OccNames
s are those that are either in
the variable, field name or data constructor namespaces
isDataSymOcc :: OccName -> Bool #
Test if the OccName
is a data constructor that starts with
a symbol (e.g. :
, or []
)
parenSymOcc :: OccName -> SDoc -> SDoc #
Wrap parens around an operator
startsWithUnderscore :: OccName -> Bool #
Haskell 98 encourages compilers to suppress warnings about unused
names in a pattern if they start with _
: this implements that test
isUnderscore :: OccName -> Bool #
isDerivedOccName :: OccName -> Bool #
Test for definitions internally generated by GHC. This predicate is used to suppress printing of internal definitions in some debug prints
isDefaultMethodOcc :: OccName -> Bool #
isTypeableBindOcc :: OccName -> Bool #
Is an OccName
one of a Typeable TyCon
or Module
binding?
This is needed as these bindings are renamed differently.
See Note [Grand plan for Typeable] in GHC.Tc.Instance.Typeable.
mkDataConWrapperOcc :: OccName -> OccName #
mkWorkerOcc :: OccName -> OccName #
mkMatcherOcc :: OccName -> OccName #
mkBuilderOcc :: OccName -> OccName #
mkDefaultMethodOcc :: OccName -> OccName #
mkClassOpAuxOcc :: OccName -> OccName #
mkForeignExportOcc :: OccName -> OccName #
mkRepEqOcc :: OccName -> OccName #
mkClassDataConOcc :: OccName -> OccName #
mkNewTyCoOcc :: OccName -> OccName #
mkInstTyCoOcc :: OccName -> OccName #
mkEqPredCoOcc :: OccName -> OccName #
mkCon2TagOcc :: OccName -> OccName #
mkTag2ConOcc :: OccName -> OccName #
mkMaxTagOcc :: OccName -> OccName #
mkDataTOcc :: OccName -> OccName #
mkDataCOcc :: OccName -> OccName #
mkTyConRepOcc :: OccName -> OccName #
mkDataConWorkerOcc :: OccName -> OccName #
mkSuperDictAuxOcc :: Int -> OccName -> OccName #
Derive a name for the representation type constructor of a
data
/newtype
instance.
mkMethodOcc :: OccName -> OccName #
initTidyOccEnv :: [OccName] -> TidyOccEnv #
delTidyOccEnvList :: TidyOccEnv -> [FastString] -> TidyOccEnv #
avoidClashesOccEnv :: TidyOccEnv -> [OccName] -> TidyOccEnv #
tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName) #
Instances
NFData NameSpace | |
Defined in GHC.Types.Name.Occurrence | |
Uniquable NameSpace | |
Defined in GHC.Types.Name.Occurrence | |
Binary NameSpace | |
Eq NameSpace | |
Ord NameSpace | |
Defined in GHC.Types.Name.Occurrence |
A unique, unambiguous name for something, containing information about where that thing originated.
Instances
Data Name | |
Defined in GHC.Types.Name 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 # 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 # | |
NFData Name | |
Defined in GHC.Types.Name | |
NamedThing Name | |
Defined in GHC.Types.Name | |
HasOccName Name | |
Defined in GHC.Types.Name | |
Uniquable Name | |
Defined in GHC.Types.Name | |
Binary Name | Assumes that the |
Outputable Name | |
Defined in GHC.Types.Name | |
OutputableBndr Name | |
Defined in GHC.Types.Name pprBndr :: BindingSite -> Name -> SDoc # pprPrefixOcc :: Name -> SDoc # pprInfixOcc :: Name -> SDoc # bndrIsJoin_maybe :: Name -> JoinPointHood # | |
Eq Name | |
Ord Name | Caution: This instance is implemented via See |
type Anno Name | |
Defined in GHC.Hs.Extension |
Occurrence Name
In this context that means: "classified (i.e. as a type name, value name, etc) but not qualified and not yet resolved"
Instances
Data OccName | |
Defined in GHC.Types.Name.Occurrence 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 # | |
NFData OccName | |
Defined in GHC.Types.Name.Occurrence | |
HasOccName OccName | |
Defined in GHC.Types.Name.Occurrence | |
Binary OccName | |
Outputable OccName | |
Defined in GHC.Types.Name.Occurrence | |
OutputableBndr OccName | |
Defined in GHC.Types.Name.Occurrence pprBndr :: BindingSite -> OccName -> SDoc # pprPrefixOcc :: OccName -> SDoc # pprInfixOcc :: OccName -> SDoc # | |
Eq OccName | |
Ord OccName | |
class HasOccName name where #
Other names in the compiler add additional information to an OccName. This class provides a consistent way to access the underlying OccName.
Instances
HasOccName IfaceClassOp | |
Defined in GHC.Iface.Syntax occName :: IfaceClassOp -> OccName # | |
HasOccName IfaceConDecl | |
Defined in GHC.Iface.Syntax occName :: IfaceConDecl -> OccName # | |
HasOccName IfaceDecl | |
Defined in GHC.Iface.Syntax | |
HasOccName HoleFitCandidate | |
Defined in GHC.Tc.Errors.Hole.FitTypes occName :: HoleFitCandidate -> OccName # | |
HasOccName TcBinder | |
Defined in GHC.Tc.Types.BasicTypes | |
HasOccName FieldLabel | |
Defined in GHC.Types.FieldLabel occName :: FieldLabel -> OccName # | |
HasOccName Name | |
Defined in GHC.Types.Name | |
HasOccName OccName | |
Defined in GHC.Types.Name.Occurrence | |
HasOccName RdrName | |
Defined in GHC.Types.Name.Reader | |
HasOccName Var | |
Defined in GHC.Types.Var | |
HasOccName (GlobalRdrEltX info) | |
Defined in GHC.Types.Name.Reader occName :: GlobalRdrEltX info -> OccName # |
class NamedThing a where #
A class allowing convenient access to the Name
of various datatypes
Instances
type FastStringEnv a = UniqFM FastString a #
A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why it's not deterministic and why it matters. Use DFastStringEnv if the set eventually gets converted into a list or folded over in a way where the order changes the generated code.
type TidyOccEnv = UniqFM FastString Int #
A map keyed on OccName
. See Note [OccEnv].
Instances
Functor OccEnv | |
NFData a => NFData (OccEnv a) | |
Defined in GHC.Types.Name.Occurrence | |
Outputable a => Outputable (OccEnv a) | |
Defined in GHC.Types.Name.Occurrence |
data BuiltInSyntax #
BuiltInSyntax is for things like (:)
, []
and tuples,
which have special syntactic forms. They aren't in scope
as such.
nameModule :: HasDebugCallStack => Name -> Module #
Test if the OccName
is that for any operator (whether
it is a data constructor or variable or whatever)
mkVarOccFS :: FastString -> OccName #
isFieldName :: Name -> Bool #
tidyNameOcc :: Name -> OccName -> Name #
nameOccName :: Name -> OccName #
setNameUnique :: Name -> Unique -> Name #
nameUnique :: Name -> Unique #
emptyFsEnv :: FastStringEnv a #
extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a #
lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a #
mkFsEnv :: [(FastString, a)] -> FastStringEnv a #
fieldName :: FastString -> NameSpace #
isDataConNameSpace :: NameSpace -> Bool #
isTcClsNameSpace :: NameSpace -> Bool #
isTvNameSpace :: NameSpace -> Bool #
isVarNameSpace :: NameSpace -> Bool #
isTermVarOrFieldNameSpace :: NameSpace -> Bool #
Is this a term variable or field name namespace?
isValNameSpace :: NameSpace -> Bool #
isFieldNameSpace :: NameSpace -> Bool #
pprNameSpace :: NameSpace -> SDoc #
pprNonVarNameSpace :: NameSpace -> SDoc #
pprNameSpaceBrief :: NameSpace -> SDoc #
pprOccName :: IsLine doc => OccName -> doc #
occNameMangledFS :: OccName -> FastString #
Mangle field names to avoid duplicate symbols.
See Note [Mangling OccNames].
mkOccNameFS :: NameSpace -> FastString -> OccName #
mkRecFieldOcc :: FastString -> String -> OccName #
mkRecFieldOccFS :: FastString -> FastString -> OccName #
varToRecFieldOcc :: HasDebugCallStack => FastString -> OccName -> OccName #
recFieldToVarOcc :: HasDebugCallStack => OccName -> OccName #
mkDataOccFS :: FastString -> OccName #
mkTyVarOcc :: String -> OccName #
mkTyVarOccFS :: FastString -> OccName #
mkTcOccFS :: FastString -> OccName #
mkClsOccFS :: FastString -> OccName #
demoteOccName :: OccName -> Maybe OccName #
demoteOccTvName :: OccName -> Maybe OccName #
promoteOccName :: OccName -> Maybe OccName #
emptyOccEnv :: OccEnv a #
The empty OccEnv
.
unitOccEnv :: OccName -> a -> OccEnv a #
A singleton OccEnv
.
extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a #
lookupOccEnv_AllNameSpaces :: OccEnv a -> OccName -> [a] #
lookupOccEnv_WithFields :: OccEnv a -> OccName -> [a] #
Lookup an element in an OccEnv
, looking in the record field
namespace for a variable.
lookupFieldsOccEnv :: OccEnv a -> FastString -> [a] #
Look up all the record fields that match with the given FastString
in an OccEnv
.
elemOccEnv :: OccName -> OccEnv a -> Bool #
Compute whether there is a value keyed by the given OccName
.
nonDetFoldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b #
Fold over an OccEnv
. Non-deterministic, unless the folding function
is commutative (i.e. a1
for all f
( a2 f
b ) == a2 f
( a1 f
b )a1
, a2
, b
).
nonDetOccEnvElts :: OccEnv a -> [a] #
Obtain the elements of an OccEnv
.
The resulting order is non-deterministic.
plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a #
Union of two OccEnv
s with a combining function.
filterOccEnv :: (a -> Bool) -> OccEnv a -> OccEnv a #
Filter out all elements in an OccEnv
using a predicate.
alterOccEnv :: (Maybe a -> Maybe a) -> OccEnv a -> OccName -> OccEnv a #
Alter an OccEnv
, adding or removing an element at the given key.
intersectOccEnv_C :: (a -> b -> c) -> OccEnv a -> OccEnv b -> OccEnv c #
minusOccEnv :: OccEnv a -> OccEnv b -> OccEnv a #
minusOccEnv_C :: (a -> b -> Maybe a) -> OccEnv a -> OccEnv b -> OccEnv a #
Alters (replaces or removes) those elements of the first OccEnv
that are
mentioned in the second OccEnv
.
Same idea as differenceWith
.
minusOccEnv_C_Ns :: (UniqFM NameSpace a -> UniqFM NameSpace b -> UniqFM NameSpace a) -> OccEnv a -> OccEnv b -> OccEnv a #
strictMapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b #
Map over an OccEnv
strictly.
forceOccEnv :: (a -> ()) -> OccEnv a -> () #
Force an OccEnv
with the provided function.
emptyOccSet :: OccSet #
unitOccSet :: OccName -> OccSet #
extendOccSet :: OccSet -> OccName -> OccSet #
extendOccSetList :: OccSet -> [OccName] -> OccSet #
unionOccSets :: OccSet -> OccSet -> OccSet #
unionManyOccSets :: [OccSet] -> OccSet #
elemOccSet :: OccName -> OccSet -> Bool #
isEmptyOccSet :: OccSet -> Bool #
occNameString :: OccName -> String #
setOccNameSpace :: NameSpace -> OccName -> OccName #
isFieldOcc :: OccName -> Bool #
fieldOcc_maybe :: OccName -> Maybe FastString #
Value OccNames
s are those that are either in
the variable, field name or data constructor namespaces
isDataSymOcc :: OccName -> Bool #
Test if the OccName
is a data constructor that starts with
a symbol (e.g. :
, or []
)
parenSymOcc :: OccName -> SDoc -> SDoc #
Wrap parens around an operator
startsWithUnderscore :: OccName -> Bool #
Haskell 98 encourages compilers to suppress warnings about unused
names in a pattern if they start with _
: this implements that test
isUnderscore :: OccName -> Bool #
isDerivedOccName :: OccName -> Bool #
Test for definitions internally generated by GHC. This predicate is used to suppress printing of internal definitions in some debug prints
isDefaultMethodOcc :: OccName -> Bool #
isTypeableBindOcc :: OccName -> Bool #
Is an OccName
one of a Typeable TyCon
or Module
binding?
This is needed as these bindings are renamed differently.
See Note [Grand plan for Typeable] in GHC.Tc.Instance.Typeable.
mkDataConWrapperOcc :: OccName -> OccName #
mkWorkerOcc :: OccName -> OccName #
mkMatcherOcc :: OccName -> OccName #
mkBuilderOcc :: OccName -> OccName #
mkDefaultMethodOcc :: OccName -> OccName #
mkClassOpAuxOcc :: OccName -> OccName #
mkForeignExportOcc :: OccName -> OccName #
mkRepEqOcc :: OccName -> OccName #
mkClassDataConOcc :: OccName -> OccName #
mkNewTyCoOcc :: OccName -> OccName #
mkInstTyCoOcc :: OccName -> OccName #
mkEqPredCoOcc :: OccName -> OccName #
mkCon2TagOcc :: OccName -> OccName #
mkTag2ConOcc :: OccName -> OccName #
mkMaxTagOcc :: OccName -> OccName #
mkDataTOcc :: OccName -> OccName #
mkDataCOcc :: OccName -> OccName #
mkTyConRepOcc :: OccName -> OccName #
mkDataConWorkerOcc :: OccName -> OccName #
mkSuperDictAuxOcc :: Int -> OccName -> OccName #
Derive a name for the representation type constructor of a
data
/newtype
instance.
mkMethodOcc :: OccName -> OccName #
initTidyOccEnv :: [OccName] -> TidyOccEnv #
delTidyOccEnvList :: TidyOccEnv -> [FastString] -> TidyOccEnv #
avoidClashesOccEnv :: TidyOccEnv -> [OccName] -> TidyOccEnv #
tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName) #
nameNameSpace :: Name -> NameSpace #
nameSrcLoc :: Name -> SrcLoc #
nameSrcSpan :: Name -> SrcSpan #
isWiredInName :: Name -> Bool #
isWiredIn :: NamedThing thing => thing -> Bool #
isBuiltInSyntax :: Name -> Bool #
isTupleTyConName :: Name -> Bool #
isSumTyConName :: Name -> Bool #
isUnboxedTupleDataConLikeName :: Name -> Bool #
This matches a datacon as well as its worker and promoted tycon.
isExternalName :: Name -> Bool #
isInternalName :: Name -> Bool #
isHoleName :: Name -> Bool #
isDynLinkName :: Platform -> Module -> Name -> Bool #
Will the Name
come from a dynamically linked package?
nameModule_maybe :: Name -> Maybe Module #
namePun_maybe :: Name -> Maybe FastString #
nameIsLocalOrFrom :: Module -> Name -> Bool #
Returns True if the name is
(a) Internal
(b) External but from the specified module
(c) External but from the interactive
package
The key idea is that False means: the entity is defined in some other module you can find the details (type, fixity, instances) in some interface file those details will be stored in the EPT or HPT
True means: the entity is defined in this module or earlier in the GHCi session you can find details (type, fixity, instances) in the TcGblEnv or TcLclEnv
The isInteractiveModule part is because successive interactions of a GHCi session
each give rise to a fresh module (Ghci1, Ghci2, etc), but they all come
from the magic interactive
package; and all the details are kept in the
TcLclEnv, TcGblEnv, NOT in the HPT or EPT.
See Note [The interactive package] in GHC.Runtime.Context
nameIsExternalOrFrom :: Module -> Name -> Bool #
Returns True if the name is external or from the interactive
package
See documentation of nameIsLocalOrFrom
function
nameIsHomePackage :: Module -> Name -> Bool #
nameIsHomePackageImport :: Module -> Name -> Bool #
nameIsFromExternalPackage :: HomeUnit -> Name -> Bool #
Returns True if the Name comes from some other package: neither this package nor the interactive package.
isTyVarName :: Name -> Bool #
isTyConName :: Name -> Bool #
isDataConName :: Name -> Bool #
isSystemName :: Name -> Bool #
mkClonedInternalName :: Unique -> Name -> Name #
mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name #
Create a name which definitely originates in the given module
mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name #
Create a name which is actually defined by the compiler itself
mkSystemName :: Unique -> OccName -> Name #
Create a name brought into being by the compiler
mkSystemVarName :: Unique -> FastString -> Name #
mkSysTvName :: Unique -> FastString -> Name #
mkFCallName :: Unique -> FastString -> Name #
Make a name for a foreign call
setNameLoc :: Name -> SrcSpan -> Name #
localiseName :: Name -> Name #
Make the Name
into an internal name, regardless of what it was to begin with
stableNameCmp :: Name -> Name -> Ordering #
Compare Names lexicographically This only works for Names that originate in the source code or have been tidied.
pprFullName :: Module -> Name -> SDoc #
Print fully qualified name (with unit-id, module and unique)
pprTickyName :: Module -> Name -> SDoc #
Print a ticky ticky styled name
Module argument is the module to use for internal and system names. When printing the name in a ticky profile, the module name is included even for local things. However, ticky uses the format "x (M)" rather than "M.x". Hence, this function provides a separation from normal styling.
pprNameUnqualified :: Name -> SDoc #
Print the string of Name unqualifiedly directly.
pprDefinedAt :: Name -> SDoc #
pprNameDefnLoc :: Name -> SDoc #
nameStableString :: Name -> String #
Get a string representation of a Name
that's unique and stable
across recompilations. Used for deterministic generation of binds for
derived instances.
eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal$String"
getSrcLoc :: NamedThing a => a -> SrcLoc #
getSrcSpan :: NamedThing a => a -> SrcSpan #
getOccString :: NamedThing a => a -> String #
getOccFS :: NamedThing a => a -> FastString #
pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc #
pprPrefixName :: NamedThing a => a -> SDoc #
module GHC.Types.Var
data JoinPointHood #
Instances
NFData JoinPointHood | |
Defined in GHC.Utils.Outputable rnf :: JoinPointHood -> () # | |
Binary JoinPointHood | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> JoinPointHood -> IO () # put :: BinHandle -> JoinPointHood -> IO (Bin JoinPointHood) # get :: BinHandle -> IO JoinPointHood # | |
Outputable JoinPointHood | |
Defined in GHC.Utils.Outputable ppr :: JoinPointHood -> SDoc # | |
Eq JoinPointHood | |
Defined in GHC.Utils.Outputable (==) :: JoinPointHood -> JoinPointHood -> Bool # (/=) :: JoinPointHood -> JoinPointHood -> Bool # |
Variable
Essentially a typed Name
, that may also contain some additional information
about the Var
and its use sites.
Instances
Data Var | |
Defined in GHC.Types.Var 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 # 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 # | |
NamedThing Var | |
Defined in GHC.Types.Var | |
HasOccName Var | |
Defined in GHC.Types.Var | |
Uniquable Var | |
Defined in GHC.Types.Var | |
Outputable Var | |
Defined in GHC.Types.Var | |
Eq Var | |
Ord Var | |
Eq (DeBruijn Var) | |
OutputableBndr (Id, TagSig) | |
Defined in GHC.Stg.InferTags.TagSig pprBndr :: BindingSite -> (Id, TagSig) -> SDoc # pprPrefixOcc :: (Id, TagSig) -> SDoc # pprInfixOcc :: (Id, TagSig) -> SDoc # bndrIsJoin_maybe :: (Id, TagSig) -> JoinPointHood # | |
type Anno Id | |
Defined in GHC.Hs.Extension |
type IdUnfoldingFun = Id -> Unfolding #
idInfo :: HasDebugCallStack => Id -> IdInfo #
globaliseId :: Id -> Id #
If it's a local, make it global
Is this a value-level (i.e., computationally relevant) Var
entifier?
Satisfies isId = not . isTyVar
.
isGlobalId :: Var -> Bool #
isExportedId :: Var -> Bool #
isExportedIdVar
means "don't throw this away"
idScaledType :: Id -> Scaled Type #
scaleVarBy :: Mult -> Var -> Var #
Like scaleIdBy
, but skips non-Ids. Useful for scaling
a mixed list of ids and tyvars.
setIdUnique :: Id -> Unique -> Id #
localiseId :: Id -> Id #
modifyIdInfo :: HasDebugCallStack => (IdInfo -> IdInfo) -> Id -> Id #
mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id #
For an explanation of global vs. local Id
s, see GHC.Types.Var.Var
mkLocalId :: HasDebugCallStack => Name -> Mult -> Type -> Id #
For an explanation of global vs. local Id
s, see GHC.Types.Var
mkLocalCoVar :: Name -> Type -> CoVar #
Make a local CoVar
mkLocalIdOrCoVar :: Name -> Mult -> Type -> Id #
Like mkLocalId
, but checks the type to see if it should make a covar
mkLocalIdWithInfo :: HasDebugCallStack => Name -> Mult -> Type -> IdInfo -> Id #
mkExportedLocalId :: IdDetails -> Name -> Type -> Id #
Create a local Id
that is marked as exported.
This prevents things attached to it from being removed as dead code.
See Note [Exported LocalIds]
mkExportedVanillaId :: Name -> Type -> Id #
mkSysLocal :: FastString -> Unique -> Mult -> Type -> Id #
mkSysLocalOrCoVar :: FastString -> Unique -> Mult -> Type -> Id #
Like mkSysLocal
, but checks to see if we have a covar type
mkSysLocalM :: MonadUnique m => FastString -> Mult -> Type -> m Id #
mkSysLocalOrCoVarM :: MonadUnique m => FastString -> Mult -> Type -> m Id #
mkUserLocal :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id #
Create a user local Id
. These are local Id
s (see GHC.Types.Var) with a name and location that the user might recognize
mkUserLocalOrCoVar :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id #
Like mkUserLocal
, but checks if we have a coercion type
mkWorkerId :: Unique -> Id -> Type -> Id #
Workers get local names. CoreTidy will externalise these if necessary
mkTemplateLocal :: Int -> Type -> Id #
Create a template local: a family of system local Id
s in bijection with Int
s, typically used in unfoldings
mkTemplateLocals :: [Type] -> [Id] #
Create a template local for a series of types
mkTemplateLocalsNum :: Int -> [Type] -> [Id] #
Create a template local for a series of type, but start from a specified template local
recordSelectorTyCon :: Id -> RecSelParent #
isRecordSelector :: Id -> Bool #
isDataConRecordSelector :: Id -> Bool #
isPatSynRecordSelector :: Id -> Bool #
isNaughtyRecordSelector :: Id -> Bool #
isClassOpId :: Id -> Bool #
isClassOpId_maybe :: Id -> Maybe Class #
isPrimOpId :: Id -> Bool #
isPrimOpId_maybe :: Id -> Maybe PrimOp #
isFCallId_maybe :: Id -> Maybe ForeignCall #
isDataConWorkId :: Id -> Bool #
isDataConWorkId_maybe :: Id -> Maybe DataCon #
isDataConWrapId :: Id -> Bool #
isDataConWrapId_maybe :: Id -> Maybe DataCon #
isDataConId_maybe :: Id -> Maybe DataCon #
isWorkerLikeId :: Id -> Bool #
An Id for which we might require all callers to pass strict arguments properly tagged + evaluated.
See Note [CBV Function Ids]
idJoinPointHood :: Var -> JoinPointHood #
Doesn't return strictness marks
Get from either the worker or the wrapper Id
to the DataCon
. Currently used only in the desugarer.
INVARIANT: idDataCon (dataConWrapId d) = d
: remember, dataConWrapId
can return either the wrapper or the worker
hasNoBinding :: Id -> Bool #
Returns True
of an Id
which may not have a
binding, even though it is defined in this module.
isImplicitId :: Id -> Bool #
isImplicitId
tells whether an Id
s info is implied by other
declarations, so we don't need to put its signature in an interface
file, even if it's mentioned in some other interface unfolding.
isDeadBinder :: Id -> Bool #
idJoinArity :: JoinId -> JoinArity #
asJoinId_maybe :: Id -> JoinPointHood -> Id infixl 1 #
setIdArity :: Id -> Arity -> Id infixl 1 #
idCallArity :: Id -> Arity #
setIdCallArity :: Id -> Arity -> Id infixl 1 #
idFunRepArity :: Id -> RepArity #
This function counts all arguments post-unarisation, which includes arguments with no runtime representation -- see Note [Unarisation and arity]
isDeadEndId :: Var -> Bool #
Returns true if an application to n args diverges or throws an exception See Note [Dead ends] in GHC.Types.Demand.
Accesses the Id'
s dmdSigInfo
.
setIdDmdSig :: Id -> DmdSig -> Id infixl 1 #
setIdCprSig :: Id -> CprSig -> Id infixl 1 #
zapIdDmdSig :: Id -> Id #
isStrictId :: Id -> Bool #
isStrictId
says whether either
(a) the Id
has a strict demand placed on it or
(b) definitely has a "strict type", such that it can always be
evaluated strictly (i.e an unlifted type)
We need to check (b) as well as (a), because when the demand for the
given id
hasn't been computed yet but id
has a strict
type, we still want `isStrictId id` to be True
.
Returns False if the type is levity polymorphic; False is always safe.
idTagSig_maybe :: Id -> Maybe TagSig #
idUnfolding :: IdUnfoldingFun #
Returns the Id
s unfolding, but does not expose the unfolding of a strong
loop breaker. See unfoldingInfo
.
If you really want the unfolding of a strong loopbreaker, call realIdUnfolding
.
alwaysActiveUnfoldingFun :: IdUnfoldingFun #
Returns an unfolding only if (a) not a strong loop breaker and (b) always active
whenActiveUnfoldingFun :: (Activation -> Bool) -> IdUnfoldingFun #
Returns an unfolding only if (a) not a strong loop breaker and (b) active in according to is_active
realIdUnfolding :: Id -> Unfolding #
Expose the unfolding if there is one, including for loop breakers
setIdUnfolding :: Id -> Unfolding -> Id infixl 1 #
idDemandInfo :: Id -> Demand #
setIdDemandInfo :: Id -> Demand -> Id infixl 1 #
setIdTagSig :: Id -> TagSig -> Id #
setIdCbvMarks :: Id -> [CbvMark] -> Id infixl 1 #
If all marks are NotMarkedStrict we just set nothing.
idCbvMarks_maybe :: Id -> Maybe [CbvMark] #
idCbvMarkArity :: Id -> Arity #
asNonWorkerLikeId :: Id -> Id #
Remove any cbv marks on arguments from a given Id.
asWorkerLikeId :: Id -> Id #
Turn this id into a WorkerLikeId if possible.
setCaseBndrEvald :: StrictnessMark -> Id -> Id #
zapIdUnfolding :: Id -> Id #
Similar to trimUnfolding, but also removes evaldness info.
idSpecialisation :: Id -> RuleInfo #
idCoreRules :: Id -> [CoreRule] #
idHasRules :: Id -> Bool #
setIdSpecialisation :: Id -> RuleInfo -> Id infixl 1 #
setIdCafInfo :: Id -> CafInfo -> Id #
idLFInfo_maybe :: Id -> Maybe LambdaFormInfo #
setIdLFInfo :: Id -> LambdaFormInfo -> Id #
setIdOccInfo :: Id -> OccInfo -> Id infixl 1 #
zapIdOccInfo :: Id -> Id #
idInlinePragma :: Id -> InlinePragma #
setInlinePragma :: Id -> InlinePragma -> Id infixl 1 #
modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> Id #
idInlineActivation :: Id -> Activation #
setInlineActivation :: Id -> Activation -> Id infixl 1 #
idRuleMatchInfo :: Id -> RuleMatchInfo #
isConLikeId :: Id -> Bool #
idOneShotInfo :: Id -> OneShotInfo #
setOneShotLambda :: Id -> Id #
clearOneShotLambda :: Id -> Id #
setIdOneShotInfo :: Id -> OneShotInfo -> Id infixl 1 #
updOneShotInfo :: Id -> OneShotInfo -> Id #
zapLamIdInfo :: Id -> Id #
zapFragileIdInfo :: Id -> Id #
zapIdDemandInfo :: Id -> Id #
zapIdUsageInfo :: Id -> Id #
zapIdUsageEnvInfo :: Id -> Id #
zapIdUsedOnceInfo :: Id -> Id #
zapIdTailCallInfo :: Id -> Id #
zapStableUnfolding :: Id -> Id #
module GHC.Types.Id.Info
module GHC.Types.PkgQual
module GHC.Core.Opt.Monad
module GHC.Core.Opt.Pipeline.Types
module GHC.Core.Opt.Stats
module GHC.Core
module GHC.Types.Literal
module GHC.Core.DataCon
module GHC.Core.Utils
module GHC.Core.Make
module GHC.Core.FVs
data InScopeSet #
A set of variables that are in scope at some point.
Note that this is a superset of the variables that are currently in scope. See Note [The InScopeSet invariant].
"Secrets of the Glasgow Haskell Compiler inliner" Section 3.2 provides the motivation for this abstraction.
Instances
Outputable InScopeSet | |
Defined in GHC.Types.Var.Env ppr :: InScopeSet -> SDoc # |
type IdSubstEnv = IdEnv CoreExpr #
A substitution of Expr
s for non-coercion Id
s
Type & coercion & id substitution
The Subst data type defined in this module contains substitution for tyvar, covar and id. However, operations on IdSubstEnv (mapping from Id to CoreExpr) that require the definition of the Expr data type are defined in GHC.Core.Subst to avoid circular module dependency.
Instances
Outputable Subst | |
Defined in GHC.Core.TyCo.Subst |
emptySubst :: Subst #
mkEmptySubst :: InScopeSet -> Subst #
isEmptySubst :: Subst -> Bool #
mkTCvSubst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> Subst #
getSubstInScope :: Subst -> InScopeSet #
Find the in-scope set: see Note [The substitution invariant]
setInScope :: Subst -> InScopeSet -> Subst #
Remove all substitutions that might have been built up while preserving the in-scope set originally called zapSubstEnv
extendSubstInScopeList :: Subst -> [Var] -> Subst #
Add the Var
s to the in-scope set: see also extendInScope
extendTvSubstList :: Subst -> [(TyVar, Type)] -> Subst #
Adds multiple TyVar
substitutions to the Subst
: see also extendTvSubst
substTyUnchecked :: Subst -> Type -> Type #
Substitute within a Type
disabling the sanity checks.
The problems that the sanity checks in substTy catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTyUnchecked to
substTy and remove this function. Please don't use in new code.
substCo :: HasDebugCallStack => Subst -> Coercion -> Coercion #
Substitute within a Coercion
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
extendIdSubstList :: Subst -> [(Id, CoreExpr)] -> Subst #
Adds multiple Id
substitutions to the Subst
: see also extendIdSubst
extendSubst :: Subst -> Var -> CoreArg -> Subst #
Add a substitution appropriate to the thing being substituted
(whether an expression, type, or coercion). See also
extendIdSubst
, extendTvSubst
, extendCvSubst
extendSubstList :: Subst -> [(Var, CoreArg)] -> Subst #
Add a substitution as appropriate to each of the terms being
substituted (whether expressions, types, or coercions). See also
extendSubst
.
lookupIdSubst :: HasDebugCallStack => Subst -> Id -> CoreExpr #
lookupIdSubst_maybe :: HasDebugCallStack => Subst -> Id -> Maybe CoreExpr #
mkOpenSubst :: InScopeSet -> [(Var, CoreArg)] -> Subst #
Simultaneously substitute for a bunch of variables No left-right shadowing ie the substitution for (x y. e) a1 a2 so neither x nor y scope over a1 a2
substExprSC :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr #
substExpr :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr #
substExpr applies a substitution to an entire CoreExpr
. Remember,
you may only apply the substitution once:
See Note [Substitutions apply only once] in GHC.Core.TyCo.Subst
Do *not* attempt to short-cut in the case of an empty substitution! See Note [Extending the IdSubstEnv]
substBindSC :: HasDebugCallStack => Subst -> CoreBind -> (Subst, CoreBind) #
deShadowBinds :: CoreProgram -> CoreProgram #
De-shadowing the program is sometimes a useful pre-pass. It can be done simply by running over the bindings with an empty substitution, because substitution returns a result that has no-shadowing guaranteed.
(Actually, within a single type there might still be shadowing, because
substTy
is a no-op for the empty substitution, but that's probably OK.)
- Aug 09
- This function is not used in GHC at the moment, but seems so short and simple that I'm going to leave it here
substBndrs :: Traversable f => Subst -> f Var -> (Subst, f Var) #
substRecBndrs :: Traversable f => Subst -> f Id -> (Subst, f Id) #
Substitute in a mutually recursive group of Id
s
cloneIdBndr :: Subst -> UniqSupply -> Id -> (Subst, Id) #
cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) #
Applies cloneIdBndr
to a number of Id
s, accumulating a final
substitution from left to right
Discards non-Stable unfoldings
cloneBndrs :: MonadUnique m => Subst -> [Var] -> m (Subst, [Var]) #
cloneRecIdBndrs :: MonadUnique m => Subst -> [Id] -> m (Subst, [Id]) #
Clone a mutually recursive group of Id
s
substIdType :: Subst -> Id -> Id #
substUnfoldingSC :: Subst -> Unfolding -> Unfolding #
Substitutes for the Id
s within an unfolding
NB: substUnfolding discards any unfolding without
without a Stable source. This is usually what we want,
but it may be a bit unexpected
substUnfolding :: Subst -> Unfolding -> Unfolding #
Substitutes for the Id
s within an unfolding
NB: substUnfolding discards any unfolding without
without a Stable source. This is usually what we want,
but it may be a bit unexpected
substIdOcc :: Subst -> Id -> Id #
substRulesForImportedIds :: Subst -> [CoreRule] -> [CoreRule] #
substDVarSet :: HasDebugCallStack => Subst -> DVarSet -> DVarSet #
substTickish :: Subst -> CoreTickish -> CoreTickish #
Drop free vars from the breakpoint if they have a non-variable substitution.
module GHC.Core.Rules
module GHC.Types.Annotations
module GHC.Driver.Session
module GHC.Driver.Ppr
module GHC.Unit.State
module GHC.Unit.Module
module GHC.Unit.Home
Instances
Data Type | |
Defined in GHC.Core.TyCo.Rep 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 # 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 | |
Defined in GHC.Core.TyCo.Rep | |
Eq (DeBruijn Type) | |
data Specificity #
Whether an Invisible
argument may appear in source Haskell.
InferredSpec | the argument may not appear in source Haskell, it is only inferred. |
SpecifiedSpec | the argument may appear in source Haskell, but isn't required. |
Instances
Variable
Essentially a typed Name
, that may also contain some additional information
about the Var
and its use sites.
Instances
Data Var | |
Defined in GHC.Types.Var 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 # 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 # | |
NamedThing Var | |
Defined in GHC.Types.Var | |
HasOccName Var | |
Defined in GHC.Types.Var | |
Uniquable Var | |
Defined in GHC.Types.Var | |
Outputable Var | |
Defined in GHC.Types.Var | |
Eq Var | |
Ord Var | |
Eq (DeBruijn Var) | |
OutputableBndr (Id, TagSig) | |
Defined in GHC.Stg.InferTags.TagSig pprBndr :: BindingSite -> (Id, TagSig) -> SDoc # pprPrefixOcc :: (Id, TagSig) -> SDoc # pprInfixOcc :: (Id, TagSig) -> SDoc # bndrIsJoin_maybe :: (Id, TagSig) -> JoinPointHood # | |
type Anno Id | |
Defined in GHC.Hs.Extension |
The non-dependent version of ForAllTyFlag
.
See Note [FunTyFlag]
Appears here partly so that it's together with its friends ForAllTyFlag
and ForallVisFlag, but also because it is used in IfaceType, rather
early in the compilation chain
Instances
Data FunTyFlag | |
Defined in GHC.Types.Var gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunTyFlag -> c FunTyFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunTyFlag # toConstr :: FunTyFlag -> Constr # dataTypeOf :: FunTyFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunTyFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunTyFlag) # gmapT :: (forall b. Data b => b -> b) -> FunTyFlag -> FunTyFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunTyFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunTyFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> FunTyFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunTyFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunTyFlag -> m FunTyFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunTyFlag -> m FunTyFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunTyFlag -> m FunTyFlag # | |
Binary FunTyFlag | |
Outputable FunTyFlag | |
Defined in GHC.Types.Var | |
Eq FunTyFlag | |
Ord FunTyFlag | |
Defined in GHC.Types.Var |
data ForAllTyFlag #
ForAllTyFlag
Is something required to appear in source Haskell (Required
),
permitted by request (Specified
) (visible type application), or
prohibited entirely from appearing in source Haskell (Inferred
)?
See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in GHC.Core.TyCo.Rep
pattern Specified :: ForAllTyFlag | |
pattern Inferred :: ForAllTyFlag |
Instances
type RuntimeRepType = Type #
Type synonym used for types of kind RuntimeRep.
A type of the form p
of constraint kind represents a value whose type is
the Haskell predicate p
, where a predicate is what occurs before
the =>
in a Haskell type.
We use PredType
as documentation to mark those types that we guarantee to
have this kind.
It can be expanded into its representation, but:
- The type checker must treat it as opaque
- The rest of the compiler treats it as transparent
Consider these examples:
f :: (Eq a) => a -> Int g :: (?x :: Int -> Int) => a -> Int h :: (r\l) => {r} => {l::Int | r}
Here the Eq a
and ?x :: Int -> Int
and rl
are all called "predicates"
Mult is a type alias for Type.
Mult must contain Type because multiplicity variables are mere type variables (of kind Multiplicity) in Haskell. So the simplest implementation is to make Mult be Type.
Multiplicities can be formed with: - One: GHC.Types.One (= oneDataCon) - Many: GHC.Types.Many (= manyDataCon) - Multiplication: GHC.Types.MultMul (= multMulTyCon)
So that Mult feels a bit more structured, we provide pattern synonyms and smart constructors for these.
A shorthand for data with an attached Mult
element (the multiplicity).
Instances
Data a => Data (Scaled a) | |
Defined in GHC.Core.TyCo.Rep 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) | |
Defined in GHC.Core.TyCo.Rep |
data PiTyBinder #
A PiTyBinder
represents an argument to a function. PiTyBinders can be
dependent (Named
) or nondependent (Anon
). They may also be visible or
not. See Note [PiTyBinders]
Instances
Data PiTyBinder | |
Defined in GHC.Types.Var gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PiTyBinder -> c PiTyBinder # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PiTyBinder # toConstr :: PiTyBinder -> Constr # dataTypeOf :: PiTyBinder -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PiTyBinder) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PiTyBinder) # gmapT :: (forall b. Data b => b -> b) -> PiTyBinder -> PiTyBinder # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PiTyBinder -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PiTyBinder -> r # gmapQ :: (forall d. Data d => d -> u) -> PiTyBinder -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PiTyBinder -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PiTyBinder -> m PiTyBinder # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PiTyBinder -> m PiTyBinder # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PiTyBinder -> m PiTyBinder # | |
Outputable PiTyBinder | |
Defined in GHC.Types.Var ppr :: PiTyBinder -> SDoc # |
type TyVarBinder = VarBndr TyVar ForAllTyFlag #
type ForAllTyBinder = VarBndr TyCoVar ForAllTyFlag #
Variable Binder
A ForAllTyBinder
is the binder of a ForAllTy
It's convenient to define this synonym here rather its natural
home in GHC.Core.TyCo.Rep, because it's used in GHC.Core.DataCon.hs-boot
A TyVarBinder
is a binder with only TyVar
data TyCoFolder env a #
TyCoFolder | |
|
type KnotTied (ty :: k) = ty #
A type labeled KnotTied
might have knot-tied tycons in it. See
Note [Type checking recursive type and class declarations] in
GHC.Tc.TyCl
type KindOrType = Type #
The key representation of types within the compiler
type IdSubstEnv = IdEnv CoreExpr #
A substitution of Expr
s for non-coercion Id
s
Type & coercion & id substitution
The Subst data type defined in this module contains substitution for tyvar, covar and id. However, operations on IdSubstEnv (mapping from Id to CoreExpr) that require the definition of the Expr data type are defined in GHC.Core.Subst to avoid circular module dependency.
Instances
Outputable Subst | |
Defined in GHC.Core.TyCo.Subst |
type ErrorMsgType = Type #
A type of kind ErrorMessage
(from the TypeError
module).
data TyCoMapper env (m :: Type -> Type) #
This describes how a "map" operation over a type/coercion should behave
TyCoMapper | |
|
funResultTy :: HasDebugCallStack => Type -> Type #
Extract the function result type and panic if that is not possible
splitTyConApp :: Type -> (TyCon, [Type]) #
Attempts to tease a type apart into a type constructor and the application
of a number of arguments to that constructor. Panics if that is not possible.
See also splitTyConApp_maybe
See Type for what an algebraic type is. Should only be applied to types, as opposed to e.g. partially saturated type constructors
(mkTyConTy tc) returns (TyConApp tc []) but arranges to share that TyConApp among all calls See Note [Sharing nullary TyConApps] So it's just an alias for tyConNullaryTy!
typeLevity_maybe :: HasDebugCallStack => Type -> Maybe Levity #
Tries to compute the PromDataConInfo
of the given type. Returns either
a definite PromDataConInfo
, or Nothing
if we aren't sure (e.g. the
type is representation-polymorphic).
Panics if the kind does not have the shape TYPE r
.
expandTypeSynonyms :: Type -> Type #
Expand out all type synonyms. Actually, it'd suffice to expand out just the ones that discard type variables (e.g. type Funny a = Int) But we don't know which those are currently, so we just expand all.
expandTypeSynonyms
only expands out type synonyms mentioned in the type,
not in the kinds of any TyCon or TyVar mentioned in the type.
Keep this synchronized with synonymTyConsOfType
mkForAllTy :: ForAllTyBinder -> Type -> Type #
Like mkTyCoForAllTy
, but does not check the occurrence of the binder
See Note [Unused coercion variable in ForAllTy]
liftedTypeKind :: Type #
isVisibleForAllTyFlag :: ForAllTyFlag -> Bool #
Does this ForAllTyFlag
classify an argument that is written in Haskell?
isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool #
Does this ForAllTyFlag
classify an argument that is not written in Haskell?
tyVarSpecToBinders :: [VarBndr a Specificity] -> [VarBndr a ForAllTyFlag] #
binderVars :: [VarBndr tv argf] -> [tv] #
binderFlag :: VarBndr tv argf -> argf #
binderFlags :: [VarBndr tv argf] -> [argf] #
binderType :: VarBndr TyCoVar argf -> Type #
mkForAllTyBinder :: vis -> TyCoVar -> VarBndr TyCoVar vis #
Make a named binder
mkTyVarBinder :: vis -> TyVar -> VarBndr TyVar vis #
Make a named binder
var
should be a type variable
mkForAllTyBinders :: vis -> [TyCoVar] -> [VarBndr TyCoVar vis] #
Make many named binders
mkTyVarBinders :: vis -> [TyVar] -> [VarBndr TyVar vis] #
Make many named binders Input vars should be type variables
isInvisiblePiTyBinder :: PiTyBinder -> Bool #
Does this binder bind an invisible argument?
isVisiblePiTyBinder :: PiTyBinder -> Bool #
Does this binder bind a visible argument?
isNamedPiTyBinder :: PiTyBinder -> Bool #
isAnonPiTyBinder :: PiTyBinder -> Bool #
Does this binder bind a variable that is not erased? Returns
True
for anonymous binders.
anonPiTyBinderType_maybe :: PiTyBinder -> Maybe Type #
Extract a relevant type, if there is one.
piTyBinderType :: PiTyBinder -> Type #
Is this a type-level (i.e., computationally irrelevant, thus erasable)
variable? Satisfies isTyVar = not . isId
.
chooseFunTyFlag :: HasDebugCallStack => Type -> Type -> FunTyFlag #
See GHC.Types.Var Note [FunTyFlag]
getLevity :: HasDebugCallStack => Type -> Type #
Extract the PromDataConInfo
of a type. For example, getLevity Int = Lifted
,
or getLevity (Array# Int) = Unlifted
.
Panics if this is not possible. Does not look through type family applications.
tyConAppTyCon_maybe :: Type -> Maybe TyCon #
The same as fst . splitTyConApp
We can short-cut the FunTy case
splitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #
Attempts to tease a type apart into a type constructor and the application of a number of arguments to that constructor
isLiftedTypeKind :: Kind -> Bool #
Returns True if the argument is (lifted) Type or Constraint See Note [TYPE and CONSTRAINT] in GHC.Builtin.Types.Prim
isMultiplicityTy :: Type -> Bool #
Is this the type Multiplicity
?
isLevityTy :: Type -> Bool #
Is this the type PromDataConInfo
?
isRuntimeRepTy :: Type -> Bool #
Is this the type RuntimeRep
?
rewriterView :: Type -> Maybe Type #
coreView :: Type -> Maybe Type #
This function strips off the top layer only of a type synonym
application (if any) its underlying representation type.
Returns Nothing
if there is nothing to look through.
This function does not look through type family applications.
By being non-recursive and inlined, this case analysis gets efficiently joined onto the case analysis that the caller is already doing
typeKind :: HasDebugCallStack => Type -> Kind #
piResultTy :: HasDebugCallStack => Type -> Type -> Type #
mkCoercionTy :: Coercion -> Type #
mkTyConApp :: TyCon -> [Type] -> Type #
mkCastTy :: Type -> Coercion -> Type #
Make a CastTy
. The Coercion must be nominal. Checks the
Coercion for reflexivity, dropping it if it's reflexive.
See Note [Respecting definitional equality]
in GHC.Core.TyCo.Rep
isCoercionTy :: Type -> Bool #
isPredTy :: HasDebugCallStack => Type -> Bool #
tyCoVarsOfType :: Type -> TyCoVarSet #
noFreeVarsOfType :: Type -> Bool #
mkTyVarTys :: [TyVar] -> [Type] #
mkInvisFunTy :: HasDebugCallStack => Type -> Type -> Type infixr 3 #
mkInvisFunTys :: HasDebugCallStack => [Type] -> Type -> Type #
mkVisFunTy :: HasDebugCallStack => Mult -> Type -> Type -> Type #
mkVisFunTyMany :: HasDebugCallStack => Type -> Type -> Type infixr 3 #
Make nested arrow types | Special, common, case: Arrow type with mult Many
mkVisFunTysMany :: [Type] -> Type -> Type #
mkScaledFunTys :: HasDebugCallStack => [Scaled Type] -> Type -> Type #
mkForAllTys :: [ForAllTyBinder] -> Type -> Type #
Wraps foralls over the type using the provided TyCoVar
s from left to right
mkInvisForAllTys :: [InvisTVBinder] -> Type -> Type #
Wraps foralls over the type using the provided InvisTVBinder
s from left to right
mkPiTy :: HasDebugCallStack => PiTyBinder -> Type -> Type #
mkPiTys :: HasDebugCallStack => [PiTyBinder] -> Type -> Type #
tcMkInvisFunTy :: TypeOrConstraint -> Type -> Type -> Type #
foldTyCo :: Monoid a => TyCoFolder env a -> env -> (Type -> a, [Type] -> a, Coercion -> a, [Coercion] -> a) #
funTyFlagTyCon :: FunTyFlag -> TyCon #
tyCoVarsOfTypes :: [Type] -> TyCoVarSet #
coVarsOfType :: Type -> CoVarSet #
coVarsOfTypes :: [Type] -> CoVarSet #
closeOverKinds :: TyCoVarSet -> TyCoVarSet #
closeOverKindsList :: [TyVar] -> [TyVar] #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministically ordered list.
closeOverKindsDSet :: DTyVarSet -> DTyVarSet #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministic set.
tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet #
tyCoFVsOfType
that returns free variables of a type in a deterministic
set. For explanation of why using VarSet
is not deterministic see
Note [Deterministic FV] in GHC.Utils.FV.
tyCoFVsOfType :: Type -> FV #
The worker for tyCoFVsOfType
and tyCoFVsOfTypeList
.
The previous implementation used unionVarSet
which is O(n+m) and can
make the function quadratic.
It's exported, so that it can be composed with
other functions that compute free variables.
See Note [FV naming conventions] in GHC.Utils.FV.
Eta-expanded because that makes it run faster (apparently) See Note [FV eta expansion] in GHC.Utils.FV for explanation.
tyCoFVsBndr :: ForAllTyBinder -> FV -> FV #
tyCoFVsVarBndrs :: [Var] -> FV -> FV #
tyCoFVsVarBndr :: Var -> FV -> FV #
scopedSort :: [TyCoVar] -> [TyCoVar] #
Do a topological sort on a list of tyvars, so that binders occur before occurrences E.g. given [ a::k, k::*, b::k ] it'll return a well-scoped list [ k::*, a::k, b::k ]
This is a deterministic sorting operation (that is, doesn't depend on Uniques).
It is also meant to be stable: that is, variables should not be reordered unnecessarily. This is specified in Note [ScopedSort] See also Note [Ordering of implicit variables] in GHC.Rename.HsType
tyCoVarsOfTypeWellScoped :: Type -> [TyVar] #
Get the free vars of a type in scoped order
tyCoVarsOfTypesWellScoped :: [Type] -> [TyVar] #
Get the free vars of types in scoped order
tyConsOfType :: Type -> UniqSet TyCon #
All type constructors occurring in the type; looking through type synonyms, but not newtypes. When it finds a Class, it returns the class TyCon.
composeTCvSubst :: Subst -> Subst -> Subst #
Composes two substitutions, applying the second one provided first, like in function composition. This function leaves IdSubstEnv untouched because IdSubstEnv is not used during substitution for types.
emptySubst :: Subst #
mkEmptySubst :: InScopeSet -> Subst #
isEmptySubst :: Subst -> Bool #
isEmptyTCvSubst :: Subst -> Bool #
Checks whether the tyvar and covar environments are empty.
This function should be used over isEmptySubst
when substituting
for types, because types currently do not contain expressions; we can
safely disregard the expression environment when deciding whether
to skip a substitution. Using isEmptyTCvSubst
gives us a non-trivial
performance boost (up to 70% less allocation for T18223)
mkTCvSubst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> Subst #
getTvSubstEnv :: Subst -> TvSubstEnv #
getSubstInScope :: Subst -> InScopeSet #
Find the in-scope set: see Note [The substitution invariant]
setInScope :: Subst -> InScopeSet -> Subst #
getSubstRangeTyCoFVs :: Subst -> VarSet #
Returns the free variables of the types in the range of a substitution as a non-deterministic set.
notElemSubst :: Var -> Subst -> Bool #
Remove all substitutions that might have been built up while preserving the in-scope set originally called zapSubstEnv
extendSubstInScopeList :: Subst -> [Var] -> Subst #
Add the Var
s to the in-scope set: see also extendInScope
extendSubstInScopeSet :: Subst -> VarSet -> Subst #
Add the Var
s to the in-scope set: see also extendInScope
unionSubst :: Subst -> Subst -> Subst #
zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> Subst #
Generates the in-scope set for the Subst
from the types in the incoming
environment. No CoVars or Ids, please!
zipTCvSubst :: HasDebugCallStack => [TyCoVar] -> [Type] -> Subst #
mkTvSubstPrs :: [(TyVar, Type)] -> Subst #
Generates the in-scope set for the TCvSubst
from the types in the
incoming environment. No CoVars, please! The InScopeSet is just a thunk
so with a bit of luck it'll never be evaluated
zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv #
The InScopeSet is just a thunk so with a bit of luck it'll never be evaluated
zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv #
substTyWith :: HasDebugCallStack => [TyVar] -> [Type] -> Type -> Type #
Type substitution, see zipTvSubst
substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type #
Type substitution, see zipTvSubst
. Disables sanity checks.
The problems that the sanity checks in substTy catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTyUnchecked to
substTy and remove this function. Please don't use in new code.
substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion #
Coercion substitution, see zipTvSubst
. Disables sanity checks.
The problems that the sanity checks in substCo catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substCoUnchecked to
substCo and remove this function. Please don't use in new code.
substTysWith :: HasDebugCallStack => [TyVar] -> [Type] -> [Type] -> [Type] #
Type substitution, see zipTvSubst
substTyAddInScope :: HasDebugCallStack => Subst -> Type -> Type #
Substitute within a Type
after adding the free variables of the type
to the in-scope set. This is useful for the case when the free variables
aren't already in the in-scope set or easily available.
See also Note [The substitution invariant].
substTyUnchecked :: Subst -> Type -> Type #
Substitute within a Type
disabling the sanity checks.
The problems that the sanity checks in substTy catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTyUnchecked to
substTy and remove this function. Please don't use in new code.
substScaledTy :: HasDebugCallStack => Subst -> Scaled Type -> Scaled Type #
substScaledTyUnchecked :: HasDebugCallStack => Subst -> Scaled Type -> Scaled Type #
substTys :: HasDebugCallStack => Subst -> [Type] -> [Type] #
Substitute within several Type
s
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substScaledTys :: HasDebugCallStack => Subst -> [Scaled Type] -> [Scaled Type] #
substTysUnchecked :: Subst -> [Type] -> [Type] #
Substitute within several Type
s disabling the sanity checks.
The problems that the sanity checks in substTys catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTysUnchecked to
substTys and remove this function. Please don't use in new code.
substTheta :: HasDebugCallStack => Subst -> ThetaType -> ThetaType #
Substitute within a ThetaType
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substThetaUnchecked :: Subst -> ThetaType -> ThetaType #
Substitute within a ThetaType
disabling the sanity checks.
The problems that the sanity checks in substTys catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substThetaUnchecked to
substTheta and remove this function. Please don't use in new code.
substTyVar :: Subst -> TyVar -> Type #
substTyVarToTyVar :: HasDebugCallStack => Subst -> TyVar -> TyVar #
substTyVars :: Subst -> [TyVar] -> [Type] #
substCo :: HasDebugCallStack => Subst -> Coercion -> Coercion #
Substitute within a Coercion
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substCoUnchecked :: Subst -> Coercion -> Coercion #
Substitute within a Coercion
disabling sanity checks.
The problems that the sanity checks in substCo catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substCoUnchecked to
substCo and remove this function. Please don't use in new code.
substTyVarBndr :: HasDebugCallStack => Subst -> TyVar -> (Subst, TyVar) #
substTyVarBndrs :: HasDebugCallStack => Subst -> [TyVar] -> (Subst, [TyVar]) #
substVarBndr :: HasDebugCallStack => Subst -> TyCoVar -> (Subst, TyCoVar) #
substVarBndrs :: HasDebugCallStack => Subst -> [TyCoVar] -> (Subst, [TyCoVar]) #
cloneTyVarBndrs :: Subst -> [TyVar] -> UniqSupply -> (Subst, [TyVar]) #
substTyCoBndr :: Subst -> PiTyBinder -> (Subst, PiTyBinder) #
tidyVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) #
This tidies up a type for printing in an error message, or in an interface file.
It doesn't change the uniques at all, just the print names.
tidyFreeTyCoVars :: TidyEnv -> [TyCoVar] -> TidyEnv #
Add the free TyVar
s to the env in tidy form,
so that we can tidy the type they are free in
tidyOpenTyCoVar :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) #
Treat a new TyCoVar
as a binder, and give it a fresh tidy name
using the environment if one has not already been allocated. See
also tidyVarBndr
tidyTyCoVarOcc :: TidyEnv -> TyCoVar -> TyCoVar #
tidyTypes :: TidyEnv -> [Type] -> [Type] #
Tidy a list of Types
See Note [Strictness in tidyType and friends]
tidyOpenTypes :: TidyEnv -> [Type] -> (TidyEnv, [Type]) #
Grabs the free type variables, tidies them
and then uses tidyType
to work over the type itself
tidyTopType :: Type -> Type #
Calls tidyType
on a top-level type (i.e. with an empty tidying environment)
coreFullView :: Type -> Type #
Iterates coreView
until there is no more to synonym to expand.
NB: coreFullView is non-recursive and can be inlined;
core_full_view is the recursive one
See Note [Inlining coreView].
kindRep :: HasDebugCallStack => Kind -> RuntimeRepType #
Extract the RuntimeRep classifier of a type from its kind. For example,
kindRep * = LiftedRep
; Panics if this is not possible.
Treats * and Constraint as the same
kindRep_maybe :: HasDebugCallStack => Kind -> Maybe RuntimeRepType #
Given a kind (TYPE rr) or (CONSTRAINT rr), extract its RuntimeRep classifier rr.
For example, kindRep_maybe * = Just LiftedRep
Returns Nothing
if the kind is not of form (TYPE rr)
isUnliftedTypeKind :: Kind -> Bool #
Returns True if the kind classifies unlifted types (like 'Int#') and False otherwise. Note that this returns False for representation-polymorphic kinds, which may be specialized to a kind that classifies unlifted types.
pickyIsLiftedTypeKind :: Kind -> Bool #
kindBoxedRepLevity_maybe :: Type -> Maybe Levity #
isLiftedRuntimeRep :: RuntimeRepType -> Bool #
Check whether a type of kind RuntimeRep
is lifted.
- True of
LiftedRep :: RuntimeRep
- False of type variables, type family applications,
and of other reps such as
IntRep :: RuntimeRep
.
isUnliftedRuntimeRep :: RuntimeRepType -> Bool #
Check whether a type of kind RuntimeRep
is unlifted.
- True of definitely unlifted
RuntimeRep
s such asUnliftedRep
,IntRep
,FloatRep
, ... - False of
LiftedRep
, - False for type variables and type family applications.
isLiftedLevity :: Type -> Bool #
isUnliftedLevity :: Type -> Bool #
isRuntimeRepVar :: TyVar -> Bool #
Is a tyvar of type RuntimeRep
?
isLevityVar :: TyVar -> Bool #
Is a tyvar of type PromDataConInfo
?
isMultiplicityVar :: TyVar -> Bool #
Is a tyvar of type Multiplicity
?
splitRuntimeRep_maybe :: RuntimeRepType -> Maybe (TyCon, [Type]) #
(splitRuntimeRep_maybe rr) takes a Type rr :: RuntimeRep, and
returns the (TyCon,[Type]) for the RuntimeRep, if possible, where
the TyCon is one of the promoted DataCons of RuntimeRep.
Remember: the unique on TyCon that is a a promoted DataCon is the
same as the unique on the DataCon
See Note [Promoted data constructors] in GHC.Core.TyCon
May not be possible if rr
is a type variable or type
family application
isBoxedRuntimeRep :: RuntimeRepType -> Bool #
See isBoxedRuntimeRep_maybe
.
runtimeRepLevity_maybe :: RuntimeRepType -> Maybe Levity #
Check whether a type (usually of kind RuntimeRep
) is lifted, unlifted,
or unknown. Returns Nothing if the type isn't of kind RuntimeRep
.
`runtimeRepLevity_maybe rr` returns:
levityType_maybe :: LevityType -> Maybe Levity #
levityType_maybe
takes a Type of kind Levity, and returns its levity
May not be possible for a type variable or type family application
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]) #
getTyVar :: HasDebugCallStack => Type -> TyVar #
Attempts to obtain the type variable underlying a Type
, and panics with the
given message if this is not a type variable type. See also getTyVar_maybe
repGetTyVar_maybe :: Type -> Maybe TyVar #
Attempts to obtain the type variable underlying a Type
, without
any expansion
getCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN) #
If the type is a tyvar, possibly under a cast, returns it, along with the coercion. Thus, the co is :: kind tv ~N kind ty
splitAppTy_maybe :: Type -> Maybe (Type, Type) #
Attempt to take a type application apart, whether it is a function, type constructor, or plain type application. Note that type family applications are NEVER unsaturated by this!
splitAppTy :: Type -> (Type, Type) #
Attempts to take a type application apart, as in splitAppTy_maybe
,
and panics if this is not possible
splitAppTyNoView_maybe :: HasDebugCallStack => Type -> Maybe (Type, Type) #
Does the AppTy split as in splitAppTy_maybe
, but assumes that
any coreView stuff is already done
tcSplitAppTyNoView_maybe :: Type -> Maybe (Type, Type) #
Just like splitAppTyNoView_maybe, but does not split (c => t) See Note [Decomposing fat arrow c=>t]
splitAppTys :: HasDebugCallStack => Type -> (Type, [Type]) #
Recursively splits a type as far as is possible, leaving a residual type being applied to and the type arguments applied to it. Never fails, even if that means returning an empty list of type applications.
splitAppTysNoView :: HasDebugCallStack => Type -> (Type, [Type]) #
Like splitAppTys
, but doesn't look through type synonyms
mkNumLitTy :: Integer -> Type #
isNumLitTy :: Type -> Maybe Integer #
Is this a numeric literal. We also look through type synonyms.
mkStrLitTy :: FastString -> Type #
isStrLitTy :: Type -> Maybe FastString #
Is this a symbol literal. We also look through type synonyms.
mkCharLitTy :: Char -> Type #
isCharLitTy :: Type -> Maybe Char #
Is this a char literal? We also look through type synonyms.
userTypeError_maybe :: Type -> Maybe ErrorMsgType #
Is this type a custom user error? If so, give us the error message.
pprUserTypeErrorTy :: ErrorMsgType -> SDoc #
Render a type corresponding to a user type error into a SDoc.
funTyConAppTy_maybe :: FunTyFlag -> Type -> Type -> Type -> Maybe (TyCon, [Type]) #
Given the components of a FunTy figure out the corresponding TyConApp.
tyConAppFunTy_maybe :: HasDebugCallStack => TyCon -> [Type] -> Maybe Type #
Return Just if this TyConApp should be represented as a FunTy
tyConAppFunCo_maybe :: HasDebugCallStack => Role -> TyCon -> [Coercion] -> Maybe Coercion #
Return Just if this TyConAppCo should be represented as a FunCo
mkFunctionType :: HasDebugCallStack => Mult -> Type -> Type -> Type #
This one works out the FunTyFlag from the argument type See GHC.Types.Var Note [FunTyFlag]
mkScaledFunctionTys :: [Scaled Type] -> Type -> Type #
Like mkFunctionType, compute the FunTyFlag from the arguments
splitFunTy :: Type -> (Mult, Type, Type) #
Attempts to extract the multiplicity, argument and result types from a type,
and panics if that is not possible. See also splitFunTy_maybe
splitFunTy_maybe :: Type -> Maybe (FunTyFlag, Mult, Type, Type) #
Attempts to extract the multiplicity, argument and result types from a type
funArgTy :: HasDebugCallStack => Type -> Type #
Just like piResultTys
but for a single argument
Try not to iterate piResultTy
, because it's inefficient to substitute
one variable at a time; instead use 'piResultTys"
Extract the function argument type and panic if that is not possible
piResultTys :: HasDebugCallStack => Type -> [Type] -> Type #
(piResultTys f_ty [ty1, .., tyn]) gives the type of (f ty1 .. tyn)
where f :: f_ty
piResultTys
is interesting because:
1. f_ty
may have more for-alls than there are args
2. Less obviously, it may have fewer for-alls
For case 2. think of:
piResultTys (forall a.a) [forall b.b, Int]
This really can happen, but only (I think) in situations involving
undefined. For example:
undefined :: forall a. a
Term: undefined (forall b. b->b)
Int
This term should have type (Int -> Int), but notice that
there are more type args than foralls in undefined
s type.
tyConAppTyConPicky_maybe :: Type -> Maybe TyCon #
Retrieve the tycon heading this type, if there is one. Does not look through synonyms.
tyConAppTyCon :: HasDebugCallStack => Type -> TyCon #
tyConAppArgs_maybe :: Type -> Maybe [Type] #
The same as snd . splitTyConApp
tyConAppArgs :: HasCallStack => Type -> [Type] #
splitTyConAppNoView_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #
tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type]) #
tcSplitTyConApp_maybe splits a type constructor application into its type constructor and applied types.
Differs from splitTyConApp_maybe in that it does *not* split types headed with (=>), as that's not a TyCon in the type-checker.
Note that this may fail (in funTyConAppTy_maybe) in the case
of a FunTy
with an argument of unknown kind FunTy
(e.g. `FunTy (a :: k) Int`, since the kind of a
isn't of
the form `TYPE rep`. This isn't usually a problem but may
be temporarily the case during canonicalization:
see Note [Decomposing FunTy] in GHC.Tc.Solver.Equality
and Note [The Purely Kinded Type Invariant (PKTI)] in GHC.Tc.Gen.HsType,
Wrinkle around FunTy
Consequently, you may need to zonk your type before using this function.
tcSplitTyConApp :: Type -> (TyCon, [Type]) #
newTyConInstRhs :: TyCon -> [Type] -> Type #
Unwrap one layer
of newtype on a type constructor and its
arguments, using an eta-reduced version of the newtype
if possible.
This requires tys to have at least newTyConInstArity tycon
elements.
isCoercionTy_maybe :: Type -> Maybe Coercion #
stripCoercionTy :: Type -> Coercion #
tyConBindersPiTyBinders :: [TyConBinder] -> [PiTyBinder] #
mkTyCoForAllTy :: TyCoVar -> ForAllTyFlag -> Type -> Type #
Make a dependent forall over a TyCoVar
mkTyCoForAllTys :: [ForAllTyBinder] -> Type -> Type #
Make a dependent forall over a TyCoVar
mkInfForAllTy :: TyVar -> Type -> Type #
Like mkTyCoInvForAllTy
, but tv should be a tyvar
mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type #
Like mkForAllTys
, but assumes all variables are dependent and
Inferred
, a common case
mkInfForAllTys :: [TyVar] -> Type -> Type #
Like mkTyCoInvForAllTys
, but tvs should be a list of tyvar
mkSpecForAllTy :: TyVar -> Type -> Type #
Like mkForAllTy
, but assumes the variable is dependent and Specified
,
a common case
mkSpecForAllTys :: [TyVar] -> Type -> Type #
Like mkForAllTys
, but assumes all variables are dependent and
Specified
, a common case
mkVisForAllTys :: [TyVar] -> Type -> Type #
Like mkForAllTys, but assumes all variables are dependent and visible
:: [TyVar] | binders |
-> TyCoVarSet | free variables of result |
-> [TyConBinder] |
Given a list of type-level vars and the free vars of a result kind, makes PiTyBinders, preferring anonymous binders if the variable is, in fact, not dependent. e.g. mkTyConBindersPreferAnon (k:*),(b:k),(c:k) We want (k:*) Named, (b:k) Anon, (c:k) Anon
All non-coercion binders are visible.
splitForAllForAllTyBinders :: Type -> ([ForAllTyBinder], Type) #
Take a ForAllTy apart, returning the binders and result type
splitForAllTyCoVars :: Type -> ([TyCoVar], Type) #
Take a ForAllTy apart, returning the list of tycovars and the result type. This always succeeds, even if it returns only an empty list. Note that the result type returned may have free variables that were bound by a forall.
splitForAllTyVars :: Type -> ([TyVar], Type) #
Like splitForAllTyCoVars
, but split only for tyvars.
This always succeeds, even if it returns only an empty list. Note that the
result type returned may have free variables that were bound by a forall.
splitForAllReqTyBinders :: Type -> ([ReqTyBinder], Type) #
Like splitForAllTyCoVars
, but only splits ForAllTy
s with Required
type
variable binders. Furthermore, each returned tyvar is annotated with ()
.
splitForAllInvisTyBinders :: Type -> ([InvisTyBinder], Type) #
Like splitForAllTyCoVars
, but only splits ForAllTy
s with Invisible
type
variable binders. Furthermore, each returned tyvar is annotated with its
Specificity
.
isForAllTy :: Type -> Bool #
Checks whether this is a proper forall (with a named binder)
isForAllTy_ty :: Type -> Bool #
Like isForAllTy
, but returns True only if it is a tyvar binder
isForAllTy_invis_ty :: Type -> Bool #
Like isForAllTy
, but returns True only if it is an inferred tyvar binder
isForAllTy_co :: Type -> Bool #
Like isForAllTy
, but returns True only if it is a covar binder
splitForAllTyCoVar :: Type -> (TyCoVar, Type) #
Take a forall type apart, or panics if that is not possible.
dropForAlls :: Type -> Type #
Drops all ForAllTys
splitForAllForAllTyBinder_maybe :: Type -> Maybe (ForAllTyBinder, Type) #
Attempts to take a ForAllTy apart, returning the full ForAllTyBinder
splitForAllTyCoVar_maybe :: Type -> Maybe (TyCoVar, Type) #
Attempts to take a ForAllTy apart, returning the Var
splitForAllTyVar_maybe :: Type -> Maybe (TyVar, Type) #
Attempts to take a ForAllTy apart, but only if the binder is a TyVar
splitForAllCoVar_maybe :: Type -> Maybe (CoVar, Type) #
Like splitForAllTyCoVar_maybe
, but only returns Just if it is a covar binder.
splitPiTy_maybe :: Type -> Maybe (PiTyBinder, Type) #
Attempts to take a forall type apart; works with proper foralls and functions
splitPiTy :: Type -> (PiTyBinder, Type) #
Takes a forall type apart, or panics
splitPiTys :: Type -> ([PiTyBinder], Type) #
Split off all PiTyBinders to a type, splitting both proper foralls and functions
getRuntimeArgTys :: Type -> [(Scaled Type, FunTyFlag)] #
Extracts a list of run-time arguments from a function type, looking through newtypes to the right of arrows.
Examples:
newtype Identity a = I a getRuntimeArgTys (Int -> Bool -> Double) == [(Int, FTF_T_T), (Bool, FTF_T_T)] getRuntimeArgTys (Identity Int -> Bool -> Double) == [(Identity Int, FTF_T_T), (Bool, FTF_T_T)] getRuntimeArgTys (Int -> Identity (Bool -> Identity Double)) == [(Int, FTF_T_T), (Bool, FTF_T_T)] getRuntimeArgTys (forall a. Show a => Identity a -> a -> Int -> Bool) == [(Show a, FTF_C_T), (Identity a, FTF_T_T),(a, FTF_T_T),(Int, FTF_T_T)]
Note that, in the last case, the returned types might mention an out-of-scope type variable. This function is used only when we really care about the kinds of the returned types, so this is OK.
- *Warning**: this function can return an infinite list. For example:
newtype N a = MkN (a -> N a) getRuntimeArgTys (N a) == repeat (a, FTF_T_T)
invisibleTyBndrCount :: Type -> Int #
splitInvisPiTys :: Type -> ([PiTyBinder], Type) #
Like splitPiTys
, but returns only *invisible* binders, including constraints.
Stops at the first visible binder.
splitInvisPiTysN :: Int -> Type -> ([PiTyBinder], Type) #
Same as splitInvisPiTys
, but stop when
- you have found n
PiTyBinder
s,
- or you run out of invisible binders
filterOutInvisibleTypes :: TyCon -> [Type] -> [Type] #
filterOutInferredTypes :: TyCon -> [Type] -> [Type] #
partitionInvisibles :: [(a, ForAllTyFlag)] -> ([a], [a]) #
Given a list of things paired with their visibilities, partition the things into (invisible things, visible things).
tyConForAllTyFlags :: TyCon -> [Type] -> [ForAllTyFlag] #
Given a TyCon
and a list of argument types to which the TyCon
is
applied, determine each argument's visibility
(Inferred
, Specified
, or Required
).
Wrinkle: consider the following scenario:
T :: forall k. k -> k tyConForAllTyFlags T [forall m. m -> m -> m, S, R, Q]
After substituting, we get
T (forall m. m -> m -> m) :: (forall m. m -> m -> m) -> forall n. n -> n -> n
Thus, the first argument is invisible, S
is visible, R
is invisible again,
and Q
is visible.
appTyForAllTyFlags :: Type -> [Type] -> [ForAllTyFlag] #
Given a Type
and a list of argument types to which the Type
is
applied, determine each argument's visibility
(Inferred
, Specified
, or Required
).
Most of the time, the arguments will be Required
, but not always. Consider
f :: forall a. a -> Type
. In f Type Bool
, the first argument (Type
) is
Specified
and the second argument (Bool
) is Required
. It is precisely
this sort of higher-rank situation in which appTyForAllTyFlags
comes in handy,
since f Type Bool
would be represented in Core using AppTy
s.
(See also #15792).
isAtomicTy :: Type -> Bool #
mkFamilyTyConApp :: TyCon -> [Type] -> Type #
Given a family instance TyCon and its arg types, return the corresponding family type. E.g:
data family T a data instance T (Maybe b) = MkT b
Where the instance tycon is :RTL, so:
mkFamilyTyConApp :RTL Int = T (Maybe Int)
coAxNthLHS :: forall (br :: BranchFlag). CoAxiom br -> Int -> Type #
Get the type on the LHS of a coercion induced by a type/data family instance.
isFamFreeTy :: Type -> Bool #
typeLevity :: HasDebugCallStack => Type -> Levity #
isUnliftedType :: HasDebugCallStack => Type -> Bool #
Is the given type definitely unlifted? See Type for what an unlifted type is.
Panics on representation-polymorphic types; See mightBeUnliftedType
for
a more approximate predicate that behaves better in the presence of
representation polymorphism.
mightBeLiftedType :: Type -> Bool #
definitelyLiftedType :: Type -> Bool #
mightBeUnliftedType :: Type -> Bool #
definitelyUnliftedType :: Type -> Bool #
isBoxedType :: Type -> Bool #
See Type for what a boxed type is.
Panics on representation-polymorphic types; See mightBeUnliftedType
for
a more approximate predicate that behaves better in the presence of
representation polymorphism.
isRuntimeRepKindedTy :: Type -> Bool #
Is this a type of kind RuntimeRep? (e.g. LiftedRep)
dropRuntimeRepArgs :: [Type] -> [Type] #
Drops prefix of RuntimeRep constructors in TyConApp
s. Useful for e.g.
dropping 'LiftedRep arguments of unboxed tuple TyCon applications:
dropRuntimeRepArgs [ 'LiftedRep, 'IntRep , String, Int# ] == [String, Int#]
getRuntimeRep :: HasDebugCallStack => Type -> RuntimeRepType #
Extract the RuntimeRep classifier of a type. For instance,
getRuntimeRep_maybe Int = LiftedRep
. Panics if this is not possible.
isUnboxedTupleType :: Type -> Bool #
isUnboxedSumType :: Type -> Bool #
isDataFamilyAppType :: Type -> Bool #
Check whether a type is a data family type
isStrictType :: HasDebugCallStack => Type -> Bool #
Computes whether an argument (or let right hand side) should
be computed strictly or lazily, based only on its type.
Currently, it's just isUnliftedType
.
Panics on representation-polymorphic types.
isTerminatingType :: HasDebugCallStack => Type -> Bool #
True = a term of this type cannot be bottom This identifies the types described by Note [NON-BOTTOM-DICTS invariant] in GHC.Core NB: unlifted types are not terminating types! e.g. you can write a term (loop 1)::Int# that diverges.
isCoVarType :: Type -> Bool #
Does this type classify a core (unlifted) Coercion? At either role nominal or representational (t1 ~# t2) or (t1 ~R# t2) See Note [Types for coercions, predicates, and evidence] in GHC.Core.TyCo.Rep
isPrimitiveType :: Type -> Bool #
Returns true of types that are opaque to Haskell.
isValidJoinPointType :: JoinArity -> Type -> Bool #
Determine whether a type could be the type of a join point of given total
arity, according to the polymorphism rule. A join point cannot be polymorphic
in its return type, since given
join j a
b x y z = e1 in e2,
the types of e1 and e2 must be the same, and a and b are not in scope for e2.
(See Note [The polymorphism rule of join points] in GHC.Core.) Returns False
also if the type simply doesn't have enough arguments.
Note that we need to know how many arguments (type *and* value) the putative join point takes; for instance, if j :: forall a. a -> Int then j could be a binary join point returning an Int, but it could *not* be a unary join point returning a -> Int.
TODO: See Note [Excess polymorphism and join points]
sORTKind_maybe :: Kind -> Maybe (TypeOrConstraint, Type) #
isTYPEorCONSTRAINT :: Kind -> Bool #
Does this classify a type allowed to have values? Responds True to things like *, TYPE Lifted, TYPE IntRep, TYPE v, Constraint.
True of a kind `TYPE _` or `CONSTRAINT _`
tyConIsTYPEorCONSTRAINT :: TyCon -> Bool #
isConstraintLikeKind :: Kind -> Bool #
isConstraintKind :: Kind -> Bool #
tcIsLiftedTypeKind :: Kind -> Bool #
Is this kind equivalent to Type
i.e. TYPE LiftedRep?
tcIsBoxedTypeKind :: Kind -> Bool #
Is this kind equivalent to TYPE (BoxedRep l)
for some l :: Levity
?
isTypeLikeKind :: Kind -> Bool #
Is this kind equivalent to TYPE r
(for some unknown r)?
This considers Constraint
to be distinct from *
.
returnsConstraintKind :: Kind -> Bool #
typeHasFixedRuntimeRep :: HasDebugCallStack => Type -> Bool #
Returns True if a type has a syntactically fixed runtime rep, as per Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete.
This function is equivalent to `isFixedRuntimeRepKind . typeKind` but much faster.
Precondition: The type has kind (
TYPE
blah)
isFixedRuntimeRepKind :: HasDebugCallStack => Kind -> Bool #
Checks that a kind of the form Type
, Constraint
or 'TYPE r
is concrete. See isConcreteType
.
Precondition: The type has kind `TYPE blah` or `CONSTRAINT blah`
isConcreteType :: Type -> Bool #
Tests whether the given type is concrete, i.e. it whether it consists only of concrete type constructors, concrete type variables, and applications.
See Note [Concrete types] in GHC.Tc.Utils.Concrete.
:: Bool | Should specified binders count towards injective positions in the kind of the TyCon? (If you're using visible kind applications, then you want True here. |
-> TyCon | |
-> Int | The number of args the |
-> Bool | Does |
Does a TyCon
(that is applied to some number of arguments) need to be
ascribed with an explicit kind signature to resolve ambiguity if rendered as
a source-syntax type?
(See Note [When does a tycon application need an explicit kind signature?]
for a full explanation of what this function checks for.)
unrestricted :: a -> Scaled a #
Scale a payload by Many
irrelevantMult :: Scaled a -> a #
isLinearType :: Type -> Bool #
mkTYPEapp :: RuntimeRepType -> Type #
mkTYPEapp_maybe :: RuntimeRepType -> Maybe Type #
Given a RuntimeRep
, applies TYPE
to it.
On the fly it rewrites
TYPE LiftedRep --> liftedTypeKind (a synonym)
TYPE UnliftedRep --> unliftedTypeKind (ditto)
TYPE ZeroBitRep --> zeroBitTypeKind (ditto)
NB: no need to check for TYPE (BoxedRep Lifted), TYPE (BoxedRep Unlifted)
because those inner types should already have been rewritten
to LiftedRep and UnliftedRep respectively, by mkTyConApp
see Note [TYPE and CONSTRAINT] in GHC.Builtin.Types.Prim. See Note [Using synonyms to compress types] in GHC.Core.Type
mkCONSTRAINTapp :: RuntimeRepType -> Type #
Just like mkTYPEapp
mkCONSTRAINTapp_maybe :: RuntimeRepType -> Maybe Type #
Just like mkTYPEapp_maybe
mkBoxedRepApp_maybe :: LevityType -> Maybe Type #
Given a PromDataConInfo
, apply BoxedRep
to it
On the fly, rewrite
BoxedRep Lifted --> liftedRepTy (a synonym)
BoxedRep Unlifted --> unliftedRepTy (ditto)
See Note [TYPE and CONSTRAINT] in GHC.Builtin.Types.Prim.
See Note [Using synonyms to compress types] in GHC.Core.Type
mkTupleRepApp_maybe :: Type -> Maybe Type #
Given a `[RuntimeRep]`, apply TupleRep
to it
On the fly, rewrite
TupleRep [] -> zeroBitRepTy (a synonym)
See Note [TYPE and CONSTRAINT] in GHC.Builtin.Types.Prim.
See Note [Using synonyms to compress types] in GHC.Core.Type
module GHC.Core.TyCon
A Coercion
is concrete evidence of the equality/convertibility
of two types.
Instances
Data Coercion | |
Defined in GHC.Core.TyCo.Rep 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 | |
Defined in GHC.Core.TyCo.Rep | |
Eq (DeBruijn Coercion) | |
See Note [Roles] in GHC.Core.Coercion
Order of constructors matters: the Ord instance coincides with the *super*typing relation on roles.
Instances
Data Role | |
Defined in Language.Haskell.Syntax.Basic 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 # 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 # | |
Eq Role | |
Ord Role | |
type Anno (Maybe Role) | |
Defined in GHC.Hs.Decls | |
type Anno (Maybe Role) | |
Defined in GHC.Hs.Decls |
Variable
Essentially a typed Name
, that may also contain some additional information
about the Var
and its use sites.
Instances
Data Var | |
Defined in GHC.Types.Var 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 # 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 # | |
NamedThing Var | |
Defined in GHC.Types.Var | |
HasOccName Var | |
Defined in GHC.Types.Var | |
Uniquable Var | |
Defined in GHC.Types.Var | |
Outputable Var | |
Defined in GHC.Types.Var | |
Eq Var | |
Ord Var | |
Eq (DeBruijn Var) | |
OutputableBndr (Id, TagSig) | |
Defined in GHC.Stg.InferTags.TagSig pprBndr :: BindingSite -> (Id, TagSig) -> SDoc # pprPrefixOcc :: (Id, TagSig) -> SDoc # pprInfixOcc :: (Id, TagSig) -> SDoc # bndrIsJoin_maybe :: (Id, TagSig) -> JoinPointHood # | |
type Anno Id | |
Defined in GHC.Hs.Extension |
type MCoercionN = MCoercion #
A semantically more meaningful type to represent what may or may not be a
useful Coercion
.
Instances
Data MCoercion | |
Defined in GHC.Core.TyCo.Rep 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 | |
Defined in GHC.Core.TyCo.Rep |
data UnivCoProvenance #
For simplicity, we have just one UnivCo that represents a coercion from
some type to some other type, with (in general) no restrictions on the
type. The UnivCoProvenance specifies more exactly what the coercion really
is and why a program should (or shouldn't!) trust the coercion.
It is reasonable to consider each constructor of UnivCoProvenance
as a totally independent coercion form; their only commonality is
that they don't tell you what types they coercion between. (That info
is in the UnivCo
constructor of Coercion
.
Instances
Data UnivCoProvenance | |
Defined in GHC.Core.TyCo.Rep 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 | |
Defined in GHC.Core.TyCo.Rep ppr :: UnivCoProvenance -> SDoc # |
Instances
Data CoSel | |
Defined in GHC.Core.TyCo.Rep gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CoSel -> c CoSel # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CoSel # dataTypeOf :: CoSel -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CoSel) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoSel) # gmapT :: (forall b. Data b => b -> b) -> CoSel -> CoSel # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CoSel -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CoSel -> r # gmapQ :: (forall d. Data d => d -> u) -> CoSel -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CoSel -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CoSel -> m CoSel # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CoSel -> m CoSel # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CoSel -> m CoSel # | |
NFData CoSel | |
Defined in GHC.Core.TyCo.Rep | |
Binary CoSel | |
Outputable CoSel | |
Defined in GHC.Core.TyCo.Rep | |
Eq CoSel | |
Instances
Data FunSel | |
Defined in GHC.Core.TyCo.Rep gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunSel -> c FunSel # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunSel # toConstr :: FunSel -> Constr # dataTypeOf :: FunSel -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunSel) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunSel) # gmapT :: (forall b. Data b => b -> b) -> FunSel -> FunSel # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunSel -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunSel -> r # gmapQ :: (forall d. Data d => d -> u) -> FunSel -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunSel -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunSel -> m FunSel # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunSel -> m FunSel # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunSel -> m FunSel # | |
Outputable FunSel | |
Defined in GHC.Core.TyCo.Rep | |
Eq FunSel | |
data LeftOrRight #
Instances
Data LeftOrRight | |
Defined in GHC.Types.Basic 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 | |
Defined in GHC.Types.Basic put_ :: BinHandle -> LeftOrRight -> IO () # put :: BinHandle -> LeftOrRight -> IO (Bin LeftOrRight) # get :: BinHandle -> IO LeftOrRight # | |
Outputable LeftOrRight | |
Defined in GHC.Types.Basic ppr :: LeftOrRight -> SDoc # | |
Eq LeftOrRight | |
Defined in GHC.Types.Basic (==) :: LeftOrRight -> LeftOrRight -> Bool # (/=) :: LeftOrRight -> LeftOrRight -> Bool # |
data CoercionHole #
A coercion to be filled in by the type-checker. See Note [Coercion holes]
Instances
Data CoercionHole | |
Defined in GHC.Core.TyCo.Rep 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 # | |
Uniquable CoercionHole | |
Defined in GHC.Core.TyCo.Rep getUnique :: CoercionHole -> Unique # | |
Outputable CoercionHole | |
Defined in GHC.Core.TyCo.Rep ppr :: CoercionHole -> SDoc # |
type MCoercionR = MCoercion #
data LiftingContext #
Instances
Outputable LiftingContext | |
Defined in GHC.Core.Coercion ppr :: LiftingContext -> SDoc # |
data NormaliseStepResult ev #
The result of stepping in a normalisation function.
See topNormaliseTypeX
.
NS_Done | Nothing more to do |
NS_Abort | Utter failure. The outer function should fail too. |
NS_Step RecTcChecker Type ev | We stepped, yielding new bits; ^ ev is evidence; Usually a co :: old type ~ new type |
Instances
Functor NormaliseStepResult | |
Defined in GHC.Core.Coercion fmap :: (a -> b) -> NormaliseStepResult a -> NormaliseStepResult b # (<$) :: a -> NormaliseStepResult b -> NormaliseStepResult a # | |
Outputable ev => Outputable (NormaliseStepResult ev) | |
Defined in GHC.Core.Coercion ppr :: NormaliseStepResult ev -> SDoc # |
type NormaliseStepper ev = RecTcChecker -> TyCon -> [Type] -> NormaliseStepResult ev #
A function to check if we can reduce a type by one step. Used
with topNormaliseTypeX
.
pickLR :: LeftOrRight -> (a, a) -> a #
Is this a coercion variable?
Satisfies
.isId
v ==> isCoVar
v == not (isNonCoVarId
v)
topNormaliseNewType_maybe :: Type -> Maybe (Coercion, Type) #
Sometimes we want to look through a newtype
and get its associated coercion.
This function strips off newtype
layers enough to reveal something that isn't
a newtype
. Specifically, here's the invariant:
topNormaliseNewType_maybe rec_nts ty = Just (co, ty')
then (a) co : ty ~R ty'
.
(b) ty' is not a newtype.
The function returns Nothing
for non-newtypes
,
or unsaturated applications
This function does *not* look through type families, because it has no access to the type family environment. If you do have that at hand, consider to use topNormaliseType_maybe, which should be a drop-in replacement for topNormaliseNewType_maybe If topNormliseNewType_maybe ty = Just (co, ty'), then co : ty ~R ty'
coercionType :: Coercion -> Type #
coercionRKind :: Coercion -> Type #
coercionLKind :: Coercion -> Type #
coercionKind :: Coercion -> Pair Type #
If it is the case that
c :: (t1 ~ t2)
i.e. the kind of c
relates t1
and t2
, then coercionKind c = Pair t1 t2
.
mkCoercionType :: Role -> Type -> Type -> Type #
Makes a coercion type from two types: the types whose equality
is proven by the relevant Coercion
coVarKindsTypesRole :: HasDebugCallStack => CoVar -> (Kind, Kind, Type, Type, Role) #
decomposePiCos :: HasDebugCallStack => CoercionN -> Pair Type -> [Type] -> ([CoercionN], CoercionN) #
isReflexiveCo :: Coercion -> Bool #
Slowly checks if the coercion is reflexive. Don't call this in a loop, as it walks over the entire coercion.
isReflCo :: Coercion -> Bool #
Tests if this coercion is obviously reflexive. Guaranteed to work
very quickly. Sometimes a coercion can be reflexive, but not obviously
so. c.f. isReflexiveCo
isGReflCo :: Coercion -> Bool #
Tests if this coercion is obviously a generalized reflexive coercion. Guaranteed to work very quickly.
mkAxiomRuleCo :: CoAxiomRule -> [Coercion] -> Coercion #
:: Role | role of the created coercion, "r" |
-> CoercionN | :: phi1 ~N phi2 |
-> Coercion | g1 :: phi1 |
-> Coercion | g2 :: phi2 |
-> Coercion | :: g1 ~r g2 |
Make a "coercion between coercions".
mkSubCo :: HasDebugCallStack => Coercion -> Coercion #
mkNomReflCo :: Type -> Coercion #
Make a nominal reflexive coercion
mkLRCo :: LeftOrRight -> Coercion -> Coercion #
mkSymCo :: Coercion -> Coercion #
Create a symmetric version of the given Coercion
that asserts
equality between the same types but in the other "direction", so
a kind of t1 ~ t2
becomes the kind t2 ~ t1
.
:: UnivCoProvenance | |
-> Role | role of the built coercion, "r" |
-> Type | t1 :: k1 |
-> Type | t2 :: k2 |
-> Coercion | :: t1 ~r t2 |
Make a universal coercion between two arbitrary types.
mkPhantomCo :: Coercion -> Type -> Type -> Coercion #
Make a phantom coercion between two types. The coercion passed in must be a nominal coercion between the kinds of the types.
mkAxiomInstCo :: CoAxiom Branched -> BranchIndex -> [Coercion] -> Coercion #
mkForAllCo :: HasDebugCallStack => TyCoVar -> ForAllTyFlag -> ForAllTyFlag -> CoercionN -> Coercion -> Coercion #
Make a Coercion from a tycovar, a kind coercion, and a body coercion.
mkTyConAppCo :: HasDebugCallStack => Role -> TyCon -> [Coercion] -> Coercion #
Apply a type constructor to a list of coercions. It is the caller's responsibility to get the roles correct on argument coercions.
coHoleCoVar :: CoercionHole -> CoVar #
setCoHoleCoVar :: CoercionHole -> CoVar -> CoercionHole #
coercionSize :: Coercion -> Int #
tyCoVarsOfCo :: Coercion -> TyCoVarSet #
tyCoVarsOfCos :: [Coercion] -> TyCoVarSet #
coVarsOfCo :: Coercion -> CoVarSet #
tyCoVarsOfCoDSet :: Coercion -> DTyCoVarSet #
Get a deterministic set of the vars free in a coercion
tyCoFVsOfCo :: Coercion -> FV #
tyCoFVsOfCos :: [Coercion] -> FV #
getCvSubstEnv :: Subst -> CvSubstEnv #
substCoWith :: HasDebugCallStack => [TyVar] -> [Type] -> Coercion -> Coercion #
Coercion substitution, see zipTvSubst
substCos :: HasDebugCallStack => Subst -> [Coercion] -> [Coercion] #
Substitute within several Coercion
s
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substCoVar :: Subst -> CoVar -> Coercion #
substCoVars :: Subst -> [CoVar] -> [Coercion] #
substCoVarBndr :: HasDebugCallStack => Subst -> CoVar -> (Subst, CoVar) #
tidyCo :: TidyEnv -> Coercion -> Coercion #
Tidy a Coercion
See Note [Strictness in tidyType and friends]
pprParendCo :: Coercion -> SDoc #
setCoVarUnique :: CoVar -> Unique -> CoVar #
setCoVarName :: CoVar -> Name -> CoVar #
etaExpandCoAxBranch :: CoAxBranch -> ([TyVar], [Type], Type) #
pprCoAxiom :: forall (br :: BranchFlag). CoAxiom br -> SDoc #
pprCoAxBranchUser :: TyCon -> CoAxBranch -> SDoc #
pprCoAxBranchLHS :: TyCon -> CoAxBranch -> SDoc #
pprCoAxBranch :: TyCon -> CoAxBranch -> SDoc #
checkReflexiveMCo :: MCoercion -> MCoercion #
isGReflMCo :: MCoercion -> Bool #
Tests if this MCoercion is obviously generalized reflexive Guaranteed to work very quickly.
mkTransMCo :: MCoercion -> MCoercion -> MCoercion #
Compose two MCoercions via transitivity
mkTransMCoL :: MCoercion -> Coercion -> MCoercion #
mkTransMCoR :: Coercion -> MCoercion -> MCoercion #
mkFunResMCo :: Id -> MCoercionR -> MCoercionR #
mkGReflLeftMCo :: Role -> Type -> MCoercionN -> Coercion #
mkGReflRightMCo :: Role -> Type -> MCoercionN -> Coercion #
mkCoherenceRightMCo :: Role -> Type -> MCoercionN -> Coercion -> Coercion #
Like mkCoherenceRightCo
, but with an MCoercion
decomposeFunCo :: HasDebugCallStack => Coercion -> (CoercionN, Coercion, Coercion) #
getCoVar_maybe :: Coercion -> Maybe CoVar #
Extract a covar, if possible. This check is dirty. Be ashamed of yourself. (It's dirty because it cares about the structure of a coercion, which is morally reprehensible.)
splitAppCo_maybe :: Coercion -> Maybe (Coercion, Coercion) #
Attempt to take a coercion application apart.
splitForAllCo_maybe :: Coercion -> Maybe (TyCoVar, ForAllTyFlag, ForAllTyFlag, Coercion, Coercion) #
splitForAllCo_ty_maybe :: Coercion -> Maybe (TyVar, ForAllTyFlag, ForAllTyFlag, Coercion, Coercion) #
Like splitForAllCo_maybe
, but only returns Just for tyvar binder
splitForAllCo_co_maybe :: Coercion -> Maybe (CoVar, ForAllTyFlag, ForAllTyFlag, Coercion, Coercion) #
Like splitForAllCo_maybe
, but only returns Just for covar binder
coVarLType :: HasDebugCallStack => CoVar -> Type #
coVarRType :: HasDebugCallStack => CoVar -> Type #
coVarTypes :: HasDebugCallStack => CoVar -> Pair Type #
mkRuntimeRepCo :: HasDebugCallStack => Coercion -> Coercion #
Given a coercion `co :: (t1 :: TYPE r1) ~ (t2 :: TYPE r2)` produce a coercion `rep_co :: r1 ~ r2` But actually it is possible that co :: (t1 :: CONSTRAINT r1) ~ (t2 :: CONSTRAINT r2) or co :: (t1 :: TYPE r1) ~ (t2 :: CONSTRAINT r2) or co :: (t1 :: CONSTRAINT r1) ~ (t2 :: TYPE r2) See Note [mkRuntimeRepCo]
isReflCoVar_maybe :: Var -> Maybe Coercion #
isGReflCo_maybe :: Coercion -> Maybe (Type, Role) #
Returns the type coerced if this coercion is a generalized reflexive coercion. Guaranteed to work very quickly.
isReflCo_maybe :: Coercion -> Maybe (Type, Role) #
Returns the type coerced if this coercion is reflexive. Guaranteed
to work very quickly. Sometimes a coercion can be reflexive, but not
obviously so. c.f. isReflexiveCo_maybe
isReflexiveCo_maybe :: Coercion -> Maybe (Type, Role) #
Extracts the coerced type from a reflexive coercion. This potentially walks over the entire coercion, so avoid doing this in a loop.
mkRepReflCo :: Type -> Coercion #
Make a representational reflexive coercion
mkFunCoNoFTF :: HasDebugCallStack => Role -> CoercionN -> Coercion -> Coercion -> Coercion #
mkHomoForAllCos :: [ForAllTyBinder] -> Coercion -> Coercion #
Make a Coercion quantified over a type/coercion variable; the variable has the same kind and visibility in both sides of the coercion
mkNakedForAllCo :: TyVar -> ForAllTyFlag -> ForAllTyFlag -> CoercionN -> Coercion -> Coercion #
mkCoVarCos :: [CoVar] -> [Coercion] #
mkAxInstCo :: forall (br :: BranchFlag). Role -> CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Coercion #
mkUnbranchedAxInstCo :: Role -> CoAxiom Unbranched -> [Type] -> [Coercion] -> Coercion #
mkAxInstRHS :: forall (br :: BranchFlag). CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Type #
mkUnbranchedAxInstRHS :: CoAxiom Unbranched -> [Type] -> [Coercion] -> Type #
mkAxInstLHS :: forall (br :: BranchFlag). CoAxiom br -> BranchIndex -> [Type] -> [Coercion] -> Type #
Return the left-hand type of the axiom, when the axiom is instantiated at the types given.
mkUnbranchedAxInstLHS :: CoAxiom Unbranched -> [Type] -> [Coercion] -> Type #
Instantiate the left-hand side of an unbranched axiom
mkHoleCo :: CoercionHole -> Coercion #
Make a coercion from a coercion hole
:: FunSel | |
-> a | multiplicity |
-> a | argument |
-> a | result |
-> a | One of the above three |
Extract the nth field of a FunCo
mkGReflRightCo :: Role -> Type -> CoercionN -> Coercion #
Given ty :: k1
, co :: k1 ~ k2
,
produces co' :: ty ~r (ty |> co)
mkGReflLeftCo :: Role -> Type -> CoercionN -> Coercion #
Given r
, ty :: k1
, and co :: k1 ~N k2
,
produces co' :: (ty |> co) ~r ty
mkCoherenceLeftCo :: Role -> Type -> CoercionN -> Coercion -> Coercion #
Given ty :: k1
, co :: k1 ~ k2
, co2:: ty ~r ty'
,
produces @co' :: (ty |> co) ~r ty'
It is not only a utility function, but it saves allocation when co
is a GRefl coercion.
mkCoherenceRightCo :: Role -> Type -> CoercionN -> Coercion -> Coercion #
Given ty :: k1
, co :: k1 ~ k2
, co2:: ty' ~r ty
,
produces @co' :: ty' ~r (ty |> co)
It is not only a utility function, but it saves allocation when co
is a GRefl coercion.
downgradeRole :: Role -> Role -> Coercion -> Coercion #
Like downgradeRole_maybe
, but panics if the change isn't a downgrade.
See Note [Role twiddling functions]
setNominalRole_maybe :: Role -> Coercion -> Maybe CoercionN #
Converts a coercion to be nominal, if possible. See Note [Role twiddling functions]
tyConRoleListX :: Role -> TyCon -> [Role] #
tyConRoleListRepresentational :: TyCon -> [Role] #
promoteCoercion :: HasDebugCallStack => Coercion -> CoercionN #
like mkKindCo, but aggressively & recursively optimizes to avoid using a KindCo constructor. The output role is nominal.
castCoercionKind2 :: Coercion -> Role -> Type -> Type -> CoercionN -> CoercionN -> Coercion #
Creates a new coercion with both of its types casted by different casts
castCoercionKind2 g r t1 t2 h1 h2
, where g :: t1 ~r t2
,
has type (t1 |> h1) ~r (t2 |> h2)
.
h1
and h2
must be nominal.
castCoercionKind1 :: Coercion -> Role -> Type -> Type -> CoercionN -> Coercion #
castCoercionKind1 g r t1 t2 h
= coercionKind g r t1 t2 h h
That is, it's a specialised form of castCoercionKind, where the two
kind coercions are identical
castCoercionKind1 g r t1 t2 h
, where g :: t1 ~r t2
,
has type (t1 |> h) ~r (t2 |> h)
.
h
must be nominal.
See Note [castCoercionKind1]
castCoercionKind :: Coercion -> CoercionN -> CoercionN -> Coercion #
Creates a new coercion with both of its types casted by different casts
castCoercionKind g h1 h2
, where g :: t1 ~r t2
,
has type (t1 |> h1) ~r (t2 |> h2)
.
h1
and h2
must be nominal.
It calls coercionKindRole
, so it's quite inefficient (which I
stands for)
Use castCoercionKind2
instead if t1
, t2
, and r
are known beforehand.
mkPiCo :: Role -> Var -> Coercion -> Coercion #
Make a forall Coercion
, where both types related by the coercion
are quantified over the same variable.
instNewTyCon_maybe :: TyCon -> [Type] -> Maybe (Type, Coercion) #
If `instNewTyCon_maybe T ts = Just (rep_ty, co)` then `co :: T ts ~R# rep_ty`
Checks for a newtype, and for being saturated
composeSteppers :: NormaliseStepper ev -> NormaliseStepper ev -> NormaliseStepper ev #
Try one stepper and then try the next, if the first doesn't make progress. So if it returns NS_Done, it means that both steppers are satisfied
unwrapNewTypeStepper :: NormaliseStepper Coercion #
A NormaliseStepper
that unwraps newtypes, careful not to fall into
a loop. If it would fall into a loop, it produces NS_Abort
.
topNormaliseTypeX :: NormaliseStepper ev -> (ev -> ev -> ev) -> Type -> Maybe (ev, Type) #
A general function for normalising the top-level of a type. It continues
to use the provided NormaliseStepper
until that function fails, and then
this function returns. The roles of the coercions produced by the
NormaliseStepper
must all be the same, which is the role returned from
the call to topNormaliseTypeX
.
Typically ev is Coercion.
If topNormaliseTypeX step plus ty = Just (ev, ty')
then ty ~ev1~ t1 ~ev2~ t2 ... ~evn~ ty'
and ev = ev1 plus
ev2 plus
... plus
evn
If it returns Nothing then no newtype unwrapping could happen
eqCoercion :: Coercion -> Coercion -> Bool #
Syntactic equality of coercions
eqCoercionX :: RnEnv2 -> Coercion -> Coercion -> Bool #
Compare two Coercion
s, with respect to an RnEnv2
liftCoSubstWithEx :: Role -> [TyVar] -> [Coercion] -> [TyCoVar] -> [Type] -> (Type -> Coercion, [Type]) #
liftCoSubst :: HasDebugCallStack => Role -> LiftingContext -> Type -> Coercion #
liftCoSubst role lc ty
produces a coercion (at role role
)
that coerces between lc_left(ty)
and lc_right(ty)
, where
lc_left
is a substitution mapping type variables to the left-hand
types of the mapped coercions in lc
, and similar for lc_right
.
:: LiftingContext | original LC |
-> TyCoVar | new variable to map... |
-> Coercion | ...to this lifted version |
-> LiftingContext |
Extend a lifting context with a new mapping.
extendLiftingContextCvSubst :: LiftingContext -> CoVar -> Coercion -> LiftingContext #
Extend the substitution component of a lifting context with a new binding for a coercion variable. Used during coercion optimisation.
extendLiftingContextAndInScope #
:: LiftingContext | Original LC |
-> TyCoVar | new variable to map... |
-> Coercion | to this coercion |
-> LiftingContext |
Extend a lifting context with a new mapping, and extend the in-scope set
zapLiftingContext :: LiftingContext -> LiftingContext #
Erase the environments in a lifting context
substForAllCoBndrUsingLC :: Bool -> (Coercion -> Coercion) -> LiftingContext -> TyCoVar -> Coercion -> (LiftingContext, TyCoVar, Coercion) #
Like substForAllCoBndr
, but works on a lifting context
liftCoSubstTyVar :: LiftingContext -> Role -> TyVar -> Maybe Coercion #
:: (r -> CoercionN) | coercion getter |
-> (LiftingContext -> Type -> r) | callback |
-> LiftingContext | |
-> TyCoVar | |
-> (LiftingContext, TyCoVar, r) |
isMappedByLC :: TyCoVar -> LiftingContext -> Bool #
Is a var in the domain of a lifting context?
substLeftCo :: LiftingContext -> Coercion -> Coercion #
substRightCo :: LiftingContext -> Coercion -> Coercion #
swapLiftCoEnv :: LiftCoEnv -> LiftCoEnv #
Apply "sym" to all coercions in a LiftCoEnv
lcSubstLeft :: LiftingContext -> Subst #
lcSubstRight :: LiftingContext -> Subst #
liftEnvSubstLeft :: Subst -> LiftCoEnv -> Subst #
liftEnvSubstRight :: Subst -> LiftCoEnv -> Subst #
lcLookupCoVar :: LiftingContext -> CoVar -> Maybe Coercion #
Lookup a CoVar
in the substitution in a LiftingContext
lcInScopeSet :: LiftingContext -> InScopeSet #
Get the InScopeSet
from a LiftingContext
coercionKinds :: [Coercion] -> Pair [Type] #
Apply coercionKind
to multiple Coercion
s
getNthFromType :: HasDebugCallStack => CoSel -> Type -> Type #
coercionRole :: Coercion -> Role #
Retrieve the role from a coercion.
mkPrimEqPred :: Type -> Type -> Type #
Creates a primitive nominal type equality predicate. t1 ~# t2 Invariant: the types are not Coercions
mkReprPrimEqPred :: Type -> Type -> Type #
Creates a primitive representational type equality predicate. t1 ~R# t2 Invariant: the types are not Coercions
mkPrimEqPredRole :: Role -> Type -> Type -> PredType #
Makes a lifted equality predicate at the given role
mkNomPrimEqPred :: Kind -> Type -> Type -> Type #
Creates a primitive nominal type equality predicate with an explicit (but homogeneous) kind: (~#) k k ty1 ty2
buildCoercion :: Type -> Type -> CoercionN #
Assuming that two types are the same, ignoring coercions, find a nominal coercion between the types. This is useful when optimizing transitivity over coercion applications, where splitting two AppCos might yield different kinds. See Note [EtaAppCo] in GHC.Core.Coercion.Opt.
hasCoercionHoleTy :: Type -> Bool #
Is there a hetero-kind coercion hole in this type? (That is, a coercion hole with ch_hetero_kind=True.) See wrinkle (EIK2) of Note [Equalities with incompatible kinds] in GHC.Tc.Solver.Equality
hasCoercionHoleCo :: Coercion -> Bool #
Is there a hetero-kind coercion hole in this coercion?
hasThisCoercionHoleTy :: Type -> CoercionHole -> Bool #
setCoHoleType :: CoercionHole -> Type -> CoercionHole #
Set the type of a CoercionHole
module GHC.Builtin.Types
module GHC.Driver.Env
module GHC.Types.Basic
module GHC.Types.Var.Set
module GHC.Types.Var.Env
module GHC.Types.Name.Set
module GHC.Types.Name.Env
Unique identifier.
The type of unique identifiers that are used in many places in GHC
for fast ordering and equality tests. You should generate these with
the functions from the UniqSupply
module
These are sometimes also referred to as "keys" in comments in GHC.
Instances
Show Unique | |
Uniquable Unique | |
Defined in GHC.Types.Unique | |
Outputable Unique | |
Defined in GHC.Types.Unique | |
Eq Unique | |
Class of things that we can obtain a Unique
from
Instances
module GHC.Types.Unique.Set
module GHC.Types.Unique.FM
module GHC.Data.FiniteMap
module GHC.Utils.Misc
module GHC.Serialized
module GHC.Types.SrcLoc
module GHC.Utils.Outputable
module GHC.Utils.Panic
module GHC.Types.Unique.Supply
module GHC.Data.FastString
module GHC.Tc.Errors.Hole.FitTypes
module GHC.Tc.Errors.Hole.Plugin
module GHC.Unit.Module.ModGuts
module GHC.Unit.Module.ModSummary
module GHC.Unit.Module.ModIface
module GHC.Types.Meta
module GHC.Types.SourceError
A collection of messages emitted by GHC during error reporting. A diagnostic message is typically a warning or an error. See Note [Messages].
INVARIANT: All the messages in this collection must be relevant, i.e.
their Severity
should not be SevIgnore
. The smart constructor
mkMessages
will filter out any message which Severity
is SevIgnore
.
Instances
Foldable Messages | |
Defined in GHC.Types.Error fold :: Monoid m => Messages m -> m # foldMap :: Monoid m => (a -> m) -> Messages a -> m # foldMap' :: Monoid m => (a -> m) -> Messages a -> m # foldr :: (a -> b -> b) -> b -> Messages a -> b # foldr' :: (a -> b -> b) -> b -> Messages a -> b # foldl :: (b -> a -> b) -> b -> Messages a -> b # foldl' :: (b -> a -> b) -> b -> Messages a -> b # foldr1 :: (a -> a -> a) -> Messages a -> a # foldl1 :: (a -> a -> a) -> Messages a -> a # elem :: Eq a => a -> Messages a -> Bool # maximum :: Ord a => Messages a -> a # minimum :: Ord a => Messages a -> a # | |
Traversable Messages | |
Functor Messages | |
Monoid (Messages e) | |
Semigroup (Messages e) | |
Diagnostic e => ToJson (Messages e) | |
Defined in GHC.Types.Error | |
Diagnostic e => Outputable (Messages e) | |
Defined in GHC.Types.Error |
data HsParsedModule #
Getting Name
s
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.
thNameToGhcNameIO :: NameCache -> Name -> IO (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.
One must be careful to consistently use the same NameCache
to
create identifier that might be compared. (C.f. how the
ST
Monad enforces that variables from separate
runST
invocations are never intermingled; it would
be valid to use the same tricks for Name
s and NameCache
s.)
For now, the easiest and recommended way to ensure a consistent
NameCache
is used it to retrieve the preexisting one from an active
HscEnv
. A single HscEnv
is created per GHC "session", and this
ensures everything in that session will get the same name cache.