| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Language.Haskell.Liquid.GHC.API
Description
This module re-exports a bunch of the GHC API.
Synopsis
- parser :: String -> DynFlags -> FilePath -> (WarningMessages, Either ErrorMessages (Located (HsModule GhcPs)))
- lookupName :: GhcMonad m => Name -> m (Maybe TyThing)
- obtainTermFromId :: GhcMonad m => Int -> Bool -> Id -> m Term
- obtainTermFromVal :: GhcMonad m => Int -> Bool -> Type -> a -> m Term
- getHistorySpan :: GhcMonad m => History -> m SrcSpan
- getGHCiMonad :: GhcMonad m => m Name
- setGHCiMonad :: GhcMonad m => String -> m ()
- moduleTrustReqs :: GhcMonad m => Module -> m (Bool, Set InstalledUnitId)
- isModuleTrusted :: GhcMonad m => Module -> m Bool
- lookupModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module
- findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module
- showRichTokenStream :: [(Located Token, String)] -> String
- addSourceToTokens :: RealSrcLoc -> StringBuffer -> [Located Token] -> [(Located Token, String)]
- getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)]
- getTokenStream :: GhcMonad m => Module -> m [Located Token]
- pprParenSymName :: NamedThing a => a -> SDoc
- dataConType :: DataCon -> Type
- getNameToInstancesIndex :: GhcMonad m => [Module] -> Maybe [Module] -> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
- getGRE :: GhcMonad m => m GlobalRdrEnv
- findGlobalAnns :: (GhcMonad m, Typeable a) => ([Word8] -> a) -> AnnTarget Name -> m [a]
- lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing)
- isDictonaryId :: Id -> Bool
- modInfoModBreaks :: ModuleInfo -> ModBreaks
- modInfoSafe :: ModuleInfo -> SafeHaskellMode
- modInfoRdrEnv :: ModuleInfo -> Maybe GlobalRdrEnv
- modInfoIface :: ModuleInfo -> Maybe ModIface
- modInfoLookupName :: GhcMonad m => ModuleInfo -> Name -> m (Maybe TyThing)
- mkPrintUnqualifiedForModule :: GhcMonad m => ModuleInfo -> m (Maybe PrintUnqualified)
- modInfoIsExportedName :: ModuleInfo -> Name -> Bool
- modInfoInstances :: ModuleInfo -> [ClsInst]
- modInfoExportsWithSelectors :: ModuleInfo -> [Name]
- modInfoExports :: ModuleInfo -> [Name]
- modInfoTopLevelScope :: ModuleInfo -> Maybe [Name]
- modInfoTyThings :: ModuleInfo -> [TyThing]
- getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo)
- getPrintUnqual :: GhcMonad m => m PrintUnqualified
- getInsts :: GhcMonad m => m ([ClsInst], [FamInst])
- getBindings :: GhcMonad m => m [TyThing]
- isLoaded :: GhcMonad m => ModuleName -> m Bool
- getModuleGraph :: GhcMonad m => m ModuleGraph
- compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule
- compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule
- loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod
- desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule
- typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule
- parseModule :: GhcMonad m => ModSummary -> m ParsedModule
- getModSummary :: GhcMonad m => ModuleName -> m ModSummary
- workingDirectoryChanged :: GhcMonad m => m ()
- guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target
- removeTarget :: GhcMonad m => TargetId -> m ()
- addTarget :: GhcMonad m => Target -> m ()
- getTargets :: GhcMonad m => m [Target]
- setTargets :: GhcMonad m => [Target] -> m ()
- parseDynamicFlags :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- getInteractiveDynFlags :: GhcMonad m => m DynFlags
- setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
- getProgramDynFlags :: GhcMonad m => m DynFlags
- setLogAction :: GhcMonad m => LogAction -> m ()
- setProgramDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId]
- setSessionDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId]
- initGhcMonad :: GhcMonad m => Maybe FilePath -> m ()
- withCleanupSession :: GhcMonad m => m a -> m a
- runGhcT :: ExceptionMonad m => Maybe FilePath -> GhcT m a -> m a
- runGhc :: Maybe FilePath -> Ghc a -> IO a
- defaultCleanupHandler :: ExceptionMonad m => DynFlags -> m a -> m a
- defaultErrorHandler :: ExceptionMonad m => FatalMessager -> FlushOut -> m a -> m a
- class ParsedMod m where
- parsedSource :: m -> ParsedSource
- class ParsedMod m => TypecheckedMod m where
- renamedSource :: m -> Maybe RenamedSource
- typecheckedSource :: m -> TypecheckedSource
- moduleInfo :: m -> ModuleInfo
- data ParsedModule = ParsedModule {}
- data TypecheckedModule = TypecheckedModule {}
- data DesugaredModule = DesugaredModule {}
- type ParsedSource = Located (HsModule GhcPs)
- type RenamedSource = (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString)
- type TypecheckedSource = LHsBinds GhcTc
- data CoreModule = CoreModule {
- cm_module :: !Module
- cm_types :: !TypeEnv
- cm_binds :: CoreProgram
- cm_safe :: SafeHaskellMode
- data ModuleInfo
- cyclicModuleErr :: [ModSummary] -> SDoc
- topSortModuleGraph :: Bool -> ModuleGraph -> Maybe ModuleName -> [SCC ModSummary]
- load :: GhcMonad m => LoadHowMuch -> m SuccessFlag
- depanal :: GhcMonad m => [ModuleName] -> Bool -> m ModuleGraph
- data LoadHowMuch
- reconstructType :: HscEnv -> Int -> Id -> IO (Maybe Type)
- moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool
- showModule :: GhcMonad m => ModSummary -> m String
- dynCompileExpr :: GhcMonad m => String -> m Dynamic
- compileParsedExpr :: GhcMonad m => LHsExpr GhcPs -> m HValue
- compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue
- compileExprRemote :: GhcMonad m => String -> m ForeignHValue
- compileExpr :: GhcMonad m => String -> m HValue
- parseExpr :: GhcMonad m => String -> m (LHsExpr GhcPs)
- parseInstanceHead :: GhcMonad m => String -> m Type
- getInstancesForType :: GhcMonad m => Type -> m [ClsInst]
- typeKind :: GhcMonad m => Bool -> String -> m (Type, Kind)
- exprType :: GhcMonad m => TcRnExprMode -> String -> m Type
- getDocs :: GhcMonad m => Name -> m (Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString))
- isDecl :: DynFlags -> String -> Bool
- isImport :: DynFlags -> String -> Bool
- hasImport :: DynFlags -> String -> Bool
- isStmt :: DynFlags -> String -> Bool
- parseName :: GhcMonad m => String -> m [Name]
- getRdrNamesInScope :: GhcMonad m => m [RdrName]
- getNamesInScope :: GhcMonad m => m [Name]
- getInfo :: GhcMonad m => Bool -> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
- moduleIsInterpreted :: GhcMonad m => Module -> m Bool
- getContext :: GhcMonad m => m [InteractiveImport]
- setContext :: GhcMonad m => [InteractiveImport] -> m ()
- abandonAll :: GhcMonad m => m Bool
- abandon :: GhcMonad m => m Bool
- forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- resumeExec :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> m ExecResult
- parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs)
- runParsedDecls :: GhcMonad m => [LHsDecl GhcPs] -> m [Name]
- runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name]
- runDecls :: GhcMonad m => String -> m [Name]
- execStmt' :: GhcMonad m => GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult
- execStmt :: GhcMonad m => String -> ExecOptions -> m ExecResult
- execOptions :: ExecOptions
- getHistoryModule :: History -> Module
- getResumeContext :: GhcMonad m => m [Resume]
- data GetDocsFailure
- showModuleIndex :: (Int, Int) -> String
- dumpIfaceStats :: HscEnv -> IO ()
- hscCompileCoreExpr' :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
- hscCompileCoreExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
- hscParseIdentifier :: HscEnv -> String -> IO (Located RdrName)
- hscParseType :: String -> Hsc (LHsType GhcPs)
- hscParseStmtWithLocation :: String -> Int -> String -> Hsc (Maybe (GhciLStmt GhcPs))
- hscParseExpr :: String -> Hsc (LHsExpr GhcPs)
- hscKcType :: HscEnv -> Bool -> String -> IO (Type, Kind)
- hscTcExpr :: HscEnv -> TcRnExprMode -> String -> IO Type
- hscImport :: HscEnv -> String -> IO (ImportDecl GhcPs)
- hscAddSptEntries :: HscEnv -> [SptEntry] -> IO ()
- hscParsedDecls :: HscEnv -> [LHsDecl GhcPs] -> IO ([TyThing], InteractiveContext)
- hscDeclsWithLocation :: HscEnv -> String -> String -> Int -> IO ([TyThing], InteractiveContext)
- hscParseDeclsWithLocation :: HscEnv -> String -> Int -> String -> IO [LHsDecl GhcPs]
- hscDecls :: HscEnv -> String -> IO ([TyThing], InteractiveContext)
- hscParsedStmt :: HscEnv -> GhciLStmt GhcPs -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
- hscStmtWithLocation :: HscEnv -> String -> String -> Int -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
- hscStmt :: HscEnv -> String -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
- hscCompileCmmFile :: HscEnv -> FilePath -> FilePath -> IO ()
- hscInteractive :: HscEnv -> CgGuts -> ModLocation -> IO (Maybe FilePath, CompiledByteCode, [SptEntry])
- hscGenHardCode :: HscEnv -> CgGuts -> ModLocation -> FilePath -> IO (FilePath, Maybe FilePath, [(ForeignSrcLang, FilePath)])
- hscSimpleIface' :: TcGblEnv -> Maybe Fingerprint -> Hsc (ModIface, Maybe Fingerprint, ModDetails)
- hscSimplify' :: [String] -> ModGuts -> Hsc ModGuts
- hscSimplify :: HscEnv -> [String] -> ModGuts -> IO ModGuts
- hscGetSafe :: HscEnv -> Module -> SrcSpan -> IO (Bool, Set InstalledUnitId)
- hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO Bool
- hscFileFrontEnd :: ModSummary -> Hsc TcGblEnv
- batchMsg :: Messager
- oneShotMsg :: HscEnv -> RecompileRequired -> IO ()
- hscMaybeWriteIface :: DynFlags -> ModIface -> Maybe Fingerprint -> ModLocation -> IO ()
- hscIncrementalCompile :: Bool -> Maybe TcGblEnv -> Maybe Messager -> HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> (Int, Int) -> IO (HscStatus, ModDetails, DynFlags)
- genericHscFrontend :: ModSummary -> Hsc FrontendResult
- makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails
- hscDesugar' :: ModLocation -> TcGblEnv -> Hsc ModGuts
- hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts
- tcRnModule' :: ModSummary -> Bool -> HsParsedModule -> Hsc TcGblEnv
- hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff)
- hscParse' :: ModSummary -> Hsc HsParsedModule
- hscParse :: HscEnv -> ModSummary -> IO HsParsedModule
- hscRnImportDecls :: HscEnv -> [LImportDecl GhcPs] -> IO GlobalRdrEnv
- hscGetModuleInterface :: HscEnv -> Module -> IO ModIface
- hscIsGHCiMonad :: HscEnv -> String -> IO Name
- hscTcRnGetInfo :: HscEnv -> Name -> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
- hscTcRcLookupName :: HscEnv -> Name -> IO (Maybe TyThing)
- hscTcRnLookupRdrName :: HscEnv -> Located RdrName -> IO [Name]
- ioMsgMaybe :: IO (Messages, Maybe a) -> Hsc a
- getHscEnv :: Hsc HscEnv
- newHscEnv :: DynFlags -> IO HscEnv
- type Messager = HscEnv -> (Int, Int) -> RecompileRequired -> ModSummary -> IO ()
- runTcInteractive :: HscEnv -> TcRn a -> IO (Messages, Maybe a)
- data TcRnExprMode
- pprFamInst :: FamInst -> SDoc
- defaultWarnErrLogger :: WarnErrLogger
- printException :: GhcMonad m => SourceError -> m ()
- getSessionDynFlags :: GhcMonad m => m DynFlags
- class (Functor m, MonadIO m, ExceptionMonad m, HasDynFlags m) => GhcMonad (m :: Type -> Type) where
- getSession :: m HscEnv
- setSession :: HscEnv -> m ()
- data Ghc a
- data GhcT (m :: Type -> Type) a
- type WarnErrLogger = forall (m :: Type -> Type). GhcMonad m => Maybe SourceError -> m ()
- phaseForeignLanguage :: Phase -> Maybe ForeignSrcLang
- extendCompleteMatchMap :: CompleteMatchMap -> [CompleteMatch] -> CompleteMatchMap
- mkCompleteMatchMap :: [CompleteMatch] -> CompleteMatchMap
- byteCodeOfObject :: Unlinked -> CompiledByteCode
- nameOfObject :: Unlinked -> FilePath
- isInterpretable :: Unlinked -> Bool
- isObject :: Unlinked -> Bool
- linkableObjs :: Linkable -> [FilePath]
- isObjectLinkable :: Linkable -> Bool
- numToTrustInfo :: Word8 -> IfaceTrustInfo
- trustInfoToNum :: IfaceTrustInfo -> Word8
- noIfaceTrustInfo :: IfaceTrustInfo
- setSafeMode :: SafeHaskellMode -> IfaceTrustInfo
- getSafeMode :: IfaceTrustInfo -> SafeHaskellMode
- isHpcUsed :: HpcInfo -> AnyHpcUsage
- emptyHpcInfo :: AnyHpcUsage -> HpcInfo
- showModMsg :: DynFlags -> HscTarget -> Bool -> ModSummary -> String
- isBootSummary :: ModSummary -> Bool
- msObjFilePath :: ModSummary -> FilePath
- msHiFilePath :: ModSummary -> FilePath
- msHsFilePath :: ModSummary -> FilePath
- ms_home_imps :: ModSummary -> [Located ModuleName]
- ms_home_srcimps :: ModSummary -> [Located ModuleName]
- ms_home_allimps :: ModSummary -> [ModuleName]
- home_imps :: [(Maybe FastString, Located ModuleName)] -> [Located ModuleName]
- ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
- ms_mod_name :: ModSummary -> ModuleName
- ms_installed_mod :: ModSummary -> InstalledModule
- mkModuleGraph :: [ModSummary] -> ModuleGraph
- extendMG :: ModuleGraph -> ModSummary -> ModuleGraph
- isTemplateHaskellOrQQNonBoot :: ModSummary -> Bool
- emptyMG :: ModuleGraph
- mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
- mgElemModule :: ModuleGraph -> Module -> Bool
- mgModSummaries :: ModuleGraph -> [ModSummary]
- mgBootModules :: ModuleGraph -> ModuleSet
- mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
- needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
- soExt :: Platform -> FilePath
- mkHsSOName :: Platform -> FilePath -> FilePath
- mkSOName :: Platform -> FilePath -> FilePath
- updNameCache :: IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
- addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
- noDependencies :: Dependencies
- lookupFixity :: FixityEnv -> Name -> Fixity
- emptyFixityEnv :: FixityEnv
- mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Maybe Fixity
- plusWarns :: Warnings -> Warnings -> Warnings
- emptyIfaceWarnCache :: OccName -> Maybe WarningTxt
- mkIfaceWarnCache :: Warnings -> OccName -> Maybe WarningTxt
- tyThingId :: TyThing -> Id
- tyThingConLike :: TyThing -> ConLike
- tyThingDataCon :: TyThing -> DataCon
- tyThingCoAxiom :: TyThing -> CoAxiom Branched
- tyThingTyCon :: TyThing -> TyCon
- lookupTypeHscEnv :: HscEnv -> Name -> IO (Maybe TyThing)
- lookupType :: DynFlags -> HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing
- plusTypeEnv :: TypeEnv -> TypeEnv -> TypeEnv
- extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
- extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
- extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
- lookupTypeEnv :: TypeEnv -> Name -> Maybe TyThing
- typeEnvFromEntities :: [Id] -> [TyCon] -> [FamInst] -> TypeEnv
- mkTypeEnvWithImplicits :: [TyThing] -> TypeEnv
- mkTypeEnv :: [TyThing] -> TypeEnv
- typeEnvClasses :: TypeEnv -> [Class]
- typeEnvDataCons :: TypeEnv -> [DataCon]
- typeEnvPatSyns :: TypeEnv -> [PatSyn]
- typeEnvIds :: TypeEnv -> [Id]
- typeEnvCoAxioms :: TypeEnv -> [CoAxiom Branched]
- typeEnvTyCons :: TypeEnv -> [TyCon]
- typeEnvElts :: TypeEnv -> [TyThing]
- emptyTypeEnv :: TypeEnv
- tyThingAvailInfo :: TyThing -> [AvailInfo]
- tyThingsTyCoVars :: [TyThing] -> TyCoVarSet
- tyThingParent_maybe :: TyThing -> Maybe TyThing
- isImplicitTyThing :: TyThing -> Bool
- implicitTyConThings :: TyCon -> [TyThing]
- implicitClassThings :: Class -> [TyThing]
- implicitTyThings :: TyThing -> [TyThing]
- pkgQual :: DynFlags -> PrintUnqualified
- mkQualPackage :: DynFlags -> QueryQualifyPackage
- mkQualModule :: DynFlags -> QueryQualifyModule
- mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
- substInteractiveContext :: InteractiveContext -> TCvSubst -> InteractiveContext
- icExtendGblRdrEnv :: GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv
- setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
- setInteractivePackage :: HscEnv -> HscEnv
- extendInteractiveContextWithIds :: InteractiveContext -> [Id] -> InteractiveContext
- extendInteractiveContext :: InteractiveContext -> [TyThing] -> [ClsInst] -> [FamInst] -> Maybe [Type] -> FixityEnv -> InteractiveContext
- icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
- icInScopeTTs :: InteractiveContext -> [TyThing]
- icInteractiveModule :: InteractiveContext -> Module
- emptyInteractiveContext :: DynFlags -> InteractiveContext
- appendStubC :: ForeignStubs -> SDoc -> ForeignStubs
- importedByUser :: [ImportedBy] -> [ImportedModsVal]
- emptyModDetails :: ModDetails
- mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> OccName -> Maybe (OccName, Fingerprint)
- emptyFullModIface :: Module -> ModIface
- emptyPartialModIface :: Module -> PartialModIface
- renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName
- mi_free_holes :: ModIface -> UniqDSet ModuleName
- mi_semantic_module :: forall (a :: ModIfacePhase). ModIface_ a -> Module
- mi_fix :: ModIface -> OccName -> Fixity
- mi_boot :: ModIface -> Bool
- prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
- metaRequestAW :: Functor f => MetaHook f -> LHsExpr GhcTc -> f Serialized
- metaRequestD :: Functor f => MetaHook f -> LHsExpr GhcTc -> f [LHsDecl GhcPs]
- metaRequestT :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsType GhcPs)
- metaRequestP :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LPat GhcPs)
- metaRequestE :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsExpr GhcPs)
- hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
- hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst])
- hptCompleteSigs :: HscEnv -> [CompleteMatch]
- lookupIfaceByModule :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
- lookupHptByModule :: HomePackageTable -> Module -> Maybe HomeModInfo
- listToHpt :: [(ModuleName, HomeModInfo)] -> HomePackageTable
- addListToHpt :: HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable
- addToHpt :: HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable
- delFromHpt :: HomePackageTable -> ModuleName -> HomePackageTable
- mapHpt :: (HomeModInfo -> HomeModInfo) -> HomePackageTable -> HomePackageTable
- allHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> Bool
- filterHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> HomePackageTable
- eltsHpt :: HomePackageTable -> [HomeModInfo]
- lookupHptDirectly :: HomePackageTable -> Unique -> Maybe HomeModInfo
- lookupHpt :: HomePackageTable -> ModuleName -> Maybe HomeModInfo
- pprHPT :: HomePackageTable -> SDoc
- emptyPackageIfaceTable :: PackageIfaceTable
- emptyHomePackageTable :: HomePackageTable
- pprTargetId :: TargetId -> SDoc
- pprTarget :: Target -> SDoc
- hscEPS :: HscEnv -> IO ExternalPackageState
- handleFlagWarnings :: DynFlags -> [Warn] -> IO ()
- printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO ()
- handleSourceError :: ExceptionMonad m => (SourceError -> m a) -> m a -> m a
- throwOneError :: MonadIO io => ErrMsg -> io a
- throwErrors :: MonadIO io => ErrorMessages -> io a
- mkApiErr :: DynFlags -> SDoc -> GhcApiError
- srcErrorMessages :: SourceError -> ErrorMessages
- mkSrcErr :: ErrorMessages -> SourceError
- runInteractiveHsc :: HscEnv -> Hsc a -> IO a
- mkInteractiveHscEnv :: HscEnv -> HscEnv
- runHsc :: HscEnv -> Hsc a -> IO a
- data HscStatus
- newtype Hsc a = Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages))
- data SourceError
- data GhcApiError
- data HscEnv = HscEnv {
- hsc_dflags :: DynFlags
- hsc_targets :: [Target]
- hsc_mod_graph :: ModuleGraph
- hsc_IC :: InteractiveContext
- hsc_HPT :: HomePackageTable
- hsc_EPS :: !(IORef ExternalPackageState)
- hsc_NC :: !(IORef NameCache)
- hsc_FC :: !(IORef FinderCache)
- hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
- hsc_iserv :: MVar (Maybe IServ)
- hsc_dynLinker :: DynLinker
- data IServ = IServ {
- iservPipe :: Pipe
- iservProcess :: ProcessHandle
- iservLookupSymbolCache :: IORef (UniqFM (Ptr ()))
- iservPendingFrees :: [HValueRef]
- data Target = Target {}
- data TargetId
- type InputFileBuffer = StringBuffer
- type HomePackageTable = DModuleNameEnv HomeModInfo
- type PackageIfaceTable = ModuleEnv ModIface
- data HomeModInfo = HomeModInfo {
- hm_iface :: !ModIface
- hm_details :: !ModDetails
- hm_linkable :: !(Maybe Linkable)
- data MetaRequest
- = MetaE (LHsExpr GhcPs -> MetaResult)
- | MetaP (LPat GhcPs -> MetaResult)
- | MetaT (LHsType GhcPs -> MetaResult)
- | MetaD ([LHsDecl GhcPs] -> MetaResult)
- | MetaAW (Serialized -> MetaResult)
- data MetaResult
- type MetaHook (f :: Type -> Type) = MetaRequest -> LHsExpr GhcTc -> f MetaResult
- type FinderCache = InstalledModuleEnv InstalledFindResult
- data InstalledFindResult
- data FindResult
- = Found ModLocation Module
- | NoPackage UnitId
- | FoundMultiple [(Module, ModuleOrigin)]
- | NotFound {
- fr_paths :: [FilePath]
- fr_pkg :: Maybe UnitId
- fr_mods_hidden :: [UnitId]
- fr_pkgs_hidden :: [UnitId]
- fr_unusables :: [(UnitId, UnusablePackageReason)]
- fr_suggestions :: [ModuleSuggestion]
- type PartialModIface = ModIface_ 'ModIfaceCore
- type ModIface = ModIface_ 'ModIfaceFinal
- data ModIfaceBackend = ModIfaceBackend {
- mi_iface_hash :: !Fingerprint
- mi_mod_hash :: !Fingerprint
- mi_flag_hash :: !Fingerprint
- mi_opt_hash :: !Fingerprint
- mi_hpc_hash :: !Fingerprint
- mi_plugin_hash :: !Fingerprint
- mi_orphan :: !WhetherHasOrphans
- mi_finsts :: !WhetherHasFamInst
- mi_exp_hash :: !Fingerprint
- mi_orphan_hash :: !Fingerprint
- mi_warn_fn :: !(OccName -> Maybe WarningTxt)
- mi_fix_fn :: !(OccName -> Maybe Fixity)
- mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
- data ModIface_ (phase :: ModIfacePhase) = ModIface {
- mi_module :: !Module
- mi_sig_of :: !(Maybe Module)
- mi_hsc_src :: !HscSource
- mi_deps :: Dependencies
- mi_usages :: [Usage]
- mi_exports :: ![IfaceExport]
- mi_used_th :: !Bool
- mi_fixities :: [(OccName, Fixity)]
- mi_warns :: Warnings
- mi_anns :: [IfaceAnnotation]
- mi_decls :: [IfaceDeclExts phase]
- mi_globals :: !(Maybe GlobalRdrEnv)
- mi_insts :: [IfaceClsInst]
- mi_fam_insts :: [IfaceFamInst]
- mi_rules :: [IfaceRule]
- mi_hpc :: !AnyHpcUsage
- mi_trust :: !IfaceTrustInfo
- mi_trust_pkg :: !Bool
- mi_complete_sigs :: [IfaceCompleteMatch]
- mi_doc_hdr :: Maybe HsDocString
- mi_decl_docs :: DeclDocMap
- mi_arg_docs :: ArgDocMap
- mi_final_exts :: !(IfaceBackendExts phase)
- type IfaceExport = AvailInfo
- data ModDetails = ModDetails {
- md_exports :: [AvailInfo]
- md_types :: !TypeEnv
- md_insts :: ![ClsInst]
- md_fam_insts :: ![FamInst]
- md_rules :: ![CoreRule]
- md_anns :: ![Annotation]
- md_complete_sigs :: [CompleteMatch]
- type ImportedMods = ModuleEnv [ImportedBy]
- data ImportedBy
- data ImportedModsVal = ImportedModsVal {}
- data ModGuts = ModGuts {
- mg_module :: !Module
- mg_hsc_src :: HscSource
- mg_loc :: SrcSpan
- mg_exports :: ![AvailInfo]
- mg_deps :: !Dependencies
- mg_usages :: ![Usage]
- mg_used_th :: !Bool
- mg_rdr_env :: !GlobalRdrEnv
- mg_fix_env :: !FixityEnv
- mg_tcs :: ![TyCon]
- mg_insts :: ![ClsInst]
- mg_fam_insts :: ![FamInst]
- mg_patsyns :: ![PatSyn]
- mg_rules :: ![CoreRule]
- mg_binds :: !CoreProgram
- mg_foreign :: !ForeignStubs
- mg_foreign_files :: ![(ForeignSrcLang, FilePath)]
- mg_warns :: !Warnings
- mg_anns :: [Annotation]
- mg_complete_sigs :: [CompleteMatch]
- mg_hpc_info :: !HpcInfo
- mg_modBreaks :: !(Maybe ModBreaks)
- mg_inst_env :: InstEnv
- mg_fam_inst_env :: FamInstEnv
- mg_safe_haskell :: SafeHaskellMode
- mg_trust_pkg :: Bool
- mg_doc_hdr :: !(Maybe HsDocString)
- mg_decl_docs :: !DeclDocMap
- mg_arg_docs :: !ArgDocMap
- data CgGuts = CgGuts {
- cg_module :: !Module
- cg_tycons :: [TyCon]
- cg_binds :: CoreProgram
- cg_foreign :: !ForeignStubs
- cg_foreign_files :: ![(ForeignSrcLang, FilePath)]
- cg_dep_pkgs :: ![InstalledUnitId]
- cg_hpc_info :: !HpcInfo
- cg_modBreaks :: !(Maybe ModBreaks)
- cg_spt_entries :: [SptEntry]
- data ForeignStubs
- data InteractiveContext = InteractiveContext {
- ic_dflags :: DynFlags
- ic_mod_index :: Int
- ic_imports :: [InteractiveImport]
- ic_tythings :: [TyThing]
- ic_rn_gbl_env :: GlobalRdrEnv
- ic_instances :: ([ClsInst], [FamInst])
- ic_fix_env :: FixityEnv
- ic_default :: Maybe [Type]
- ic_resume :: [Resume]
- ic_monad :: Name
- ic_int_print :: Name
- ic_cwd :: Maybe FilePath
- data InteractiveImport
- type TypeEnv = NameEnv TyThing
- class Monad m => MonadThings (m :: Type -> Type) where
- lookupThing :: Name -> m TyThing
- lookupId :: Name -> m Id
- lookupDataCon :: Name -> m DataCon
- lookupTyCon :: Name -> m TyCon
- data Warnings
- = NoWarnings
- | WarnAll WarningTxt
- | WarnSome [(OccName, WarningTxt)]
- type FixityEnv = NameEnv FixItem
- data FixItem = FixItem OccName Fixity
- type WhetherHasOrphans = Bool
- type IsBootInterface = Bool
- data Dependencies = Deps {
- dep_mods :: [(ModuleName, IsBootInterface)]
- dep_pkgs :: [(InstalledUnitId, Bool)]
- dep_orphs :: [Module]
- dep_finsts :: [Module]
- dep_plgins :: [ModuleName]
- data Usage
- = UsagePackageModule { }
- | UsageHomeModule { }
- | UsageFile { }
- | UsageMergedRequirement { }
- type PackageTypeEnv = TypeEnv
- type PackageRuleBase = RuleBase
- type PackageInstEnv = InstEnv
- type PackageFamInstEnv = FamInstEnv
- type PackageCompleteMatchMap = CompleteMatchMap
- data ExternalPackageState = EPS {
- eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface))
- eps_PIT :: !PackageIfaceTable
- eps_free_holes :: InstalledModuleEnv (UniqDSet ModuleName)
- eps_PTE :: !PackageTypeEnv
- eps_inst_env :: !PackageInstEnv
- eps_fam_inst_env :: !PackageFamInstEnv
- eps_rule_base :: !PackageRuleBase
- eps_ann_env :: !PackageAnnEnv
- eps_complete_matches :: !PackageCompleteMatchMap
- eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv)
- eps_stats :: !EpsStats
- data EpsStats = EpsStats {
- n_ifaces_in :: !Int
- n_decls_in :: !Int
- n_decls_out :: !Int
- n_rules_in :: !Int
- n_rules_out :: !Int
- n_insts_in :: !Int
- n_insts_out :: !Int
- data ModuleGraph
- data ModSummary = ModSummary {
- ms_mod :: Module
- ms_hsc_src :: HscSource
- ms_location :: ModLocation
- ms_hs_date :: UTCTime
- ms_obj_date :: Maybe UTCTime
- ms_iface_date :: Maybe UTCTime
- ms_hie_date :: Maybe UTCTime
- ms_srcimps :: [(Maybe FastString, Located ModuleName)]
- ms_textual_imps :: [(Maybe FastString, Located ModuleName)]
- ms_parsed_mod :: Maybe HsParsedModule
- ms_hspp_file :: FilePath
- ms_hspp_opts :: DynFlags
- ms_hspp_buf :: Maybe StringBuffer
- data SourceModified
- data HpcInfo
- type AnyHpcUsage = Bool
- type IsSafeImport = Bool
- data IfaceTrustInfo
- data HsParsedModule = HsParsedModule {}
- data CompleteMatch = CompleteMatch {}
- type CompleteMatchMap = UniqFM [CompleteMatch]
- data HsModule pass = HsModule {
- hsmodName :: Maybe (Located ModuleName)
- hsmodExports :: Maybe (Located [LIE pass])
- hsmodImports :: [LImportDecl pass]
- hsmodDecls :: [LHsDecl pass]
- hsmodDeprecMessage :: Maybe (Located WarningTxt)
- hsmodHaddockModHeader :: Maybe LHsDocString
- lPatImplicits :: LPat GhcRn -> [(SrcSpan, [Name])]
- hsValBindsImplicits :: forall (idR :: Pass). HsValBindsLR GhcRn (GhcPass idR) -> [(SrcSpan, [Name])]
- lStmtsImplicits :: forall (idR :: Pass) body. [LStmtLR GhcRn (GhcPass idR) (Located (body (GhcPass idR)))] -> [(SrcSpan, [Name])]
- hsDataFamInstBinders :: forall (p :: Pass). DataFamInstDecl (GhcPass p) -> ([Located (IdP (GhcPass p))], [LFieldOcc (GhcPass p)])
- getPatSynBinds :: [(RecFlag, LHsBinds id)] -> [PatSynBind id id]
- hsPatSynSelectors :: forall (p :: Pass). HsValBinds (GhcPass p) -> [IdP (GhcPass p)]
- hsForeignDeclsBinders :: [LForeignDecl pass] -> [Located (IdP pass)]
- hsLTyClDeclBinders :: forall (p :: Pass). Located (TyClDecl (GhcPass p)) -> ([Located (IdP (GhcPass p))], [LFieldOcc (GhcPass p)])
- hsTyClForeignBinders :: [TyClGroup GhcRn] -> [LForeignDecl GhcRn] -> [Name]
- hsGroupBinders :: HsGroup GhcRn -> [Name]
- collectPatsBinders :: forall (p :: Pass). [LPat (GhcPass p)] -> [IdP (GhcPass p)]
- collectPatBinders :: forall (p :: Pass). LPat (GhcPass p) -> [IdP (GhcPass p)]
- collectStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. StmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)]
- collectLStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. LStmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)]
- collectStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. [StmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)]
- collectLStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. [LStmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)]
- collectMethodBinders :: LHsBindsLR idL idR -> [Located (IdP idL)]
- collectHsBindListBinders :: forall (p :: Pass) idR. [LHsBindLR (GhcPass p) idR] -> [IdP (GhcPass p)]
- collectHsBindsBinders :: forall (p :: Pass) idR. LHsBindsLR (GhcPass p) idR -> [IdP (GhcPass p)]
- collectHsBindBinders :: (SrcSpanLess (LPat p) ~ Pat p, HasSrcSpan (LPat p)) => HsBindLR p idR -> [IdP p]
- collectHsValBinders :: forall (idL :: Pass) (idR :: Pass). HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)]
- collectHsIdBinders :: forall (idL :: Pass) (idR :: Pass). HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)]
- collectLocalBinders :: forall (idL :: Pass) (idR :: Pass). HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)]
- isBangedHsBind :: HsBind GhcTc -> Bool
- isUnliftedHsBind :: HsBind GhcTc -> Bool
- mkMatch :: forall (p :: Pass). HsMatchContext (NameOrRdrName (IdP (GhcPass p))) -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> Located (HsLocalBinds (GhcPass p)) -> LMatch (GhcPass p) (LHsExpr (GhcPass p))
- mkPrefixFunRhs :: Located id -> HsMatchContext id
- mkSimpleGeneratedFunBind :: SrcSpan -> RdrName -> [LPat GhcPs] -> LHsExpr GhcPs -> LHsBind GhcPs
- isInfixFunBind :: HsBindLR id1 id2 -> Bool
- mkPatSynBind :: Located RdrName -> HsPatSynDetails (Located RdrName) -> LPat GhcPs -> HsPatSynDir GhcPs -> HsBind GhcPs
- mkVarBind :: forall (p :: Pass). IdP (GhcPass p) -> LHsExpr (GhcPass p) -> LHsBind (GhcPass p)
- mkHsVarBind :: SrcSpan -> RdrName -> LHsExpr GhcPs -> LHsBind GhcPs
- mkTopFunBind :: Origin -> Located Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn
- mkFunBind :: Origin -> Located RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> HsBind GhcPs
- mkHsDictLet :: TcEvBinds -> LHsExpr GhcTc -> LHsExpr GhcTc
- mkHsWrapPatCo :: forall (id :: Pass). TcCoercionN -> Pat (GhcPass id) -> Type -> Pat (GhcPass id)
- mkHsWrapPat :: forall (id :: Pass). HsWrapper -> Pat (GhcPass id) -> Type -> Pat (GhcPass id)
- mkLHsCmdWrap :: forall (p :: Pass). HsWrapper -> LHsCmd (GhcPass p) -> LHsCmd (GhcPass p)
- mkHsCmdWrap :: forall (p :: Pass). HsWrapper -> HsCmd (GhcPass p) -> HsCmd (GhcPass p)
- mkLHsWrapCo :: forall (id :: Pass). TcCoercionN -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- mkHsWrapCoR :: forall (id :: Pass). TcCoercionR -> HsExpr (GhcPass id) -> HsExpr (GhcPass id)
- mkHsWrapCo :: forall (id :: Pass). TcCoercionN -> HsExpr (GhcPass id) -> HsExpr (GhcPass id)
- mkHsWrap :: forall (id :: Pass). HsWrapper -> HsExpr (GhcPass id) -> HsExpr (GhcPass id)
- mkLHsWrap :: forall (id :: Pass). HsWrapper -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- typeToLHsType :: Type -> LHsType GhcPs
- mkClassOpSigs :: [LSig GhcPs] -> [LSig GhcPs]
- mkHsSigEnv :: (LSig GhcRn -> Maybe ([Located Name], a)) -> [LSig GhcRn] -> NameEnv a
- mkLHsSigWcType :: LHsType GhcPs -> LHsSigWcType GhcPs
- mkLHsSigType :: LHsType GhcPs -> LHsSigType GhcPs
- chunkify :: [a] -> [[a]]
- mkChunkified :: ([a] -> a) -> [a] -> a
- mkBigLHsPatTup :: [LPat GhcRn] -> LPat GhcRn
- mkBigLHsVarPatTup :: [IdP GhcRn] -> LPat GhcRn
- mkBigLHsTup :: forall (id :: Pass). [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id)
- mkBigLHsVarTup :: forall (id :: Pass). [IdP (GhcPass id)] -> LHsExpr (GhcPass id)
- missingTupArg :: HsTupArg GhcPs
- nlTuplePat :: [LPat GhcPs] -> Boxity -> LPat GhcPs
- mkLHsVarTuple :: forall (a :: Pass). [IdP (GhcPass a)] -> LHsExpr (GhcPass a)
- mkLHsTupleExpr :: forall (a :: Pass). [LHsExpr (GhcPass a)] -> LHsExpr (GhcPass a)
- nlHsAppKindTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsKind (GhcPass p) -> LHsType (GhcPass p)
- nlHsTyConApp :: forall (p :: Pass). IdP (GhcPass p) -> [LHsType (GhcPass p)] -> LHsType (GhcPass p)
- nlHsParTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p)
- nlHsFunTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- nlHsTyVar :: forall (p :: Pass). IdP (GhcPass p) -> LHsType (GhcPass p)
- nlHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- nlList :: [LHsExpr GhcPs] -> LHsExpr GhcPs
- nlHsCase :: LHsExpr GhcPs -> [LMatch GhcPs (LHsExpr GhcPs)] -> LHsExpr GhcPs
- nlHsIf :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- nlHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- nlHsLam :: LMatch GhcPs (LHsExpr GhcPs) -> LHsExpr GhcPs
- nlHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
- nlHsDo :: HsStmtContext Name -> [LStmt GhcPs (LHsExpr GhcPs)] -> LHsExpr GhcPs
- nlWildPatName :: LPat GhcRn
- nlWildPat :: LPat GhcPs
- nlWildConPat :: DataCon -> LPat GhcPs
- nlNullaryConPat :: forall (p :: Pass). IdP (GhcPass p) -> LPat (GhcPass p)
- nlConPatName :: Name -> [LPat GhcRn] -> LPat GhcRn
- nlConPat :: RdrName -> [LPat GhcPs] -> LPat GhcPs
- nlInfixConPat :: RdrName -> LPat GhcPs -> LPat GhcPs -> LPat GhcPs
- nlConVarPatName :: Name -> [Name] -> LPat GhcRn
- nlConVarPat :: RdrName -> [RdrName] -> LPat GhcPs
- nlHsVarApps :: forall (id :: Pass). IdP (GhcPass id) -> [IdP (GhcPass id)] -> LHsExpr (GhcPass id)
- nlHsApps :: forall (id :: Pass). IdP (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id)
- nlHsSyntaxApps :: forall (id :: Pass). SyntaxExpr (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id)
- nlHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- nlLitPat :: HsLit GhcPs -> LPat GhcPs
- nlVarPat :: forall (id :: Pass). IdP (GhcPass id) -> LPat (GhcPass id)
- nlHsIntLit :: forall (p :: Pass). Integer -> LHsExpr (GhcPass p)
- nlHsLit :: forall (p :: Pass). HsLit (GhcPass p) -> LHsExpr (GhcPass p)
- nlHsDataCon :: DataCon -> LHsExpr GhcTc
- nlHsVar :: forall (id :: Pass). IdP (GhcPass id) -> LHsExpr (GhcPass id)
- mkHsStringPrimLit :: forall (p :: Pass). FastString -> HsLit (GhcPass p)
- mkHsString :: forall (p :: Pass). String -> HsLit (GhcPass p)
- unqualQuasiQuote :: RdrName
- mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsSplice GhcPs
- mkTypedSplice :: SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs
- mkUntypedSplice :: SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs
- mkHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> HsExpr GhcPs
- mkRecStmt :: forall (idL :: Pass) bodyR. [LStmtLR (GhcPass idL) GhcPs bodyR] -> StmtLR (GhcPass idL) GhcPs bodyR
- emptyRecStmtId :: StmtLR GhcTc GhcTc bodyR
- emptyRecStmtName :: StmtLR GhcRn GhcRn bodyR
- emptyRecStmt :: forall (idL :: Pass) bodyR. StmtLR (GhcPass idL) GhcPs bodyR
- unitRecStmtTc :: RecStmtTc
- mkTcBindStmt :: LPat GhcTc -> Located (bodyR GhcTc) -> StmtLR GhcTc GhcTc (Located (bodyR GhcTc))
- mkBindStmt :: forall (idL :: Pass) (idR :: Pass) bodyR. XBindStmt (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) ~ NoExtField => LPat (GhcPass idL) -> Located (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR)))
- mkBodyStmt :: forall bodyR (idL :: Pass). Located (bodyR GhcPs) -> StmtLR (GhcPass idL) GhcPs (Located (bodyR GhcPs))
- mkLastStmt :: forall bodyR (idR :: Pass) (idL :: Pass). Located (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR)))
- mkGroupByUsingStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkGroupUsingStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkTransformByStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkTransformStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- emptyTransStmt :: StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkNPlusKPat :: Located RdrName -> Located (HsOverLit GhcPs) -> Pat GhcPs
- mkNPat :: Located (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> Pat GhcPs
- mkHsCmdIf :: forall (p :: Pass). LHsExpr (GhcPass p) -> LHsCmd (GhcPass p) -> LHsCmd (GhcPass p) -> HsCmd (GhcPass p)
- mkHsIf :: forall (p :: Pass). LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) -> HsExpr (GhcPass p)
- mkHsComp :: HsStmtContext Name -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> HsExpr GhcPs
- mkHsDo :: HsStmtContext Name -> [ExprLStmt GhcPs] -> HsExpr GhcPs
- mkHsIsString :: SourceText -> FastString -> HsOverLit GhcPs
- mkHsFractional :: FractionalLit -> HsOverLit GhcPs
- mkHsIntegral :: IntegralLit -> HsOverLit GhcPs
- nlParPat :: forall (name :: Pass). LPat (GhcPass name) -> LPat (GhcPass name)
- mkParPat :: forall (name :: Pass). LPat (GhcPass name) -> LPat (GhcPass name)
- mkLHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- nlHsTyApps :: forall (id :: Pass). IdP (GhcPass id) -> [Type] -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id)
- nlHsTyApp :: forall (id :: Pass). IdP (GhcPass id) -> [Type] -> LHsExpr (GhcPass id)
- mkHsCaseAlt :: forall (p :: Pass) body. LPat (GhcPass p) -> Located (body (GhcPass p)) -> LMatch (GhcPass p) (Located (body (GhcPass p)))
- mkHsLams :: [TyVar] -> [EvVar] -> LHsExpr GhcTc -> LHsExpr GhcTc
- mkHsLam :: forall (p :: Pass). XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ NoExtField => [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
- mkHsAppTypes :: LHsExpr GhcRn -> [LHsWcType GhcRn] -> LHsExpr GhcRn
- mkHsAppType :: forall (id :: Pass). NoGhcTc (GhcPass id) ~ GhcRn => LHsExpr (GhcPass id) -> LHsWcType GhcRn -> LHsExpr (GhcPass id)
- mkHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- mkMatchGroup :: XMG name (Located (body name)) ~ NoExtField => Origin -> [LMatch name (Located (body name))] -> MatchGroup name (Located (body name))
- unguardedRHS :: forall body (p :: Pass). SrcSpan -> Located (body (GhcPass p)) -> [LGRHS (GhcPass p) (Located (body (GhcPass p)))]
- unguardedGRHSs :: forall body (p :: Pass). Located (body (GhcPass p)) -> GRHSs (GhcPass p) (Located (body (GhcPass p)))
- mkSimpleMatch :: forall (p :: Pass) body. HsMatchContext (NameOrRdrName (IdP (GhcPass p))) -> [LPat (GhcPass p)] -> Located (body (GhcPass p)) -> LMatch (GhcPass p) (Located (body (GhcPass p)))
- mkHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- pprStmtInCtxt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => HsStmtContext (IdP (GhcPass idL)) -> StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc
- pprMatchInCtxt :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable (NameOrRdrName (NameOrRdrName (IdP (GhcPass idR)))), Outputable body) => Match (GhcPass idR) body -> SDoc
- matchContextErrString :: Outputable id => HsMatchContext id -> SDoc
- pprStmtContext :: (Outputable id, Outputable (NameOrRdrName id)) => HsStmtContext id -> SDoc
- pprAStmtContext :: (Outputable id, Outputable (NameOrRdrName id)) => HsStmtContext id -> SDoc
- pprMatchContextNoun :: (Outputable (NameOrRdrName id), Outputable id) => HsMatchContext id -> SDoc
- pprMatchContext :: (Outputable (NameOrRdrName id), Outputable id) => HsMatchContext id -> SDoc
- matchSeparator :: HsMatchContext id -> SDoc
- isMonadCompContext :: HsStmtContext id -> Bool
- isMonadFailStmtContext :: HsStmtContext id -> Bool
- isComprehensionContext :: HsStmtContext id -> Bool
- isPatSynCtxt :: HsMatchContext id -> Bool
- pp_dotdot :: SDoc
- thTyBrackets :: SDoc -> SDoc
- thBrackets :: SDoc -> SDoc -> SDoc
- pprHsBracket :: forall (p :: Pass). OutputableBndrId p => HsBracket (GhcPass p) -> SDoc
- isTypedBracket :: HsBracket id -> Bool
- ppr_splice :: forall (p :: Pass). OutputableBndrId p => SDoc -> IdP (GhcPass p) -> LHsExpr (GhcPass p) -> SDoc -> SDoc
- ppr_quasi :: OutputableBndr p => p -> p -> FastString -> SDoc
- ppr_splice_decl :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SDoc
- pprPendingSplice :: forall (p :: Pass). OutputableBndrId p => SplicePointName -> LHsExpr (GhcPass p) -> SDoc
- isTypedSplice :: HsSplice id -> Bool
- pprQuals :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body) => [LStmt (GhcPass p) body] -> SDoc
- pprComp :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body) => [LStmt (GhcPass p) body] -> SDoc
- ppr_do_stmts :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => [LStmtLR (GhcPass idL) (GhcPass idR) body] -> SDoc
- pprDo :: forall (p :: Pass) body any. (OutputableBndrId p, Outputable body) => HsStmtContext any -> [LStmt (GhcPass p) body] -> SDoc
- pprBy :: Outputable body => Maybe body -> SDoc
- pprTransStmt :: Outputable body => Maybe body -> body -> TransForm -> SDoc
- pprTransformStmt :: forall (p :: Pass). OutputableBndrId p => [IdP (GhcPass p)] -> LHsExpr (GhcPass p) -> Maybe (LHsExpr (GhcPass p)) -> SDoc
- pprArg :: forall (idL :: Pass). OutputableBndrId idL => ApplicativeArg (GhcPass idL) -> SDoc
- pprStmt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc
- pp_rhs :: Outputable body => HsMatchContext idL -> body -> SDoc
- pprGRHS :: forall (idR :: Pass) body idL. (OutputableBndrId idR, Outputable body) => HsMatchContext idL -> GRHS (GhcPass idR) body -> SDoc
- pprGRHSs :: forall (idR :: Pass) body idL. (OutputableBndrId idR, Outputable body) => HsMatchContext idL -> GRHSs (GhcPass idR) body -> SDoc
- pprMatch :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> SDoc
- pprMatches :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc
- hsLMatchPats :: forall (id :: Pass) body. LMatch (GhcPass id) body -> [LPat (GhcPass id)]
- matchGroupArity :: forall (id :: Pass) body. MatchGroup (GhcPass id) body -> Arity
- isSingletonMatchGroup :: [LMatch id body] -> Bool
- isEmptyMatchGroup :: MatchGroup id body -> Bool
- isInfixMatch :: Match id body -> Bool
- pprCmdArg :: forall (p :: Pass). OutputableBndrId p => HsCmdTop (GhcPass p) -> SDoc
- ppr_cmd :: forall (p :: Pass). OutputableBndrId p => HsCmd (GhcPass p) -> SDoc
- ppr_lcmd :: forall (p :: Pass). OutputableBndrId p => LHsCmd (GhcPass p) -> SDoc
- isQuietHsCmd :: HsCmd id -> Bool
- pprCmd :: forall (p :: Pass). OutputableBndrId p => HsCmd (GhcPass p) -> SDoc
- pprLCmd :: forall (p :: Pass). OutputableBndrId p => LHsCmd (GhcPass p) -> SDoc
- isAtomicHsExpr :: HsExpr id -> Bool
- parenthesizeHsExpr :: forall (p :: Pass). PprPrec -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
- hsExprNeedsParens :: PprPrec -> HsExpr p -> Bool
- pprParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> HsExpr (GhcPass p) -> SDoc
- pprParendLExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc
- pprDebugParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc
- pprExternalSrcLoc :: (StringLiteral, (Int, Int), (Int, Int)) -> SDoc
- ppr_apps :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> [Either (LHsExpr (GhcPass p)) (LHsWcType (NoGhcTc (GhcPass p)))] -> SDoc
- ppr_infix_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> Maybe SDoc
- ppr_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> SDoc
- ppr_lexpr :: forall (p :: Pass). OutputableBndrId p => LHsExpr (GhcPass p) -> SDoc
- pprBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> SDoc
- isQuietHsExpr :: HsExpr id -> Bool
- tupArgPresent :: LHsTupArg id -> Bool
- unboundVarOcc :: UnboundVar -> OccName
- mkRnSyntaxExpr :: Name -> SyntaxExpr GhcRn
- mkSyntaxExpr :: forall (p :: Pass). HsExpr (GhcPass p) -> SyntaxExpr (GhcPass p)
- noSyntaxExpr :: forall (p :: Pass). SyntaxExpr (GhcPass p)
- noExpr :: forall (p :: Pass). HsExpr (GhcPass p)
- type PostTcExpr = HsExpr GhcTc
- type PostTcTable = [(Name, PostTcExpr)]
- type CmdSyntaxTable p = [(Name, HsExpr p)]
- data UnboundVar
- data RecordConTc = RecordConTc {}
- data RecordUpdTc = RecordUpdTc {
- rupd_cons :: [ConLike]
- rupd_in_tys :: [Type]
- rupd_out_tys :: [Type]
- rupd_wrap :: HsWrapper
- type LHsTupArg id = Located (HsTupArg id)
- data HsTupArg id
- type LHsCmd id = Located (HsCmd id)
- data HsArrAppType
- type LHsCmdTop p = Located (HsCmdTop p)
- data HsCmdTop p
- data CmdTopTc = CmdTopTc Type Type (CmdSyntaxTable GhcTc)
- type HsRecordBinds p = HsRecFields p (LHsExpr p)
- data MatchGroupTc = MatchGroupTc {
- mg_arg_tys :: [Type]
- mg_res_ty :: Type
- type LMatch id body = Located (Match id body)
- data Match p body
- type LGRHS id body = Located (GRHS id body)
- data GRHS p body
- = GRHS (XCGRHS p body) [GuardLStmt p] body
- | XGRHS (XXGRHS p body)
- type LStmt id body = Located (StmtLR id id body)
- type LStmtLR idL idR body = Located (StmtLR idL idR body)
- type Stmt id body = StmtLR id id body
- type CmdLStmt id = LStmt id (LHsCmd id)
- type CmdStmt id = Stmt id (LHsCmd id)
- type ExprLStmt id = LStmt id (LHsExpr id)
- type ExprStmt id = Stmt id (LHsExpr id)
- type GuardLStmt id = LStmt id (LHsExpr id)
- type GuardStmt id = Stmt id (LHsExpr id)
- type GhciLStmt id = LStmt id (LHsExpr id)
- type GhciStmt id = Stmt id (LHsExpr id)
- data StmtLR idL idR body
- = LastStmt (XLastStmt idL idR body) body Bool (SyntaxExpr idR)
- | BindStmt (XBindStmt idL idR body) (LPat idL) body (SyntaxExpr idR) (SyntaxExpr idR)
- | ApplicativeStmt (XApplicativeStmt idL idR body) [(SyntaxExpr idR, ApplicativeArg idL)] (Maybe (SyntaxExpr idR))
- | BodyStmt (XBodyStmt idL idR body) body (SyntaxExpr idR) (SyntaxExpr idR)
- | LetStmt (XLetStmt idL idR body) (LHsLocalBindsLR idL idR)
- | ParStmt (XParStmt idL idR body) [ParStmtBlock idL idR] (HsExpr idR) (SyntaxExpr idR)
- | TransStmt { }
- | RecStmt {
- recS_ext :: XRecStmt idL idR body
- recS_stmts :: [LStmtLR idL idR body]
- recS_later_ids :: [IdP idR]
- recS_rec_ids :: [IdP idR]
- recS_bind_fn :: SyntaxExpr idR
- recS_ret_fn :: SyntaxExpr idR
- recS_mfix_fn :: SyntaxExpr idR
- | XStmtLR (XXStmtLR idL idR body)
- data RecStmtTc = RecStmtTc {
- recS_bind_ty :: Type
- recS_later_rets :: [PostTcExpr]
- recS_rec_rets :: [PostTcExpr]
- recS_ret_ty :: Type
- data TransForm
- data ParStmtBlock idL idR
- = ParStmtBlock (XParStmtBlock idL idR) [ExprLStmt idL] [IdP idR] (SyntaxExpr idR)
- | XParStmtBlock (XXParStmtBlock idL idR)
- data ApplicativeArg idL
- = ApplicativeArgOne {
- xarg_app_arg_one :: XApplicativeArgOne idL
- app_arg_pattern :: LPat idL
- arg_expr :: LHsExpr idL
- is_body_stmt :: Bool
- fail_operator :: SyntaxExpr idL
- | ApplicativeArgMany {
- xarg_app_arg_many :: XApplicativeArgMany idL
- app_stmts :: [ExprLStmt idL]
- final_expr :: HsExpr idL
- bv_pattern :: LPat idL
- | XApplicativeArg (XXApplicativeArg idL)
- = ApplicativeArgOne {
- data SpliceDecoration
- newtype ThModFinalizers = ThModFinalizers [ForeignRef (Q ())]
- data DelayedSplice = DelayedSplice TcLclEnv (LHsExpr GhcRn) TcType (LHsExpr GhcTcId)
- data HsSplicedThing id
- = HsSplicedExpr (HsExpr id)
- | HsSplicedTy (HsType id)
- | HsSplicedPat (Pat id)
- type SplicePointName = Name
- data PendingRnSplice = PendingRnSplice UntypedSpliceFlavour SplicePointName (LHsExpr GhcRn)
- data UntypedSpliceFlavour
- data PendingTcSplice = PendingTcSplice SplicePointName (LHsExpr GhcTc)
- data HsBracket p
- data ArithSeqInfo id
- data HsMatchContext id
- = FunRhs { }
- | LambdaExpr
- | CaseAlt
- | IfAlt
- | ProcExpr
- | PatBindRhs
- | PatBindGuards
- | RecUpd
- | StmtCtxt (HsStmtContext id)
- | ThPatSplice
- | ThPatQuote
- | PatSyn
- data HsStmtContext id
- = ListComp
- | MonadComp
- | DoExpr
- | MDoExpr
- | ArrowExpr
- | GhciStmtCtxt
- | PatGuard (HsMatchContext id)
- | ParStmtCtxt (HsStmtContext id)
- | TransStmtCtxt (HsStmtContext id)
- roleAnnotDeclName :: forall (p :: Pass). RoleAnnotDecl (GhcPass p) -> IdP (GhcPass p)
- annProvenanceName_maybe :: AnnProvenance name -> Maybe name
- docDeclDoc :: DocDecl -> HsDocString
- pprFullRuleName :: Located (SourceText, RuleName) -> SDoc
- collectRuleBndrSigTys :: [RuleBndr pass] -> [LHsSigWcType pass]
- flattenRuleDecls :: [LRuleDecls pass] -> [LRuleDecl pass]
- mapDerivStrategy :: forall p (pass :: Pass). p ~ GhcPass pass => (XViaStrategy p -> XViaStrategy p) -> DerivStrategy p -> DerivStrategy p
- foldDerivStrategy :: forall p (pass :: Pass) r. p ~ GhcPass pass => r -> (XViaStrategy p -> r) -> DerivStrategy p -> r
- derivStrategyName :: DerivStrategy a -> SDoc
- instDeclDataFamInsts :: forall (p :: Pass). [LInstDecl (GhcPass p)] -> [DataFamInstDecl (GhcPass p)]
- pprHsFamInstLHS :: forall (p :: Pass). OutputableBndrId p => IdP (GhcPass p) -> Maybe [LHsTyVarBndr (GhcPass p)] -> HsTyPats (GhcPass p) -> LexicalFixity -> LHsContext (GhcPass p) -> SDoc
- pprDataFamInstFlavour :: forall (p :: Pass). DataFamInstDecl (GhcPass p) -> SDoc
- pprTyFamInstDecl :: forall (p :: Pass). OutputableBndrId p => TopLevelFlag -> TyFamInstDecl (GhcPass p) -> SDoc
- hsConDeclTheta :: Maybe (LHsContext pass) -> [LHsType pass]
- hsConDeclArgTys :: HsConDeclDetails pass -> [LBangType pass]
- getConArgs :: ConDecl pass -> HsConDeclDetails pass
- getConNames :: forall (p :: Pass). ConDecl (GhcPass p) -> [Located (IdP (GhcPass p))]
- newOrDataToFlavour :: NewOrData -> TyConFlavour
- standaloneKindSigName :: forall (p :: Pass). StandaloneKindSig (GhcPass p) -> IdP (GhcPass p)
- resultVariableName :: forall (a :: Pass). FamilyResultSig (GhcPass a) -> Maybe (IdP (GhcPass a))
- famResultKindSignature :: forall (p :: Pass). FamilyResultSig (GhcPass p) -> Maybe (LHsKind (GhcPass p))
- familyDeclName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> IdP (GhcPass p)
- familyDeclLName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> Located (IdP (GhcPass p))
- tyClGroupKindSigs :: [TyClGroup pass] -> [LStandaloneKindSig pass]
- tyClGroupRoleDecls :: [TyClGroup pass] -> [LRoleAnnotDecl pass]
- tyClGroupInstDecls :: [TyClGroup pass] -> [LInstDecl pass]
- tyClGroupTyClDecls :: [TyClGroup pass] -> [LTyClDecl pass]
- pprTyClDeclFlavour :: forall (p :: Pass). TyClDecl (GhcPass p) -> SDoc
- hsDeclHasCusk :: TyClDecl GhcRn -> Bool
- countTyClDecls :: [TyClDecl pass] -> (Int, Int, Int, Int, Int)
- tyClDeclTyVars :: TyClDecl pass -> LHsQTyVars pass
- tcdName :: forall (p :: Pass). TyClDecl (GhcPass p) -> IdP (GhcPass p)
- tyClDeclLName :: forall (p :: Pass). TyClDecl (GhcPass p) -> Located (IdP (GhcPass p))
- tyFamInstDeclLName :: forall (p :: Pass). TyFamInstDecl (GhcPass p) -> Located (IdP (GhcPass p))
- tyFamInstDeclName :: forall (p :: Pass). TyFamInstDecl (GhcPass p) -> IdP (GhcPass p)
- isDataFamilyDecl :: TyClDecl pass -> Bool
- isClosedTypeFamilyInfo :: FamilyInfo pass -> Bool
- isOpenTypeFamilyInfo :: FamilyInfo pass -> Bool
- isTypeFamilyDecl :: TyClDecl pass -> Bool
- isFamilyDecl :: TyClDecl pass -> Bool
- isClassDecl :: TyClDecl pass -> Bool
- isSynDecl :: TyClDecl pass -> Bool
- isDataDecl :: TyClDecl pass -> Bool
- appendGroups :: forall (p :: Pass). HsGroup (GhcPass p) -> HsGroup (GhcPass p) -> HsGroup (GhcPass p)
- hsGroupInstDecls :: HsGroup id -> [LInstDecl id]
- emptyRnGroup :: forall (p :: Pass). HsGroup (GhcPass p)
- emptyRdrGroup :: forall (p :: Pass). HsGroup (GhcPass p)
- type LHsDecl p = Located (HsDecl p)
- data HsDecl p
- = TyClD (XTyClD p) (TyClDecl p)
- | InstD (XInstD p) (InstDecl p)
- | DerivD (XDerivD p) (DerivDecl p)
- | ValD (XValD p) (HsBind p)
- | SigD (XSigD p) (Sig p)
- | KindSigD (XKindSigD p) (StandaloneKindSig p)
- | DefD (XDefD p) (DefaultDecl p)
- | ForD (XForD p) (ForeignDecl p)
- | WarningD (XWarningD p) (WarnDecls p)
- | AnnD (XAnnD p) (AnnDecl p)
- | RuleD (XRuleD p) (RuleDecls p)
- | SpliceD (XSpliceD p) (SpliceDecl p)
- | DocD (XDocD p) DocDecl
- | RoleAnnotD (XRoleAnnotD p) (RoleAnnotDecl p)
- | XHsDecl (XXHsDecl p)
- data HsGroup p
- = HsGroup {
- hs_ext :: XCHsGroup p
- hs_valds :: HsValBinds p
- hs_splcds :: [LSpliceDecl p]
- hs_tyclds :: [TyClGroup p]
- hs_derivds :: [LDerivDecl p]
- hs_fixds :: [LFixitySig p]
- hs_defds :: [LDefaultDecl p]
- hs_fords :: [LForeignDecl p]
- hs_warnds :: [LWarnDecls p]
- hs_annds :: [LAnnDecl p]
- hs_ruleds :: [LRuleDecls p]
- hs_docs :: [LDocDecl]
- | XHsGroup (XXHsGroup p)
- = HsGroup {
- type LSpliceDecl pass = Located (SpliceDecl pass)
- data SpliceDecl p
- = SpliceDecl (XSpliceDecl p) (Located (HsSplice p)) SpliceExplicitFlag
- | XSpliceDecl (XXSpliceDecl p)
- type LTyClDecl pass = Located (TyClDecl pass)
- data TyClDecl pass
- = FamDecl {
- tcdFExt :: XFamDecl pass
- tcdFam :: FamilyDecl pass
- | SynDecl { }
- | DataDecl {
- tcdDExt :: XDataDecl pass
- tcdLName :: Located (IdP pass)
- tcdTyVars :: LHsQTyVars pass
- tcdFixity :: LexicalFixity
- tcdDataDefn :: HsDataDefn pass
- | ClassDecl {
- tcdCExt :: XClassDecl pass
- tcdCtxt :: LHsContext pass
- tcdLName :: Located (IdP pass)
- tcdTyVars :: LHsQTyVars pass
- tcdFixity :: LexicalFixity
- tcdFDs :: [LHsFunDep pass]
- tcdSigs :: [LSig pass]
- tcdMeths :: LHsBinds pass
- tcdATs :: [LFamilyDecl pass]
- tcdATDefs :: [LTyFamDefltDecl pass]
- tcdDocs :: [LDocDecl]
- | XTyClDecl (XXTyClDecl pass)
- = FamDecl {
- type LHsFunDep pass = Located (FunDep (Located (IdP pass)))
- data DataDeclRn = DataDeclRn {
- tcdDataCusk :: Bool
- tcdFVs :: NameSet
- data TyClGroup pass
- = TyClGroup {
- group_ext :: XCTyClGroup pass
- group_tyclds :: [LTyClDecl pass]
- group_roles :: [LRoleAnnotDecl pass]
- group_kisigs :: [LStandaloneKindSig pass]
- group_instds :: [LInstDecl pass]
- | XTyClGroup (XXTyClGroup pass)
- = TyClGroup {
- type LFamilyResultSig pass = Located (FamilyResultSig pass)
- data FamilyResultSig pass
- = NoSig (XNoSig pass)
- | KindSig (XCKindSig pass) (LHsKind pass)
- | TyVarSig (XTyVarSig pass) (LHsTyVarBndr pass)
- | XFamilyResultSig (XXFamilyResultSig pass)
- type LFamilyDecl pass = Located (FamilyDecl pass)
- data FamilyDecl pass
- = FamilyDecl {
- fdExt :: XCFamilyDecl pass
- fdInfo :: FamilyInfo pass
- fdLName :: Located (IdP pass)
- fdTyVars :: LHsQTyVars pass
- fdFixity :: LexicalFixity
- fdResultSig :: LFamilyResultSig pass
- fdInjectivityAnn :: Maybe (LInjectivityAnn pass)
- | XFamilyDecl (XXFamilyDecl pass)
- = FamilyDecl {
- type LInjectivityAnn pass = Located (InjectivityAnn pass)
- data InjectivityAnn pass = InjectivityAnn (Located (IdP pass)) [Located (IdP pass)]
- data FamilyInfo pass
- = DataFamily
- | OpenTypeFamily
- | ClosedTypeFamily (Maybe [LTyFamInstEqn pass])
- data HsDataDefn pass
- = HsDataDefn {
- dd_ext :: XCHsDataDefn pass
- dd_ND :: NewOrData
- dd_ctxt :: LHsContext pass
- dd_cType :: Maybe (Located CType)
- dd_kindSig :: Maybe (LHsKind pass)
- dd_cons :: [LConDecl pass]
- dd_derivs :: HsDeriving pass
- | XHsDataDefn (XXHsDataDefn pass)
- = HsDataDefn {
- type HsDeriving pass = Located [LHsDerivingClause pass]
- type LHsDerivingClause pass = Located (HsDerivingClause pass)
- data HsDerivingClause pass
- = HsDerivingClause {
- deriv_clause_ext :: XCHsDerivingClause pass
- deriv_clause_strategy :: Maybe (LDerivStrategy pass)
- deriv_clause_tys :: Located [LHsSigType pass]
- | XHsDerivingClause (XXHsDerivingClause pass)
- = HsDerivingClause {
- type LStandaloneKindSig pass = Located (StandaloneKindSig pass)
- data StandaloneKindSig pass
- = StandaloneKindSig (XStandaloneKindSig pass) (Located (IdP pass)) (LHsSigType pass)
- | XStandaloneKindSig (XXStandaloneKindSig pass)
- data NewOrData
- type LConDecl pass = Located (ConDecl pass)
- data ConDecl pass
- = ConDeclGADT {
- con_g_ext :: XConDeclGADT pass
- con_names :: [Located (IdP pass)]
- con_forall :: Located Bool
- con_qvars :: LHsQTyVars pass
- con_mb_cxt :: Maybe (LHsContext pass)
- con_args :: HsConDeclDetails pass
- con_res_ty :: LHsType pass
- con_doc :: Maybe LHsDocString
- | ConDeclH98 {
- con_ext :: XConDeclH98 pass
- con_name :: Located (IdP pass)
- con_forall :: Located Bool
- con_ex_tvs :: [LHsTyVarBndr pass]
- con_mb_cxt :: Maybe (LHsContext pass)
- con_args :: HsConDeclDetails pass
- con_doc :: Maybe LHsDocString
- | XConDecl (XXConDecl pass)
- = ConDeclGADT {
- type HsConDeclDetails pass = HsConDetails (LBangType pass) (Located [LConDeclField pass])
- type LTyFamInstEqn pass = Located (TyFamInstEqn pass)
- type HsTyPats pass = [LHsTypeArg pass]
- type TyFamInstEqn pass = FamInstEqn pass (LHsType pass)
- type TyFamDefltDecl = TyFamInstDecl
- type LTyFamDefltDecl pass = Located (TyFamDefltDecl pass)
- type LTyFamInstDecl pass = Located (TyFamInstDecl pass)
- newtype TyFamInstDecl pass = TyFamInstDecl {
- tfid_eqn :: TyFamInstEqn pass
- type LDataFamInstDecl pass = Located (DataFamInstDecl pass)
- newtype DataFamInstDecl pass = DataFamInstDecl {
- dfid_eqn :: FamInstEqn pass (HsDataDefn pass)
- type LFamInstEqn pass rhs = Located (FamInstEqn pass rhs)
- type FamInstEqn pass rhs = HsImplicitBndrs pass (FamEqn pass rhs)
- data FamEqn pass rhs
- = FamEqn {
- feqn_ext :: XCFamEqn pass rhs
- feqn_tycon :: Located (IdP pass)
- feqn_bndrs :: Maybe [LHsTyVarBndr pass]
- feqn_pats :: HsTyPats pass
- feqn_fixity :: LexicalFixity
- feqn_rhs :: rhs
- | XFamEqn (XXFamEqn pass rhs)
- = FamEqn {
- type LClsInstDecl pass = Located (ClsInstDecl pass)
- data ClsInstDecl pass
- = ClsInstDecl {
- cid_ext :: XCClsInstDecl pass
- cid_poly_ty :: LHsSigType pass
- cid_binds :: LHsBinds pass
- cid_sigs :: [LSig pass]
- cid_tyfam_insts :: [LTyFamInstDecl pass]
- cid_datafam_insts :: [LDataFamInstDecl pass]
- cid_overlap_mode :: Maybe (Located OverlapMode)
- | XClsInstDecl (XXClsInstDecl pass)
- = ClsInstDecl {
- type LInstDecl pass = Located (InstDecl pass)
- data InstDecl pass
- = ClsInstD {
- cid_d_ext :: XClsInstD pass
- cid_inst :: ClsInstDecl pass
- | DataFamInstD {
- dfid_ext :: XDataFamInstD pass
- dfid_inst :: DataFamInstDecl pass
- | TyFamInstD {
- tfid_ext :: XTyFamInstD pass
- tfid_inst :: TyFamInstDecl pass
- | XInstDecl (XXInstDecl pass)
- = ClsInstD {
- type LDerivDecl pass = Located (DerivDecl pass)
- data DerivDecl pass
- = DerivDecl {
- deriv_ext :: XCDerivDecl pass
- deriv_type :: LHsSigWcType pass
- deriv_strategy :: Maybe (LDerivStrategy pass)
- deriv_overlap_mode :: Maybe (Located OverlapMode)
- | XDerivDecl (XXDerivDecl pass)
- = DerivDecl {
- type LDerivStrategy pass = Located (DerivStrategy pass)
- data DerivStrategy pass
- type LDefaultDecl pass = Located (DefaultDecl pass)
- data DefaultDecl pass
- = DefaultDecl (XCDefaultDecl pass) [LHsType pass]
- | XDefaultDecl (XXDefaultDecl pass)
- type LForeignDecl pass = Located (ForeignDecl pass)
- data ForeignDecl pass
- = ForeignImport {
- fd_i_ext :: XForeignImport pass
- fd_name :: Located (IdP pass)
- fd_sig_ty :: LHsSigType pass
- fd_fi :: ForeignImport
- | ForeignExport {
- fd_e_ext :: XForeignExport pass
- fd_name :: Located (IdP pass)
- fd_sig_ty :: LHsSigType pass
- fd_fe :: ForeignExport
- | XForeignDecl (XXForeignDecl pass)
- = ForeignImport {
- data ForeignImport = CImport (Located CCallConv) (Located Safety) (Maybe Header) CImportSpec (Located SourceText)
- data CImportSpec
- data ForeignExport = CExport (Located CExportSpec) (Located SourceText)
- type LRuleDecls pass = Located (RuleDecls pass)
- data RuleDecls pass
- = HsRules {
- rds_ext :: XCRuleDecls pass
- rds_src :: SourceText
- rds_rules :: [LRuleDecl pass]
- | XRuleDecls (XXRuleDecls pass)
- = HsRules {
- type LRuleDecl pass = Located (RuleDecl pass)
- data RuleDecl pass
- data HsRuleRn = HsRuleRn NameSet NameSet
- type LRuleBndr pass = Located (RuleBndr pass)
- data RuleBndr pass
- = RuleBndr (XCRuleBndr pass) (Located (IdP pass))
- | RuleBndrSig (XRuleBndrSig pass) (Located (IdP pass)) (LHsSigWcType pass)
- | XRuleBndr (XXRuleBndr pass)
- type LDocDecl = Located DocDecl
- data DocDecl
- type LWarnDecls pass = Located (WarnDecls pass)
- data WarnDecls pass
- = Warnings {
- wd_ext :: XWarnings pass
- wd_src :: SourceText
- wd_warnings :: [LWarnDecl pass]
- | XWarnDecls (XXWarnDecls pass)
- = Warnings {
- type LWarnDecl pass = Located (WarnDecl pass)
- data WarnDecl pass = XWarnDecl (XXWarnDecl pass)
- type LAnnDecl pass = Located (AnnDecl pass)
- data AnnDecl pass
- = HsAnnotation (XHsAnnotation pass) SourceText (AnnProvenance (IdP pass)) (Located (HsExpr pass))
- | XAnnDecl (XXAnnDecl pass)
- data AnnProvenance name
- = ValueAnnProvenance (Located name)
- | TypeAnnProvenance (Located name)
- | ModuleAnnProvenance
- type LRoleAnnotDecl pass = Located (RoleAnnotDecl pass)
- data RoleAnnotDecl pass
- = RoleAnnotDecl (XCRoleAnnotDecl pass) (Located (IdP pass)) [Located (Maybe Role)]
- | XRoleAnnotDecl (XXRoleAnnotDecl pass)
- collectEvVarsPat :: Pat GhcTc -> Bag EvVar
- collectEvVarsPats :: [Pat GhcTc] -> Bag EvVar
- parenthesizePat :: forall (p :: Pass). PprPrec -> LPat (GhcPass p) -> LPat (GhcPass p)
- patNeedsParens :: PprPrec -> Pat p -> Bool
- isIrrefutableHsPat :: forall (p :: Pass). OutputableBndrId p => LPat (GhcPass p) -> Bool
- looksLazyPatBind :: forall (p :: Pass). HsBind (GhcPass p) -> Bool
- isBangedLPat :: forall (p :: Pass). LPat (GhcPass p) -> Bool
- mkCharLitPat :: forall (p :: Pass). SourceText -> Char -> OutPat (GhcPass p)
- mkNilPat :: forall (p :: Pass). Type -> OutPat (GhcPass p)
- mkPrefixConPat :: forall (p :: Pass). DataCon -> [OutPat (GhcPass p)] -> [Type] -> OutPat (GhcPass p)
- pprConArgs :: forall (p :: Pass). OutputableBndrId p => HsConPatDetails (GhcPass p) -> SDoc
- pprParendLPat :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LPat (GhcPass p) -> SDoc
- hsRecUpdFieldOcc :: HsRecField' (AmbiguousFieldOcc GhcTc) arg -> LFieldOcc GhcTc
- hsRecUpdFieldId :: HsRecField' (AmbiguousFieldOcc GhcTc) arg -> Located Id
- hsRecUpdFieldRdr :: forall (p :: Pass). HsRecUpdField (GhcPass p) -> Located RdrName
- hsRecFieldId :: HsRecField GhcTc arg -> Located Id
- hsRecFieldSel :: HsRecField pass arg -> Located (XCFieldOcc pass)
- hsRecFieldsArgs :: HsRecFields p arg -> [arg]
- hsRecFields :: HsRecFields p arg -> [XCFieldOcc p]
- hsConPatArgs :: HsConPatDetails p -> [LPat p]
- type InPat p = LPat p
- type OutPat p = LPat p
- data ListPatTc = ListPatTc Type (Maybe (Type, SyntaxExpr GhcTc))
- type HsConPatDetails p = HsConDetails (LPat p) (HsRecFields p (LPat p))
- data HsRecFields p arg = HsRecFields {
- rec_flds :: [LHsRecField p arg]
- rec_dotdot :: Maybe (Located Int)
- type LHsRecField' p arg = Located (HsRecField' p arg)
- type LHsRecField p arg = Located (HsRecField p arg)
- type LHsRecUpdField p = Located (HsRecUpdField p)
- type HsRecField p arg = HsRecField' (FieldOcc p) arg
- type HsRecUpdField p = HsRecField' (AmbiguousFieldOcc p) (LHsExpr p)
- data HsRecField' id arg = HsRecField {
- hsRecFieldLbl :: Located id
- hsRecFieldArg :: arg
- hsRecPun :: Bool
- pprMinimalSig :: OutputableBndr name => LBooleanFormula (Located name) -> SDoc
- pprTcSpecPrags :: TcSpecPrags -> SDoc
- pprSpec :: OutputableBndr id => id -> SDoc -> InlinePragma -> SDoc
- pprVarSig :: OutputableBndr id => [id] -> SDoc -> SDoc
- pragSrcBrackets :: SourceText -> String -> SDoc -> SDoc
- pragBrackets :: SDoc -> SDoc
- ppr_sig :: forall (p :: Pass). OutputableBndrId p => Sig (GhcPass p) -> SDoc
- hsSigDoc :: Sig name -> SDoc
- isCompleteMatchSig :: LSig name -> Bool
- isSCCFunSig :: LSig name -> Bool
- isMinimalLSig :: LSig name -> Bool
- isInlineLSig :: LSig name -> Bool
- isPragLSig :: LSig name -> Bool
- isSpecInstLSig :: LSig name -> Bool
- isSpecLSig :: LSig name -> Bool
- isTypeLSig :: LSig name -> Bool
- isFixityLSig :: LSig name -> Bool
- isDefaultMethod :: TcSpecPrags -> Bool
- hasSpecPrags :: TcSpecPrags -> Bool
- noSpecPrags :: TcSpecPrags
- isEmptyIPBindsTc :: HsIPBinds GhcTc -> Bool
- isEmptyIPBindsPR :: forall (p :: Pass). HsIPBinds (GhcPass p) -> Bool
- pprTicks :: SDoc -> SDoc -> SDoc
- ppr_monobind :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsBindLR (GhcPass idL) (GhcPass idR) -> SDoc
- plusHsValBinds :: forall (a :: Pass). HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) -> HsValBinds (GhcPass a)
- isEmptyLHsBinds :: LHsBindsLR idL idR -> Bool
- emptyLHsBinds :: LHsBindsLR idL idR
- emptyValBindsOut :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b)
- emptyValBindsIn :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b)
- isEmptyValBinds :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) -> Bool
- eqEmptyLocalBinds :: HsLocalBindsLR a b -> Bool
- isEmptyLocalBindsPR :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b) -> Bool
- isEmptyLocalBindsTc :: forall (a :: Pass). HsLocalBindsLR (GhcPass a) GhcTc -> Bool
- emptyLocalBinds :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b)
- pprDeclList :: [SDoc] -> SDoc
- pprLHsBindsForUser :: forall (idL :: Pass) (idR :: Pass) (id2 :: Pass). (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId id2) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> [LSig (GhcPass id2)] -> [SDoc]
- pprLHsBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> SDoc
- type HsLocalBinds id = HsLocalBindsLR id id
- type LHsLocalBinds id = Located (HsLocalBinds id)
- data HsLocalBindsLR idL idR
- = HsValBinds (XHsValBinds idL idR) (HsValBindsLR idL idR)
- | HsIPBinds (XHsIPBinds idL idR) (HsIPBinds idR)
- | EmptyLocalBinds (XEmptyLocalBinds idL idR)
- | XHsLocalBindsLR (XXHsLocalBindsLR idL idR)
- type LHsLocalBindsLR idL idR = Located (HsLocalBindsLR idL idR)
- type HsValBinds id = HsValBindsLR id id
- data HsValBindsLR idL idR
- = ValBinds (XValBinds idL idR) (LHsBindsLR idL idR) [LSig idR]
- | XValBindsLR (XXValBindsLR idL idR)
- data NHsValBindsLR idL = NValBinds [(RecFlag, LHsBinds idL)] [LSig GhcRn]
- type LHsBind id = LHsBindLR id id
- type LHsBinds id = LHsBindsLR id id
- type HsBind id = HsBindLR id id
- type LHsBindsLR idL idR = Bag (LHsBindLR idL idR)
- type LHsBindLR idL idR = Located (HsBindLR idL idR)
- data HsBindLR idL idR
- = FunBind { }
- | PatBind { }
- | VarBind { }
- | AbsBinds {
- abs_ext :: XAbsBinds idL idR
- abs_tvs :: [TyVar]
- abs_ev_vars :: [EvVar]
- abs_exports :: [ABExport idL]
- abs_ev_binds :: [TcEvBinds]
- abs_binds :: LHsBinds idL
- abs_sig :: Bool
- | PatSynBind (XPatSynBind idL idR) (PatSynBind idL idR)
- | XHsBindsLR (XXHsBindsLR idL idR)
- data NPatBindTc = NPatBindTc {
- pat_fvs :: NameSet
- pat_rhs_ty :: Type
- data ABExport p
- data PatSynBind idL idR
- = PSB { }
- | XPatSynBind (XXPatSynBind idL idR)
- data HsIPBinds id
- = IPBinds (XIPBinds id) [LIPBind id]
- | XHsIPBinds (XXHsIPBinds id)
- type LIPBind id = Located (IPBind id)
- data IPBind id
- type LSig pass = Located (Sig pass)
- data Sig pass
- = TypeSig (XTypeSig pass) [Located (IdP pass)] (LHsSigWcType pass)
- | PatSynSig (XPatSynSig pass) [Located (IdP pass)] (LHsSigType pass)
- | ClassOpSig (XClassOpSig pass) Bool [Located (IdP pass)] (LHsSigType pass)
- | IdSig (XIdSig pass) Id
- | FixSig (XFixSig pass) (FixitySig pass)
- | InlineSig (XInlineSig pass) (Located (IdP pass)) InlinePragma
- | SpecSig (XSpecSig pass) (Located (IdP pass)) [LHsSigType pass] InlinePragma
- | SpecInstSig (XSpecInstSig pass) SourceText (LHsSigType pass)
- | MinimalSig (XMinimalSig pass) SourceText (LBooleanFormula (Located (IdP pass)))
- | SCCFunSig (XSCCFunSig pass) SourceText (Located (IdP pass)) (Maybe (Located StringLiteral))
- | CompleteMatchSig (XCompleteMatchSig pass) SourceText (Located [Located (IdP pass)]) (Maybe (Located (IdP pass)))
- | XSig (XXSig pass)
- type LFixitySig pass = Located (FixitySig pass)
- data FixitySig pass
- = FixitySig (XFixitySig pass) [Located (IdP pass)] Fixity
- | XFixitySig (XXFixitySig pass)
- data TcSpecPrags
- type LTcSpecPrag = Located TcSpecPrag
- data TcSpecPrag = SpecPrag Id HsWrapper InlinePragma
- type HsPatSynDetails arg = HsConDetails arg [RecordPatSynField arg]
- data RecordPatSynField a = RecordPatSynField {
- recordPatSynSelectorId :: a
- recordPatSynPatVar :: a
- data HsPatSynDir id
- instanceBindFun :: TyCoVar -> BindFlag
- lookupInstEnv :: Bool -> InstEnvs -> Class -> [Type] -> ClsInstLookupResult
- lookupUniqueInstEnv :: InstEnvs -> Class -> [Type] -> Either MsgDoc (ClsInst, [Type])
- identicalClsInstHead :: ClsInst -> ClsInst -> Bool
- deleteDFunFromInstEnv :: InstEnv -> DFunId -> InstEnv
- deleteFromInstEnv :: InstEnv -> ClsInst -> InstEnv
- extendInstEnv :: InstEnv -> ClsInst -> InstEnv
- extendInstEnvList :: InstEnv -> [ClsInst] -> InstEnv
- memberInstEnv :: InstEnv -> ClsInst -> Bool
- classInstances :: InstEnvs -> Class -> [ClsInst]
- instIsVisible :: VisibleOrphanModules -> ClsInst -> Bool
- instEnvClasses :: InstEnv -> [Class]
- instEnvElts :: InstEnv -> [ClsInst]
- emptyInstEnv :: InstEnv
- mkImportedInstance :: Name -> [Maybe Name] -> Name -> DFunId -> OverlapFlag -> IsOrphan -> ClsInst
- mkLocalInstance :: DFunId -> OverlapFlag -> [TyVar] -> Class -> [Type] -> ClsInst
- instanceSig :: ClsInst -> ([TyVar], [Type], Class, [Type])
- orphNamesOfClsInst :: ClsInst -> NameSet
- instanceHead :: ClsInst -> ([TyVar], Class, [Type])
- pprInstances :: [ClsInst] -> SDoc
- pprInstanceHdr :: ClsInst -> SDoc
- pprInstance :: ClsInst -> SDoc
- instanceRoughTcs :: ClsInst -> [Maybe Name]
- updateClsInstDFun :: (DFunId -> DFunId) -> ClsInst -> ClsInst
- instanceDFunId :: ClsInst -> DFunId
- isIncoherent :: ClsInst -> Bool
- isOverlapping :: ClsInst -> Bool
- isOverlappable :: ClsInst -> Bool
- fuzzyClsInstCmp :: ClsInst -> ClsInst -> Ordering
- data ClsInst = ClsInst {}
- type InstEnv = UniqDFM ClsInstEnv
- data InstEnvs = InstEnvs {}
- type VisibleOrphanModules = ModuleSet
- type DFunInstType = Maybe Type
- type InstMatch = (ClsInst, [DFunInstType])
- type ClsInstLookupResult = ([InstMatch], [ClsInst], [InstMatch])
- data FamInst
- data Linkable = LM {}
- data Unlinked
- data SptEntry = SptEntry Id Fingerprint
- emptyModBreaks :: ModBreaks
- data CompiledByteCode
- type BreakIndex = Int
- data ModBreaks = ModBreaks {}
- parenthesizeHsContext :: forall (p :: Pass). PprPrec -> LHsContext (GhcPass p) -> LHsContext (GhcPass p)
- parenthesizeHsType :: forall (p :: Pass). PprPrec -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- hsTypeNeedsParens :: PprPrec -> HsType pass -> Bool
- pprHsType :: forall (p :: Pass). OutputableBndrId p => HsType (GhcPass p) -> SDoc
- pprConDeclFields :: forall (p :: Pass). OutputableBndrId p => [LConDeclField (GhcPass p)] -> SDoc
- pprLHsContext :: forall (p :: Pass). OutputableBndrId p => LHsContext (GhcPass p) -> SDoc
- pprHsExplicitForAll :: forall (p :: Pass). OutputableBndrId p => ForallVisFlag -> Maybe [LHsTyVarBndr (GhcPass p)] -> SDoc
- pprHsForAllExtra :: forall (p :: Pass). OutputableBndrId p => Maybe SrcSpan -> ForallVisFlag -> [LHsTyVarBndr (GhcPass p)] -> LHsContext (GhcPass p) -> SDoc
- pprHsForAll :: forall (p :: Pass). OutputableBndrId p => ForallVisFlag -> [LHsTyVarBndr (GhcPass p)] -> LHsContext (GhcPass p) -> SDoc
- pprAnonWildCard :: SDoc
- ambiguousFieldOcc :: FieldOcc GhcTc -> AmbiguousFieldOcc GhcTc
- unambiguousFieldOcc :: AmbiguousFieldOcc GhcTc -> FieldOcc GhcTc
- selectorAmbiguousFieldOcc :: AmbiguousFieldOcc GhcTc -> Id
- rdrNameAmbiguousFieldOcc :: forall (p :: Pass). AmbiguousFieldOcc (GhcPass p) -> RdrName
- mkAmbiguousFieldOcc :: Located RdrName -> AmbiguousFieldOcc GhcPs
- mkFieldOcc :: Located RdrName -> FieldOcc GhcPs
- getLHsInstDeclClass_maybe :: forall (p :: Pass). LHsSigType (GhcPass p) -> Maybe (Located (IdP (GhcPass p)))
- getLHsInstDeclHead :: forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p)
- splitLHsInstDeclTy :: LHsSigType GhcRn -> ([Name], LHsContext GhcRn, LHsType GhcRn)
- splitLHsQualTy :: LHsType pass -> (LHsContext pass, LHsType pass)
- splitLHsForAllTyInvis :: LHsType pass -> ([LHsTyVarBndr pass], LHsType pass)
- splitLHsSigmaTyInvis :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, LHsType pass)
- splitLHsPatSynTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, [LHsTyVarBndr pass], LHsContext pass, LHsType pass)
- numVisibleArgs :: [HsArg tm ty] -> Arity
- hsTyGetAppHead_maybe :: forall (p :: Pass). LHsType (GhcPass p) -> Maybe (Located (IdP (GhcPass p)))
- splitHsFunType :: LHsType GhcRn -> ([LHsType GhcRn], LHsType GhcRn)
- mkHsAppKindTy :: forall (p :: Pass). XAppKindTy (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- mkHsAppTys :: forall (p :: Pass). LHsType (GhcPass p) -> [LHsType (GhcPass p)] -> LHsType (GhcPass p)
- mkHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- mkHsOpTy :: forall (p :: Pass). LHsType (GhcPass p) -> Located (IdP (GhcPass p)) -> LHsType (GhcPass p) -> HsType (GhcPass p)
- mkAnonWildCardTy :: HsType GhcPs
- isLHsForAllTy :: LHsType p -> Bool
- ignoreParens :: LHsType pass -> LHsType pass
- hsTyKindSig :: LHsType pass -> Maybe (LHsKind pass)
- hsLTyVarBndrsToTypes :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [LHsType (GhcPass p)]
- hsLTyVarBndrToType :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> LHsType (GhcPass p)
- hsLTyVarLocNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [Located (IdP (GhcPass p))]
- hsLTyVarLocName :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> Located (IdP (GhcPass p))
- hsAllLTyVarNames :: LHsQTyVars GhcRn -> [Name]
- hsExplicitLTyVarNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [IdP (GhcPass p)]
- hsLTyVarNames :: forall (p :: Pass). [LHsTyVarBndr (GhcPass p)] -> [IdP (GhcPass p)]
- hsLTyVarName :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> IdP (GhcPass p)
- hsTyVarName :: forall (p :: Pass). HsTyVarBndr (GhcPass p) -> IdP (GhcPass p)
- hsScopedTvs :: LHsSigType GhcRn -> [Name]
- hsWcScopedTvs :: LHsSigWcType GhcRn -> [Name]
- hsConDetailsArgs :: HsConDetails (LHsType a) (Located [LConDeclField a]) -> [LHsType a]
- hsTvbAllKinded :: LHsQTyVars pass -> Bool
- isHsKindedTyVar :: HsTyVarBndr pass -> Bool
- hsIPNameFS :: HsIPName -> FastString
- mkEmptyWildCardBndrs :: thing -> HsWildCardBndrs GhcRn thing
- mkEmptyImplicitBndrs :: thing -> HsImplicitBndrs GhcRn thing
- mkHsWildCardBndrs :: thing -> HsWildCardBndrs GhcPs thing
- mkHsImplicitBndrs :: thing -> HsImplicitBndrs GhcPs thing
- dropWildCards :: LHsSigWcType pass -> LHsSigType pass
- hsSigWcType :: LHsSigWcType pass -> LHsType pass
- hsSigType :: forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p)
- hsImplicitBody :: forall (p :: Pass) thing. HsImplicitBndrs (GhcPass p) thing -> thing
- isEmptyLHsQTvs :: LHsQTyVars GhcRn -> Bool
- emptyLHsQTvs :: LHsQTyVars GhcRn
- hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr pass]
- mkHsQTvs :: [LHsTyVarBndr GhcPs] -> LHsQTyVars GhcPs
- noLHsContext :: LHsContext pass
- getBangStrictness :: LHsType a -> HsSrcBang
- getBangType :: LHsType a -> LHsType a
- type LBangType pass = Located (BangType pass)
- type BangType pass = HsType pass
- type LHsContext pass = Located (HsContext pass)
- type HsContext pass = [LHsType pass]
- type LHsType pass = Located (HsType pass)
- type HsKind pass = HsType pass
- type LHsKind pass = Located (HsKind pass)
- type LHsTyVarBndr pass = Located (HsTyVarBndr pass)
- data LHsQTyVars pass
- = HsQTvs {
- hsq_ext :: XHsQTvs pass
- hsq_explicit :: [LHsTyVarBndr pass]
- | XLHsQTyVars (XXLHsQTyVars pass)
- = HsQTvs {
- data HsImplicitBndrs pass thing
- = HsIB { }
- | XHsImplicitBndrs (XXHsImplicitBndrs pass thing)
- data HsWildCardBndrs pass thing
- = HsWC { }
- | XHsWildCardBndrs (XXHsWildCardBndrs pass thing)
- type LHsSigType pass = HsImplicitBndrs pass (LHsType pass)
- type LHsWcType pass = HsWildCardBndrs pass (LHsType pass)
- type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass)
- newtype HsIPName = HsIPName FastString
- data HsTyVarBndr pass
- = UserTyVar (XUserTyVar pass) (Located (IdP pass))
- | KindedTyVar (XKindedTyVar pass) (Located (IdP pass)) (LHsKind pass)
- | XTyVarBndr (XXTyVarBndr pass)
- data HsType pass
- = HsForAllTy {
- hst_xforall :: XForAllTy pass
- hst_fvf :: ForallVisFlag
- hst_bndrs :: [LHsTyVarBndr pass]
- hst_body :: LHsType pass
- | HsQualTy { }
- | HsTyVar (XTyVar pass) PromotionFlag (Located (IdP pass))
- | HsAppTy (XAppTy pass) (LHsType pass) (LHsType pass)
- | HsAppKindTy (XAppKindTy pass) (LHsType pass) (LHsKind pass)
- | HsFunTy (XFunTy pass) (LHsType pass) (LHsType pass)
- | HsListTy (XListTy pass) (LHsType pass)
- | HsTupleTy (XTupleTy pass) HsTupleSort [LHsType pass]
- | HsSumTy (XSumTy pass) [LHsType pass]
- | HsOpTy (XOpTy pass) (LHsType pass) (Located (IdP pass)) (LHsType pass)
- | HsParTy (XParTy pass) (LHsType pass)
- | HsIParamTy (XIParamTy pass) (Located HsIPName) (LHsType pass)
- | HsStarTy (XStarTy pass) Bool
- | HsKindSig (XKindSig pass) (LHsType pass) (LHsKind pass)
- | HsSpliceTy (XSpliceTy pass) (HsSplice pass)
- | HsDocTy (XDocTy pass) (LHsType pass) LHsDocString
- | HsBangTy (XBangTy pass) HsSrcBang (LHsType pass)
- | HsRecTy (XRecTy pass) [LConDeclField pass]
- | HsExplicitListTy (XExplicitListTy pass) PromotionFlag [LHsType pass]
- | HsExplicitTupleTy (XExplicitTupleTy pass) [LHsType pass]
- | HsTyLit (XTyLit pass) HsTyLit
- | HsWildCardTy (XWildCardTy pass)
- | XHsType (XXType pass)
- = HsForAllTy {
- data NewHsTypeX = NHsCoreTy Type
- data HsTyLit
- data HsTupleSort
- type LConDeclField pass = Located (ConDeclField pass)
- data ConDeclField pass
- = ConDeclField {
- cd_fld_ext :: XConDeclField pass
- cd_fld_names :: [LFieldOcc pass]
- cd_fld_type :: LBangType pass
- cd_fld_doc :: Maybe LHsDocString
- | XConDeclField (XXConDeclField pass)
- = ConDeclField {
- data HsConDetails arg rec
- data HsArg tm ty
- type LHsTypeArg p = HsArg (LHsType p) (LHsKind p)
- type LFieldOcc pass = Located (FieldOcc pass)
- data FieldOcc pass
- = FieldOcc {
- extFieldOcc :: XCFieldOcc pass
- rdrNameFieldOcc :: Located RdrName
- | XFieldOcc (XXFieldOcc pass)
- = FieldOcc {
- data AmbiguousFieldOcc pass
- = Unambiguous (XUnambiguous pass) (Located RdrName)
- | Ambiguous (XAmbiguous pass) (Located RdrName)
- | XAmbiguousFieldOcc (XXAmbiguousFieldOcc pass)
- data ExecOptions = ExecOptions {}
- data SingleStep
- data ExecResult
- = ExecComplete { }
- | ExecBreak {
- breakNames :: [Name]
- breakInfo :: Maybe BreakInfo
- data BreakInfo
- data Resume = Resume {
- resumeStmt :: String
- resumeContext :: ForeignRef (ResumeContext [HValueRef])
- resumeBindings :: ([TyThing], GlobalRdrEnv)
- resumeFinalIds :: [Id]
- resumeApStack :: ForeignHValue
- resumeBreakInfo :: Maybe BreakInfo
- resumeSpan :: SrcSpan
- resumeDecl :: String
- resumeCCS :: RemotePtr CostCentreStack
- resumeHistory :: [History]
- resumeHistoryIx :: Int
- data History
- promotedNilDataCon :: TyCon
- promotedConsDataCon :: TyCon
- promotedGTDataCon :: TyCon
- promotedEQDataCon :: TyCon
- promotedLTDataCon :: TyCon
- promotedJustDataCon :: TyCon
- promotedNothingDataCon :: TyCon
- promotedFalseDataCon :: TyCon
- promotedTrueDataCon :: TyCon
- mkSumTy :: [Type] -> Type
- mkTupleTy1 :: Boxity -> [Type] -> Type
- mkTupleTy :: Boxity -> [Type] -> Type
- justDataCon :: DataCon
- nothingDataCon :: DataCon
- maybeTyCon :: TyCon
- consDataCon :: DataCon
- nilDataCon :: DataCon
- mkListTy :: Type -> Type
- ordGTDataConId :: Id
- ordEQDataConId :: Id
- ordLTDataConId :: Id
- ordGTDataCon :: DataCon
- ordEQDataCon :: DataCon
- ordLTDataCon :: DataCon
- orderingTyCon :: TyCon
- trueDataConId :: Id
- falseDataConId :: Id
- trueDataCon :: DataCon
- falseDataCon :: DataCon
- boolTyCon :: TyCon
- boolTy :: Type
- doubleDataCon :: DataCon
- doubleTyCon :: TyCon
- doubleTy :: Type
- floatDataCon :: DataCon
- floatTyCon :: TyCon
- floatTy :: Type
- word8DataCon :: DataCon
- word8TyCon :: TyCon
- word8Ty :: Type
- wordDataCon :: DataCon
- wordTyCon :: TyCon
- wordTy :: Type
- intDataCon :: DataCon
- intTyCon :: TyCon
- intTy :: Type
- stringTy :: Type
- charDataCon :: DataCon
- charTyCon :: TyCon
- charTy :: Type
- boxingDataCon_maybe :: TyCon -> Maybe DataCon
- liftedRepTy :: Type
- liftedRepDataCon :: DataCon
- sumRepDataConTyCon :: TyCon
- liftedTypeKindTyCon :: TyCon
- coercibleDataCon :: DataCon
- coercibleClass :: Class
- heqDataCon :: DataCon
- heqClass :: Class
- eqDataCon :: DataCon
- eqClass :: Class
- eqTyCon :: TyCon
- unboxedSumKind :: [Type] -> Kind
- sumDataCon :: ConTag -> Arity -> DataCon
- sumTyCon :: Arity -> TyCon
- unboxedUnitDataCon :: DataCon
- unboxedUnitTyCon :: TyCon
- pairTyCon :: TyCon
- unitDataConId :: Id
- unitDataCon :: DataCon
- unitTyConKey :: Unique
- unitTyCon :: TyCon
- tupleDataConName :: Boxity -> Arity -> Name
- tupleDataCon :: Boxity -> Arity -> DataCon
- promotedTupleDataCon :: Boxity -> Arity -> TyCon
- tupleTyCon :: Boxity -> Arity -> TyCon
- cTupleDataConNames :: [Name]
- cTupleDataConName :: Arity -> Name
- cTupleTyConNameArity_maybe :: Name -> Maybe Arity
- isCTupleTyConName :: Name -> Bool
- cTupleTyConNames :: [Name]
- cTupleTyConName :: Arity -> Name
- mkTupleStr :: Boxity -> Arity -> String
- isBuiltInOcc_maybe :: OccName -> Maybe Name
- typeToTypeKind :: Kind
- constraintKindTyCon :: TyCon
- typeSymbolKindCon :: TyCon
- typeNatKindCon :: TyCon
- consDataCon_RDR :: RdrName
- listTyCon_RDR :: RdrName
- intDataCon_RDR :: RdrName
- charTyCon_RDR :: RdrName
- intTyCon_RDR :: RdrName
- true_RDR :: RdrName
- false_RDR :: RdrName
- boolTyCon_RDR :: RdrName
- liftedTypeKindTyConName :: Name
- constraintKindTyConName :: Name
- makeRecoveryTyCon :: TyCon -> TyCon
- anyTy :: Type
- anyTyCon :: TyCon
- doubleTyConName :: Name
- floatTyConName :: Name
- word8TyConName :: Name
- wordTyConName :: Name
- justDataConName :: Name
- nothingDataConName :: Name
- maybeTyConName :: Name
- consDataConName :: Name
- nilDataConName :: Name
- listTyConName :: Name
- boolTyConName :: Name
- intTyConName :: Name
- charTyConName :: Name
- coercibleTyConName :: Name
- heqTyConName :: Name
- eqTyCon_RDR :: RdrName
- eqTyConName :: Name
- mkWiredInIdName :: Module -> FastString -> Unique -> Id -> Name
- mkWiredInTyConName :: BuiltInSyntax -> Module -> FastString -> Unique -> TyCon -> Name
- wiredInTyCons :: [TyCon]
- isNeverLevPolyId :: Id -> Bool
- transferPolyIdInfo :: Id -> [Var] -> Id -> Id
- zapStableUnfolding :: Id -> Id
- zapIdTailCallInfo :: Id -> Id
- zapIdUsedOnceInfo :: Id -> Id
- zapIdUsageEnvInfo :: Id -> Id
- zapIdUsageInfo :: Id -> Id
- zapIdDemandInfo :: Id -> Id
- zapFragileIdInfo :: Id -> Id
- zapLamIdInfo :: Id -> Id
- updOneShotInfo :: Id -> OneShotInfo -> Id
- setIdOneShotInfo :: Id -> OneShotInfo -> Id
- clearOneShotLambda :: Id -> Id
- setOneShotLambda :: Id -> Id
- isProbablyOneShotLambda :: Id -> Bool
- isStateHackType :: Type -> Bool
- typeOneShot :: Type -> OneShotInfo
- stateHackOneShot :: OneShotInfo
- isOneShotBndr :: Var -> Bool
- idStateHackOneShotInfo :: Id -> OneShotInfo
- idOneShotInfo :: Id -> OneShotInfo
- isConLikeId :: Id -> Bool
- idRuleMatchInfo :: Id -> RuleMatchInfo
- setInlineActivation :: Id -> Activation -> Id
- idInlineActivation :: Id -> Activation
- modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> Id
- setInlinePragma :: Id -> InlinePragma -> Id
- idInlinePragma :: Id -> InlinePragma
- zapIdOccInfo :: Id -> Id
- setIdOccInfo :: Id -> OccInfo -> Id
- idOccInfo :: Id -> OccInfo
- setIdCafInfo :: Id -> CafInfo -> Id
- idCafInfo :: Id -> CafInfo
- setIdSpecialisation :: Id -> RuleInfo -> Id
- idHasRules :: Id -> Bool
- idCoreRules :: Id -> [CoreRule]
- idSpecialisation :: Id -> RuleInfo
- setCaseBndrEvald :: StrictnessMark -> Id -> Id
- setIdDemandInfo :: Id -> Demand -> Id
- idDemandInfo :: Id -> Demand
- setIdUnfolding :: Id -> Unfolding -> Id
- realIdUnfolding :: Id -> Unfolding
- idUnfolding :: Id -> Unfolding
- isStrictId :: Id -> Bool
- zapIdStrictness :: Id -> Id
- setIdStrictness :: Id -> StrictSig -> Id
- idStrictness :: Id -> StrictSig
- isBottomingId :: Var -> Bool
- idFunRepArity :: Id -> RepArity
- setIdCallArity :: Id -> Arity -> Id
- idCallArity :: Id -> Arity
- setIdArity :: Id -> Arity -> Id
- idArity :: Id -> Arity
- asJoinId_maybe :: Id -> Maybe JoinArity -> Id
- zapJoinId :: Id -> Id
- asJoinId :: Id -> JoinArity -> JoinId
- idJoinArity :: JoinId -> JoinArity
- isDeadBinder :: Id -> Bool
- idIsFrom :: Module -> Id -> Bool
- isImplicitId :: Id -> Bool
- hasNoBinding :: Id -> Bool
- idDataCon :: Id -> DataCon
- isJoinId_maybe :: Var -> Maybe JoinArity
- isJoinId :: Var -> Bool
- isDataConId_maybe :: Id -> Maybe DataCon
- isDataConWrapId_maybe :: Id -> Maybe DataCon
- isDataConWrapId :: Id -> Bool
- isDataConWorkId_maybe :: Id -> Maybe DataCon
- isDataConWorkId :: Id -> Bool
- isFCallId_maybe :: Id -> Maybe ForeignCall
- isFCallId :: Id -> Bool
- isPrimOpId_maybe :: Id -> Maybe PrimOp
- isDFunId :: Id -> Bool
- isPrimOpId :: Id -> Bool
- isClassOpId_maybe :: Id -> Maybe Class
- isNaughtyRecordSelector :: Id -> Bool
- isPatSynRecordSelector :: Id -> Bool
- isDataConRecordSelector :: Id -> Bool
- isRecordSelector :: Id -> Bool
- recordSelectorTyCon :: Id -> RecSelParent
- mkTemplateLocalsNum :: Int -> [Type] -> [Id]
- mkTemplateLocals :: [Type] -> [Id]
- mkTemplateLocal :: Int -> Type -> Id
- mkWorkerId :: Unique -> Id -> Type -> Id
- mkUserLocalOrCoVar :: OccName -> Unique -> Type -> SrcSpan -> Id
- mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> Id
- mkSysLocalOrCoVarM :: MonadUnique m => FastString -> Type -> m Id
- mkSysLocalM :: MonadUnique m => FastString -> Type -> m Id
- mkSysLocalOrCoVar :: FastString -> Unique -> Type -> Id
- mkSysLocal :: FastString -> Unique -> Type -> Id
- mkExportedVanillaId :: Name -> Type -> Id
- mkExportedLocalId :: IdDetails -> Name -> Type -> Id
- mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id
- mkLocalIdOrCoVarWithInfo :: Name -> Type -> IdInfo -> Id
- mkLocalIdOrCoVar :: Name -> Type -> Id
- mkLocalCoVar :: Name -> Type -> CoVar
- mkLocalId :: Name -> Type -> Id
- mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id
- mkVanillaGlobal :: Name -> Type -> Id
- mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id
- maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id
- modifyIdInfo :: HasDebugCallStack => (IdInfo -> IdInfo) -> Id -> Id
- setIdInfo :: Id -> IdInfo -> Id
- localiseId :: Id -> Id
- setIdType :: Id -> Type -> Id
- setIdUnique :: Id -> Unique -> Id
- setIdName :: Id -> Name -> Id
- idType :: Id -> Kind
- idUnique :: Id -> Unique
- idName :: Id -> Name
- collectNAnnBndrs :: Int -> AnnExpr bndr annot -> ([bndr], AnnExpr bndr annot)
- collectAnnBndrs :: AnnExpr bndr annot -> ([bndr], AnnExpr bndr annot)
- deAnnBind :: AnnBind b annot -> Bind b
- deAnnAlt :: AnnAlt bndr annot -> Alt bndr
- deAnnotate' :: AnnExpr' bndr annot -> Expr bndr
- deAnnotate :: AnnExpr bndr annot -> Expr bndr
- collectAnnArgsTicks :: (Tickish Var -> Bool) -> AnnExpr b a -> (AnnExpr b a, [AnnExpr b a], [Tickish Var])
- collectAnnArgs :: AnnExpr b a -> (AnnExpr b a, [AnnExpr b a])
- valArgCount :: [Arg b] -> Int
- valBndrCount :: [CoreBndr] -> Int
- isTypeArg :: Expr b -> Bool
- isCoArg :: Expr b -> Bool
- isTyCoArg :: Expr b -> Bool
- isValArg :: Expr b -> Bool
- isRuntimeArg :: CoreExpr -> Bool
- isRuntimeVar :: Var -> Bool
- collectArgsTicks :: (Tickish Id -> Bool) -> Expr b -> (Expr b, [Arg b], [Tickish Id])
- stripNArgs :: Word -> Expr a -> Maybe (Expr a)
- collectArgs :: Expr b -> (Expr b, [Arg b])
- collectNBinders :: Int -> Expr b -> ([b], Expr b)
- collectTyAndValBinders :: CoreExpr -> ([TyVar], [Id], CoreExpr)
- collectTyBinders :: CoreExpr -> ([TyVar], CoreExpr)
- collectBinders :: Expr b -> ([b], Expr b)
- flattenBinds :: [Bind b] -> [(b, Expr b)]
- rhssOfAlts :: [Alt b] -> [Expr b]
- rhssOfBind :: Bind b -> [Expr b]
- bindersOfBinds :: [Bind b] -> [b]
- bindersOf :: Bind b -> [b]
- exprToCoercion_maybe :: CoreExpr -> Maybe Coercion
- exprToType :: CoreExpr -> Type
- applyTypeToArg :: Type -> CoreExpr -> Type
- varsToCoreExprs :: [CoreBndr] -> [Expr b]
- varToCoreExpr :: CoreBndr -> Expr b
- mkCoBind :: CoVar -> Coercion -> CoreBind
- mkTyBind :: TyVar -> Type -> CoreBind
- mkLetRec :: [(b, Expr b)] -> Expr b -> Expr b
- mkLetNonRec :: b -> Expr b -> Expr b -> Expr b
- mkLet :: Bind b -> Expr b -> Expr b
- mkLets :: [Bind b] -> Expr b -> Expr b
- mkLams :: [b] -> Expr b -> Expr b
- mkDoubleLitDouble :: Double -> Expr b
- mkDoubleLit :: Rational -> Expr b
- mkFloatLitFloat :: Float -> Expr b
- mkFloatLit :: Rational -> Expr b
- mkStringLit :: String -> Expr b
- mkCharLit :: Char -> Expr b
- mkInt64LitInt64 :: Int64 -> Expr b
- mkWord64LitWord64 :: Word64 -> Expr b
- mkWordLitWord :: DynFlags -> Word -> Expr b
- mkWordLit :: DynFlags -> Integer -> Expr b
- mkIntLitInt :: DynFlags -> Int -> Expr b
- mkIntLit :: DynFlags -> Integer -> Expr b
- mkTyArg :: Type -> Expr b
- mkConApp2 :: DataCon -> [Type] -> [Var] -> Expr b
- mkTyApps :: Expr b -> [Type] -> Expr b
- mkConApp :: DataCon -> [Arg b] -> Expr b
- mkVarApps :: Expr b -> [Var] -> Expr b
- mkCoApps :: Expr b -> [Coercion] -> Expr b
- mkApps :: Expr b -> [Arg b] -> Expr b
- deTagExpr :: TaggedExpr t -> CoreExpr
- cmpAltCon :: AltCon -> AltCon -> Ordering
- ltAlt :: (AltCon, a, b) -> (AltCon, a, b) -> Bool
- cmpAlt :: (AltCon, a, b) -> (AltCon, a, b) -> Ordering
- canUnfold :: Unfolding -> Bool
- isFragileUnfolding :: Unfolding -> Bool
- neverUnfoldGuidance :: UnfoldingGuidance -> Bool
- isBootUnfolding :: Unfolding -> Bool
- hasSomeUnfolding :: Unfolding -> Bool
- isStableUnfolding :: Unfolding -> Bool
- isCompulsoryUnfolding :: Unfolding -> Bool
- expandUnfolding_maybe :: Unfolding -> Maybe CoreExpr
- isExpandableUnfolding :: Unfolding -> Bool
- isCheapUnfolding :: Unfolding -> Bool
- isConLikeUnfolding :: Unfolding -> Bool
- isEvaldUnfolding :: Unfolding -> Bool
- isValueUnfolding :: Unfolding -> Bool
- otherCons :: Unfolding -> [AltCon]
- maybeUnfoldingTemplate :: Unfolding -> Maybe CoreExpr
- unfoldingTemplate :: Unfolding -> CoreExpr
- isStableSource :: UnfoldingSource -> Bool
- mkOtherCon :: [AltCon] -> Unfolding
- bootUnfolding :: Unfolding
- evaldUnfolding :: Unfolding
- noUnfolding :: Unfolding
- boringCxtNotOk :: Bool
- boringCxtOk :: Bool
- unSaturatedOk :: Bool
- needSaturated :: Bool
- setRuleIdName :: Name -> CoreRule -> CoreRule
- isLocalRule :: CoreRule -> Bool
- ruleIdName :: CoreRule -> Name
- ruleActivation :: CoreRule -> Activation
- ruleModule :: CoreRule -> Maybe Module
- ruleName :: CoreRule -> RuleName
- ruleArity :: CoreRule -> Int
- isAutoRule :: CoreRule -> Bool
- isBuiltinRule :: CoreRule -> Bool
- emptyRuleEnv :: RuleEnv
- mkRuleEnv :: RuleBase -> [Module] -> RuleEnv
- chooseOrphanAnchor :: NameSet -> IsOrphan
- notOrphan :: IsOrphan -> Bool
- isOrphan :: IsOrphan -> Bool
- tickishContains :: Eq b => Tickish b -> Tickish b -> Bool
- tickishPlace :: Tickish id -> TickishPlacement
- tickishIsCode :: Tickish id -> Bool
- mkNoScope :: Tickish id -> Tickish id
- mkNoCount :: Tickish id -> Tickish id
- tickishCanSplit :: Tickish id -> Bool
- tickishFloatable :: Tickish id -> Bool
- tickishScopesLike :: Tickish id -> TickishScoping -> Bool
- tickishScoped :: Tickish id -> TickishScoping
- tickishCounts :: Tickish id -> Bool
- data Expr b
- type Arg b = Expr b
- type Alt b = (AltCon, [b], Expr b)
- data AltCon
- data Bind b
- type InBndr = CoreBndr
- type InType = Type
- type InKind = Kind
- type InBind = CoreBind
- type InExpr = CoreExpr
- type InAlt = CoreAlt
- type InArg = CoreArg
- type InCoercion = Coercion
- type OutBndr = CoreBndr
- type OutType = Type
- type OutKind = Kind
- type OutCoercion = Coercion
- type OutBind = CoreBind
- type OutExpr = CoreExpr
- type OutAlt = CoreAlt
- type OutArg = CoreArg
- type MOutCoercion = MCoercion
- data Tickish id
- = ProfNote {
- profNoteCC :: CostCentre
- profNoteCount :: !Bool
- profNoteScope :: !Bool
- | HpcTick {
- tickModule :: Module
- tickId :: !Int
- | Breakpoint {
- breakpointId :: !Int
- breakpointFVs :: [id]
- | SourceNote { }
- = ProfNote {
- data TickishScoping
- data TickishPlacement
- data IsOrphan
- type RuleBase = NameEnv [CoreRule]
- data RuleEnv = RuleEnv {}
- data CoreRule
- = Rule { }
- | BuiltinRule { }
- type RuleFun = DynFlags -> InScopeEnv -> Id -> [CoreExpr] -> Maybe CoreExpr
- type InScopeEnv = (InScopeSet, IdUnfoldingFun)
- type IdUnfoldingFun = Id -> Unfolding
- data Unfolding
- = NoUnfolding
- | BootUnfolding
- | OtherCon [AltCon]
- | DFunUnfolding { }
- | CoreUnfolding { }
- data UnfoldingSource
- data UnfoldingGuidance
- = UnfWhen {
- ug_arity :: Arity
- ug_unsat_ok :: Bool
- ug_boring_ok :: Bool
- | UnfIfGoodArgs { }
- | UnfNever
- = UnfWhen {
- type CoreProgram = [CoreBind]
- type CoreBndr = Var
- type CoreExpr = Expr CoreBndr
- type CoreArg = Arg CoreBndr
- type CoreBind = Bind CoreBndr
- type CoreAlt = Alt CoreBndr
- data TaggedBndr t = TB CoreBndr t
- type TaggedBind t = Bind (TaggedBndr t)
- type TaggedExpr t = Expr (TaggedBndr t)
- type TaggedArg t = Arg (TaggedBndr t)
- type TaggedAlt t = Alt (TaggedBndr t)
- type AnnAlt bndr annot = (AltCon, [bndr], AnnExpr bndr annot)
- data AnnBind bndr annot = AnnNonRec bndr (AnnExpr bndr annot)
- conLikeIsInfix :: ConLike -> Bool
- conLikesWithFields :: [ConLike] -> [FieldLabelString] -> [ConLike]
- conLikeFieldType :: ConLike -> FieldLabelString -> Type
- conLikeFullSig :: ConLike -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, ThetaType, [Type], Type)
- conLikeResTy :: ConLike -> [Type] -> Type
- conLikeImplBangs :: ConLike -> [HsImplBang]
- conLikeWrapId_maybe :: ConLike -> Maybe Id
- conLikeStupidTheta :: ConLike -> ThetaType
- conLikeExTyCoVars :: ConLike -> [TyCoVar]
- conLikeInstOrigArgTys :: ConLike -> [Type] -> [Type]
- conLikeFieldLabels :: ConLike -> [FieldLabel]
- conLikeArity :: ConLike -> Arity
- buildSynTyCon :: Name -> [KnotTied TyConBinder] -> Kind -> [Role] -> KnotTied Type -> TyCon
- buildAlgTyCon :: Name -> [TyVar] -> [Role] -> Maybe CType -> ThetaType -> AlgTyConRhs -> Bool -> AlgTyConFlav -> TyCon
- splitDataProductType_maybe :: Type -> Maybe (TyCon, [Type], DataCon, [Type])
- promoteDataCon :: DataCon -> TyCon
- dataConUserTyVarsArePermuted :: DataCon -> Bool
- dataConCannotMatch :: [Type] -> DataCon -> Bool
- classDataCon :: Class -> DataCon
- specialPromotedDc :: DataCon -> Bool
- isVanillaDataCon :: DataCon -> Bool
- isUnboxedTupleCon :: DataCon -> Bool
- isTupleDataCon :: DataCon -> Bool
- dataConIdentity :: DataCon -> ByteString
- dataConRepArgTys :: DataCon -> [Type]
- dataConOrigArgTys :: DataCon -> [Type]
- dataConInstArgTys :: DataCon -> [Type] -> [Type]
- dataConUserType :: DataCon -> Type
- dataConOrigResTy :: DataCon -> Type
- dataConInstSig :: DataCon -> [Type] -> ([TyCoVar], ThetaType, [Type])
- dataConSig :: DataCon -> ([TyCoVar], ThetaType, [Type], Type)
- dataConBoxer :: DataCon -> Maybe DataConBoxer
- dataConImplBangs :: DataCon -> [HsImplBang]
- dataConRepStrictness :: DataCon -> [StrictnessMark]
- isNullaryRepDataCon :: DataCon -> Bool
- isNullarySrcDataCon :: DataCon -> Bool
- dataConRepArity :: DataCon -> Arity
- dataConSrcBangs :: DataCon -> [HsSrcBang]
- dataConFieldType_maybe :: DataCon -> FieldLabelString -> Maybe (FieldLabel, Type)
- dataConFieldType :: DataCon -> FieldLabelString -> Type
- dataConImplicitTyThings :: DataCon -> [TyThing]
- dataConWrapId :: DataCon -> Id
- dataConWrapId_maybe :: DataCon -> Maybe Id
- dataConWorkId :: DataCon -> Id
- dataConTheta :: DataCon -> ThetaType
- dataConEqSpec :: DataCon -> [EqSpec]
- dataConUnivAndExTyCoVars :: DataCon -> [TyCoVar]
- dataConUnivTyVars :: DataCon -> [TyVar]
- dataConIsInfix :: DataCon -> Bool
- dataConRepType :: DataCon -> Type
- dataConOrigTyCon :: DataCon -> TyCon
- dataConTagZ :: DataCon -> ConTagZ
- dataConTag :: DataCon -> ConTag
- mkDataCon :: Name -> Bool -> TyConRepName -> [HsSrcBang] -> [FieldLabel] -> [TyVar] -> [TyCoVar] -> [TyVarBinder] -> [EqSpec] -> KnotTied ThetaType -> [KnotTied Type] -> KnotTied Type -> RuntimeRepInfo -> KnotTied TyCon -> ConTag -> ThetaType -> Id -> DataConRep -> DataCon
- isMarkedStrict :: StrictnessMark -> Bool
- isSrcUnpacked :: SrcUnpackedness -> Bool
- isSrcStrict :: SrcStrictness -> Bool
- isBanged :: HsImplBang -> Bool
- eqHsBang :: HsImplBang -> HsImplBang -> Bool
- filterEqSpec :: [EqSpec] -> [TyVar] -> [TyVar]
- substEqSpec :: TCvSubst -> EqSpec -> EqSpec
- eqSpecPreds :: [EqSpec] -> ThetaType
- eqSpecPair :: EqSpec -> (TyVar, Type)
- eqSpecType :: EqSpec -> Type
- eqSpecTyVar :: EqSpec -> TyVar
- mkEqSpec :: TyVar -> Type -> EqSpec
- data HsSrcBang = HsSrcBang SourceText SrcUnpackedness SrcStrictness
- data HsImplBang
- data SrcStrictness
- data SrcUnpackedness
- data StrictnessMark
- isEqPrimPred :: PredType -> Bool
- isEqPred :: PredType -> Bool
- isClassPred :: PredType -> Bool
- isEvVarType :: Type -> Bool
- getClassPredTys_maybe :: PredType -> Maybe (Class, [Type])
- instanceCantMatch :: [Maybe Name] -> [Maybe Name] -> Bool
- roughMatchTcs :: [Type] -> [Maybe Name]
- hsOverLitNeedsParens :: PprPrec -> HsOverLit x -> Bool
- hsLitNeedsParens :: PprPrec -> HsLit x -> Bool
- pmPprHsLit :: forall (x :: Pass). HsLit (GhcPass x) -> SDoc
- pp_st_suffix :: SourceText -> SDoc -> SDoc -> SDoc
- convertLit :: ConvertIdX a b => HsLit a -> HsLit b
- overLitType :: HsOverLit GhcTc -> Type
- negateOverLitVal :: OverLitVal -> OverLitVal
- data HsLit x
- = HsChar (XHsChar x) Char
- | HsCharPrim (XHsCharPrim x) Char
- | HsString (XHsString x) FastString
- | HsStringPrim (XHsStringPrim x) ByteString
- | HsInt (XHsInt x) IntegralLit
- | HsIntPrim (XHsIntPrim x) Integer
- | HsWordPrim (XHsWordPrim x) Integer
- | HsInt64Prim (XHsInt64Prim x) Integer
- | HsWord64Prim (XHsWord64Prim x) Integer
- | HsInteger (XHsInteger x) Integer Type
- | HsRat (XHsRat x) FractionalLit Type
- | HsFloatPrim (XHsFloatPrim x) FractionalLit
- | HsDoublePrim (XHsDoublePrim x) FractionalLit
- | XLit (XXLit x)
- data HsOverLit p
- = OverLit {
- ol_ext :: XOverLit p
- ol_val :: OverLitVal
- ol_witness :: HsExpr p
- | XOverLit (XXOverLit p)
- = OverLit {
- data OverLitTc = OverLitTc {
- ol_rebindable :: Bool
- ol_type :: Type
- data OverLitVal
- pprLiteral :: (SDoc -> SDoc) -> Literal -> SDoc
- absentLiteralOf :: TyCon -> Maybe Literal
- literalType :: Literal -> Type
- litIsLifted :: Literal -> Bool
- litFitsInChar :: Literal -> Bool
- litIsDupable :: DynFlags -> Literal -> Bool
- litIsTrivial :: Literal -> Bool
- rubbishLit :: Literal
- nullAddrLit :: Literal
- double2FloatLit :: Literal -> Literal
- float2DoubleLit :: Literal -> Literal
- int2DoubleLit :: Literal -> Literal
- double2IntLit :: Literal -> Literal
- int2FloatLit :: Literal -> Literal
- float2IntLit :: Literal -> Literal
- int2CharLit :: Literal -> Literal
- char2IntLit :: Literal -> Literal
- narrow32WordLit :: Literal -> Literal
- narrow16WordLit :: Literal -> Literal
- narrow8WordLit :: Literal -> Literal
- narrow32IntLit :: Literal -> Literal
- narrow16IntLit :: Literal -> Literal
- narrow8IntLit :: Literal -> Literal
- narrowLit :: Integral a => Proxy a -> Literal -> Literal
- int2WordLit :: DynFlags -> Literal -> Literal
- word2IntLit :: DynFlags -> Literal -> Literal
- isLitValue :: Literal -> Bool
- mapLitValue :: DynFlags -> (Integer -> Integer) -> Literal -> Literal
- isLitValue_maybe :: Literal -> Maybe Integer
- litValue :: Literal -> Integer
- isZeroLit :: Literal -> Bool
- inCharRange :: Char -> Bool
- inWordRange :: DynFlags -> Integer -> Bool
- inIntRange :: DynFlags -> Integer -> Bool
- mkLitNatural :: Integer -> Type -> Literal
- mkLitInteger :: Integer -> Type -> Literal
- mkLitString :: String -> Literal
- mkLitChar :: Char -> Literal
- mkLitDouble :: Rational -> Literal
- mkLitFloat :: Rational -> Literal
- mkLitWord64Wrap :: DynFlags -> Integer -> Literal
- mkLitWord64 :: Integer -> Literal
- mkLitInt64Wrap :: DynFlags -> Integer -> Literal
- mkLitInt64 :: Integer -> Literal
- mkLitWordWrapC :: DynFlags -> Integer -> (Literal, Bool)
- mkLitWordWrap :: DynFlags -> Integer -> Literal
- mkLitWord :: DynFlags -> Integer -> Literal
- mkLitIntWrapC :: DynFlags -> Integer -> (Literal, Bool)
- mkLitIntWrap :: DynFlags -> Integer -> Literal
- mkLitInt :: DynFlags -> Integer -> Literal
- mkLitNumber :: DynFlags -> LitNumType -> Integer -> Type -> Literal
- litNumCheckRange :: DynFlags -> LitNumType -> Integer -> Bool
- mkLitNumberWrap :: DynFlags -> LitNumType -> Integer -> Type -> Literal
- litNumIsSigned :: LitNumType -> Bool
- data Literal
- data LitNumType
- tyConAppNeedsKindSig :: Bool -> TyCon -> Int -> Bool
- classifiesTypeWithValues :: Kind -> Bool
- isKindLevPoly :: Kind -> Bool
- isConstraintKindCon :: TyCon -> Bool
- setJoinResTy :: Int -> Type -> Type -> Type
- modifyJoinResTy :: Int -> (Type -> Type) -> Type -> Type
- splitVisVarsOfTypes :: [Type] -> Pair TyCoVarSet
- splitVisVarsOfType :: Type -> Pair TyCoVarSet
- synTyConResKind :: TyCon -> Kind
- tyConsOfType :: Type -> UniqSet TyCon
- occCheckExpand :: [Var] -> Type -> Maybe Type
- resultIsLevPoly :: Type -> Bool
- isTypeLevPoly :: Type -> Bool
- tcReturnsConstraintKind :: Kind -> Bool
- tcIsRuntimeTypeKind :: Kind -> Bool
- tcIsLiftedTypeKind :: Kind -> Bool
- tcIsConstraintKind :: Kind -> Bool
- tcTypeKind :: HasDebugCallStack => Type -> Kind
- nonDetCmpTc :: TyCon -> TyCon -> Ordering
- nonDetCmpTypesX :: RnEnv2 -> [Type] -> [Type] -> Ordering
- nonDetCmpTypeX :: RnEnv2 -> Type -> Type -> Ordering
- nonDetCmpTypes :: [Type] -> [Type] -> Ordering
- nonDetCmpType :: Type -> Type -> Ordering
- eqVarBndrs :: RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2
- eqTypes :: [Type] -> [Type] -> Bool
- eqTypeX :: RnEnv2 -> Type -> Type -> Bool
- seqTypes :: [Type] -> ()
- seqType :: Type -> ()
- isValidJoinPointType :: JoinArity -> Type -> Bool
- isPrimitiveType :: Type -> Bool
- isStrictType :: HasDebugCallStack => Type -> Bool
- isDataFamilyAppType :: Type -> Bool
- isAlgType :: Type -> Bool
- isUnboxedSumType :: Type -> Bool
- isUnboxedTupleType :: Type -> Bool
- getRuntimeRep :: HasDebugCallStack => Type -> Type
- getRuntimeRep_maybe :: HasDebugCallStack => Type -> Maybe Type
- dropRuntimeRepArgs :: [Type] -> [Type]
- isRuntimeRepKindedTy :: Type -> Bool
- mightBeUnliftedType :: Type -> Bool
- isUnliftedType :: HasDebugCallStack => Type -> Bool
- isLiftedType_maybe :: HasDebugCallStack => Type -> Maybe Bool
- isCoVarType :: Type -> Bool
- isFamFreeTy :: Type -> Bool
- coAxNthLHS :: forall (br :: BranchFlag). CoAxiom br -> Int -> Type
- mkFamilyTyConApp :: TyCon -> [Type] -> Type
- closeOverKindsDSet :: DTyVarSet -> DTyVarSet
- closeOverKindsList :: [TyVar] -> [TyVar]
- closeOverKindsFV :: [TyVar] -> FV
- closeOverKinds :: TyVarSet -> TyVarSet
- binderRelevantType_maybe :: TyCoBinder -> Maybe Type
- tyBinderType :: TyBinder -> Type
- tyCoBinderType :: TyCoBinder -> Type
- tyCoBinderVar_maybe :: TyCoBinder -> Maybe TyCoVar
- isAnonTyCoBinder :: TyCoBinder -> Bool
- mkAnonBinder :: AnonArgFlag -> Type -> TyCoBinder
- isTauTy :: Type -> Bool
- appTyArgFlags :: Type -> [Type] -> [ArgFlag]
- tyConArgFlags :: TyCon -> [Type] -> [ArgFlag]
- partitionInvisibles :: [(a, ArgFlag)] -> ([a], [a])
- filterOutInferredTypes :: TyCon -> [Type] -> [Type]
- filterOutInvisibleTypes :: TyCon -> [Type] -> [Type]
- splitPiTysInvisibleN :: Int -> Type -> ([TyCoBinder], Type)
- splitPiTysInvisible :: Type -> ([TyCoBinder], Type)
- invisibleTyBndrCount :: Type -> Int
- splitForAllVarBndrs :: Type -> ([TyCoVarBinder], Type)
- splitPiTys :: Type -> ([TyCoBinder], Type)
- splitPiTy :: Type -> (TyCoBinder, Type)
- splitPiTy_maybe :: Type -> Maybe (TyCoBinder, Type)
- splitForAllTy_co_maybe :: Type -> Maybe (TyCoVar, Type)
- splitForAllTy_ty_maybe :: Type -> Maybe (TyCoVar, Type)
- splitForAllTy_maybe :: Type -> Maybe (TyCoVar, Type)
- dropForAlls :: Type -> Type
- splitForAllTy :: Type -> (TyCoVar, Type)
- isFunTy :: Type -> Bool
- isPiTy :: Type -> Bool
- isForAllTy_co :: Type -> Bool
- isForAllTy_ty :: Type -> Bool
- isForAllTy :: Type -> Bool
- splitForAllTysSameVis :: ArgFlag -> Type -> ([TyCoVar], Type)
- splitForAllTys :: Type -> ([TyCoVar], Type)
- mkTyConBindersPreferAnon :: [TyVar] -> TyCoVarSet -> [TyConBinder]
- mkLamTypes :: [Var] -> Type -> Type
- mkLamType :: Var -> Type -> Type
- mkVisForAllTys :: [TyVar] -> Type -> Type
- mkSpecForAllTys :: [TyVar] -> Type -> Type
- mkSpecForAllTy :: TyVar -> Type -> Type
- mkInvForAllTys :: [TyVar] -> Type -> Type
- mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type
- mkInvForAllTy :: TyVar -> Type -> Type
- mkTyCoInvForAllTy :: TyCoVar -> Type -> Type
- stripCoercionTy :: Type -> Coercion
- isCoercionTy_maybe :: Type -> Maybe Coercion
- mkCoercionTy :: Coercion -> Type
- discardCast :: Type -> Type
- tyConBindersTyCoBinders :: [TyConBinder] -> [TyCoBinder]
- splitCastTy_maybe :: Type -> Maybe (Type, Coercion)
- newTyConInstRhs :: TyCon -> [Type] -> Type
- nextRole :: Type -> Role
- splitListTyConApp_maybe :: Type -> Maybe Type
- repSplitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type])
- tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type])
- splitTyConApp :: Type -> (TyCon, [Type])
- tyConAppArgN :: Int -> Type -> Type
- tyConAppArgs :: Type -> [Type]
- tyConAppArgs_maybe :: Type -> Maybe [Type]
- tyConAppTyCon :: Type -> TyCon
- tyConAppTyCon_maybe :: Type -> Maybe TyCon
- tyConAppTyConPicky_maybe :: Type -> Maybe TyCon
- mkTyConApp :: TyCon -> [Type] -> Type
- applyTysX :: [TyVar] -> Type -> [Type] -> Type
- piResultTys :: HasDebugCallStack => Type -> [Type] -> Type
- funArgTy :: Type -> Type
- funResultTy :: Type -> Type
- splitFunTys :: Type -> ([Type], Type)
- splitFunTy_maybe :: Type -> Maybe (Type, Type)
- splitFunTy :: Type -> (Type, Type)
- pprUserTypeErrorTy :: Type -> SDoc
- userTypeError_maybe :: Type -> Maybe Type
- isLitTy :: Type -> Maybe TyLit
- isStrLitTy :: Type -> Maybe FastString
- mkStrLitTy :: FastString -> Type
- isNumLitTy :: Type -> Maybe Integer
- mkNumLitTy :: Integer -> Type
- repSplitAppTys :: HasDebugCallStack => Type -> (Type, [Type])
- splitAppTys :: Type -> (Type, [Type])
- splitAppTy :: Type -> (Type, Type)
- tcRepSplitAppTy_maybe :: Type -> Maybe (Type, Type)
- repSplitAppTy_maybe :: HasDebugCallStack => Type -> Maybe (Type, Type)
- splitAppTy_maybe :: Type -> Maybe (Type, Type)
- mkAppTys :: Type -> [Type] -> Type
- repGetTyVar_maybe :: Type -> Maybe TyVar
- getCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN)
- getTyVar_maybe :: Type -> Maybe TyVar
- isTyVarTy :: Type -> Bool
- getTyVar :: String -> Type -> TyVar
- mapCoercion :: Monad m => TyCoMapper env m -> env -> Coercion -> m Coercion
- mapType :: Monad m => TyCoMapper env m -> env -> Type -> m Type
- isRuntimeRepVar :: TyVar -> Bool
- isUnliftedRuntimeRep :: Type -> Bool
- isUnliftedTypeKind :: Kind -> Bool
- isLiftedRuntimeRep :: Type -> Bool
- kindRep_maybe :: HasDebugCallStack => Kind -> Maybe Type
- kindRep :: HasDebugCallStack => Kind -> Type
- expandTypeSynonyms :: Type -> Type
- data TyCoMapper env (m :: Type -> Type) = TyCoMapper {}
- cloneTyVarBndrs :: TCvSubst -> [TyVar] -> UniqSupply -> (TCvSubst, [TyVar])
- cloneTyVarBndr :: TCvSubst -> TyVar -> Unique -> (TCvSubst, TyVar)
- substVarBndrs :: HasCallStack => TCvSubst -> [TyCoVar] -> (TCvSubst, [TyCoVar])
- substVarBndr :: HasCallStack => TCvSubst -> TyCoVar -> (TCvSubst, TyCoVar)
- substTyVarBndrs :: HasCallStack => TCvSubst -> [TyVar] -> (TCvSubst, [TyVar])
- substTyVarBndr :: HasCallStack => TCvSubst -> TyVar -> (TCvSubst, TyVar)
- substCoUnchecked :: TCvSubst -> Coercion -> Coercion
- lookupTyVar :: TCvSubst -> TyVar -> Maybe Type
- substTyVars :: TCvSubst -> [TyVar] -> [Type]
- substTyVar :: TCvSubst -> TyVar -> Type
- substThetaUnchecked :: TCvSubst -> ThetaType -> ThetaType
- substTheta :: HasCallStack => TCvSubst -> ThetaType -> ThetaType
- substTysUnchecked :: TCvSubst -> [Type] -> [Type]
- substTys :: HasCallStack => TCvSubst -> [Type] -> [Type]
- substTyUnchecked :: TCvSubst -> Type -> Type
- substTy :: HasCallStack => TCvSubst -> Type -> Type
- substTyAddInScope :: TCvSubst -> Type -> Type
- substTysWith :: [TyVar] -> [Type] -> [Type] -> [Type]
- substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion
- substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type
- substTyWith :: HasCallStack => [TyVar] -> [Type] -> Type -> Type
- zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv
- zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv
- mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst
- zipTCvSubst :: HasDebugCallStack => [TyCoVar] -> [Type] -> TCvSubst
- zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> TCvSubst
- unionTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst
- extendTCvSubstList :: TCvSubst -> [Var] -> [Type] -> TCvSubst
- extendTvSubstList :: TCvSubst -> [Var] -> [Type] -> TCvSubst
- extendTvSubstAndInScope :: TCvSubst -> TyVar -> Type -> TCvSubst
- extendCvSubst :: TCvSubst -> CoVar -> Coercion -> TCvSubst
- extendTvSubstWithClone :: TCvSubst -> TyVar -> TyVar -> TCvSubst
- extendTvSubstBinderAndInScope :: TCvSubst -> TyCoBinder -> Type -> TCvSubst
- extendTvSubst :: TCvSubst -> TyVar -> Type -> TCvSubst
- extendTCvSubstWithClone :: TCvSubst -> TyCoVar -> TyCoVar -> TCvSubst
- extendTCvSubst :: TCvSubst -> TyCoVar -> Type -> TCvSubst
- extendTCvInScopeSet :: TCvSubst -> VarSet -> TCvSubst
- extendTCvInScopeList :: TCvSubst -> [Var] -> TCvSubst
- extendTCvInScope :: TCvSubst -> Var -> TCvSubst
- zapTCvSubst :: TCvSubst -> TCvSubst
- setTvSubstEnv :: TCvSubst -> TvSubstEnv -> TCvSubst
- notElemTCvSubst :: Var -> TCvSubst -> Bool
- isInScope :: Var -> TCvSubst -> Bool
- getTCvSubstRangeFVs :: TCvSubst -> VarSet
- getTCvInScope :: TCvSubst -> InScopeSet
- getTvSubstEnv :: TCvSubst -> TvSubstEnv
- mkTCvSubst :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> TCvSubst
- isEmptyTCvSubst :: TCvSubst -> Bool
- mkEmptyTCvSubst :: InScopeSet -> TCvSubst
- emptyTCvSubst :: TCvSubst
- composeTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst
- composeTCvSubstEnv :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv)
- emptyTvSubstEnv :: TvSubstEnv
- data TCvSubst = TCvSubst InScopeSet TvSubstEnv CvSubstEnv
- type TvSubstEnv = TyVarEnv Type
- pprTypeApp :: TyCon -> [Type] -> SDoc
- pprForAll :: [TyCoVarBinder] -> SDoc
- pprThetaArrowTy :: ThetaType -> SDoc
- pprParendType :: Type -> SDoc
- tidyKind :: TidyEnv -> Kind -> Kind
- tidyOpenKind :: TidyEnv -> Kind -> (TidyEnv, Kind)
- tidyTopType :: Type -> Type
- tidyOpenType :: TidyEnv -> Type -> (TidyEnv, Type)
- tidyOpenTypes :: TidyEnv -> [Type] -> (TidyEnv, [Type])
- tidyType :: TidyEnv -> Type -> Type
- tidyTypes :: TidyEnv -> [Type] -> [Type]
- tidyTyCoVarOcc :: TidyEnv -> TyCoVar -> TyCoVar
- tidyOpenTyCoVar :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar)
- tidyOpenTyCoVars :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar])
- tidyFreeTyCoVars :: TidyEnv -> [TyCoVar] -> TidyEnv
- tidyTyCoVarBinders :: TidyEnv -> [VarBndr TyCoVar vis] -> (TidyEnv, [VarBndr TyCoVar vis])
- tidyTyCoVarBinder :: TidyEnv -> VarBndr TyCoVar vis -> (TidyEnv, VarBndr TyCoVar vis)
- tidyVarBndr :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar)
- tidyVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar])
- tyCoVarsOfTypesWellScoped :: [Type] -> [TyVar]
- tyCoVarsOfTypeWellScoped :: Type -> [TyVar]
- scopedSort :: [TyCoVar] -> [TyCoVar]
- noFreeVarsOfType :: Type -> Bool
- coVarsOfTypes :: [Type] -> TyCoVarSet
- coVarsOfType :: Type -> CoVarSet
- tyCoFVsVarBndr :: Var -> FV -> FV
- tyCoFVsVarBndrs :: [Var] -> FV -> FV
- tyCoFVsBndr :: TyCoVarBinder -> FV -> FV
- tyCoFVsOfType :: Type -> FV
- tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet
- tyCoVarsOfTypes :: [Type] -> TyCoVarSet
- tyCoVarsOfType :: Type -> TyCoVarSet
- doubleX8PrimTyCon :: TyCon
- doubleX8PrimTy :: Type
- floatX16PrimTyCon :: TyCon
- floatX16PrimTy :: Type
- doubleX4PrimTyCon :: TyCon
- doubleX4PrimTy :: Type
- floatX8PrimTyCon :: TyCon
- floatX8PrimTy :: Type
- doubleX2PrimTyCon :: TyCon
- doubleX2PrimTy :: Type
- floatX4PrimTyCon :: TyCon
- floatX4PrimTy :: Type
- word64X8PrimTyCon :: TyCon
- word64X8PrimTy :: Type
- word32X16PrimTyCon :: TyCon
- word32X16PrimTy :: Type
- word16X32PrimTyCon :: TyCon
- word16X32PrimTy :: Type
- word8X64PrimTyCon :: TyCon
- word8X64PrimTy :: Type
- word64X4PrimTyCon :: TyCon
- word64X4PrimTy :: Type
- word32X8PrimTyCon :: TyCon
- word32X8PrimTy :: Type
- word16X16PrimTyCon :: TyCon
- word16X16PrimTy :: Type
- word8X32PrimTyCon :: TyCon
- word8X32PrimTy :: Type
- word64X2PrimTyCon :: TyCon
- word64X2PrimTy :: Type
- word32X4PrimTyCon :: TyCon
- word32X4PrimTy :: Type
- word16X8PrimTyCon :: TyCon
- word16X8PrimTy :: Type
- word8X16PrimTyCon :: TyCon
- word8X16PrimTy :: Type
- int64X8PrimTyCon :: TyCon
- int64X8PrimTy :: Type
- int32X16PrimTyCon :: TyCon
- int32X16PrimTy :: Type
- int16X32PrimTyCon :: TyCon
- int16X32PrimTy :: Type
- int8X64PrimTyCon :: TyCon
- int8X64PrimTy :: Type
- int64X4PrimTyCon :: TyCon
- int64X4PrimTy :: Type
- int32X8PrimTyCon :: TyCon
- int32X8PrimTy :: Type
- int16X16PrimTyCon :: TyCon
- int16X16PrimTy :: Type
- int8X32PrimTyCon :: TyCon
- int8X32PrimTy :: Type
- int64X2PrimTyCon :: TyCon
- int64X2PrimTy :: Type
- int32X4PrimTyCon :: TyCon
- int32X4PrimTy :: Type
- int16X8PrimTyCon :: TyCon
- int16X8PrimTy :: Type
- int8X16PrimTyCon :: TyCon
- int8X16PrimTy :: Type
- threadIdPrimTyCon :: TyCon
- threadIdPrimTy :: Type
- mkWeakPrimTy :: Type -> Type
- weakPrimTyCon :: TyCon
- bcoPrimTyCon :: TyCon
- bcoPrimTy :: Type
- compactPrimTy :: Type
- compactPrimTyCon :: TyCon
- mkStableNamePrimTy :: Type -> Type
- stableNamePrimTyCon :: TyCon
- mkStablePtrPrimTy :: Type -> Type
- stablePtrPrimTyCon :: TyCon
- mkTVarPrimTy :: Type -> Type -> Type
- tVarPrimTyCon :: TyCon
- mkMVarPrimTy :: Type -> Type -> Type
- mVarPrimTyCon :: TyCon
- mkMutVarPrimTy :: Type -> Type -> Type
- mutVarPrimTyCon :: TyCon
- mkSmallMutableArrayPrimTy :: Type -> Type -> Type
- mkMutableArrayArrayPrimTy :: Type -> Type
- mkMutableByteArrayPrimTy :: Type -> Type
- mkMutableArrayPrimTy :: Type -> Type -> Type
- mkSmallArrayPrimTy :: Type -> Type
- mkArrayArrayPrimTy :: Type
- byteArrayPrimTy :: Type
- mkArrayPrimTy :: Type -> Type
- smallMutableArrayPrimTyCon :: TyCon
- smallArrayPrimTyCon :: TyCon
- mutableArrayArrayPrimTyCon :: TyCon
- arrayArrayPrimTyCon :: TyCon
- byteArrayPrimTyCon :: TyCon
- mutableByteArrayPrimTyCon :: TyCon
- mutableArrayPrimTyCon :: TyCon
- arrayPrimTyCon :: TyCon
- equalityTyCon :: Role -> TyCon
- eqPhantPrimTyCon :: TyCon
- eqReprPrimTyCon :: TyCon
- eqPrimTyCon :: TyCon
- proxyPrimTyCon :: TyCon
- mkProxyPrimTy :: Type -> Type -> Type
- voidPrimTyCon :: TyCon
- voidPrimTy :: Type
- realWorldStatePrimTy :: Type
- realWorldTy :: Type
- realWorldTyCon :: TyCon
- statePrimTyCon :: TyCon
- mkStatePrimTy :: Type -> Type
- doublePrimTyCon :: TyCon
- doublePrimTy :: Type
- floatPrimTyCon :: TyCon
- floatPrimTy :: Type
- addrPrimTyCon :: TyCon
- addrPrimTy :: Type
- word64PrimTyCon :: TyCon
- word64PrimTy :: Type
- word32PrimTyCon :: TyCon
- word32PrimTy :: Type
- word16PrimTyCon :: TyCon
- word16PrimTy :: Type
- word8PrimTyCon :: TyCon
- word8PrimTy :: Type
- wordPrimTyCon :: TyCon
- wordPrimTy :: Type
- int64PrimTyCon :: TyCon
- int64PrimTy :: Type
- int32PrimTyCon :: TyCon
- int32PrimTy :: Type
- int16PrimTyCon :: TyCon
- int16PrimTy :: Type
- int8PrimTyCon :: TyCon
- int8PrimTy :: Type
- intPrimTyCon :: TyCon
- intPrimTy :: Type
- charPrimTyCon :: TyCon
- charPrimTy :: Type
- primRepToRuntimeRep :: PrimRep -> Type
- tYPE :: Type -> Type
- mkPrimTyConName :: FastString -> Unique -> TyCon -> Name
- tYPETyConName :: Name
- tYPETyCon :: TyCon
- funTyCon :: TyCon
- funTyConName :: Name
- openBetaTy :: Type
- openAlphaTy :: Type
- openBetaTyVar :: TyVar
- openAlphaTyVar :: TyVar
- runtimeRep2Ty :: Type
- runtimeRep1Ty :: Type
- runtimeRep2TyVar :: TyVar
- runtimeRep1TyVar :: TyVar
- alphaTyUnliftedRep :: Type
- alphaTysUnliftedRep :: [Type]
- alphaTyVarUnliftedRep :: TyVar
- alphaTyVarsUnliftedRep :: [TyVar]
- deltaTy :: Type
- gammaTy :: Type
- betaTy :: Type
- alphaTy :: Type
- alphaTys :: [Type]
- deltaTyVar :: TyVar
- gammaTyVar :: TyVar
- betaTyVar :: TyVar
- alphaTyVar :: TyVar
- alphaTyVars :: [TyVar]
- mkTemplateAnonTyConBinders :: [Kind] -> [TyConBinder]
- mkTemplateKindTyConBinders :: [Kind] -> [TyConBinder]
- mkTemplateKiTyVar :: Kind -> (Kind -> [Kind]) -> [TyVar]
- mkTemplateKiTyVars :: [Kind] -> ([Kind] -> [Kind]) -> [TyVar]
- mkTemplateTyConBinders :: [Kind] -> ([Kind] -> [Kind]) -> [TyConBinder]
- mkTemplateTyVars :: [Kind] -> [TyVar]
- mkTemplateTyVarsFrom :: Int -> [Kind] -> [TyVar]
- mkTemplateKindVars :: [Kind] -> [TyVar]
- doublePrimTyConName :: Name
- floatPrimTyConName :: Name
- addrPrimTyConName :: Name
- word64PrimTyConName :: Name
- word32PrimTyConName :: Name
- word16PrimTyConName :: Name
- word8PrimTyConName :: Name
- wordPrimTyConName :: Name
- int64PrimTyConName :: Name
- int32PrimTyConName :: Name
- int16PrimTyConName :: Name
- int8PrimTyConName :: Name
- intPrimTyConName :: Name
- charPrimTyConName :: Name
- exposedPrimTyCons :: [TyCon]
- unexposedPrimTyCons :: [TyCon]
- primTyCons :: [TyCon]
- provSize :: UnivCoProvenance -> Int
- coercionSize :: Coercion -> Int
- typeSize :: Type -> Int
- setCoHoleCoVar :: CoercionHole -> CoVar -> CoercionHole
- coHoleCoVar :: CoercionHole -> CoVar
- mkTyConTy :: TyCon -> Type
- mkPiTys :: [TyCoBinder] -> Type -> Type
- mkPiTy :: TyCoBinder -> Type -> Type
- mkForAllTys :: [TyCoVarBinder] -> Type -> Type
- mkInvisFunTys :: [Type] -> Type -> Type
- mkVisFunTys :: [Type] -> Type -> Type
- mkInvisFunTy :: Type -> Type -> Type
- mkVisFunTy :: Type -> Type -> Type
- mkTyCoVarTys :: [TyCoVar] -> [Type]
- mkTyCoVarTy :: TyCoVar -> Type
- mkTyVarTys :: [TyVar] -> [Type]
- mkTyVarTy :: TyVar -> Type
- isTyBinder :: TyCoBinder -> Bool
- isNamedBinder :: TyCoBinder -> Bool
- isVisibleBinder :: TyCoBinder -> Bool
- isInvisibleBinder :: TyCoBinder -> Bool
- delBinderVar :: VarSet -> TyCoVarBinder -> VarSet
- tyThingCategory :: TyThing -> String
- pprTyThingCategory :: TyThing -> SDoc
- pprShortTyThing :: TyThing -> SDoc
- type KindOrType = Type
- type KnotTied ty = ty
- type TyBinder = TyCoBinder
- type CoercionR = Coercion
- type CoercionP = Coercion
- type KindCoercion = CoercionN
- type MCoercionR = MCoercion
- data CoercionHole = CoercionHole {}
- isCoercionTy :: Type -> Bool
- mkAppTy :: Type -> Type -> Type
- mkCastTy :: Type -> Coercion -> Type
- piResultTy :: HasDebugCallStack => Type -> Type -> Type
- eqType :: Type -> Type -> Bool
- coreView :: Type -> Maybe Type
- tcView :: Type -> Maybe Type
- isRuntimeRepTy :: Type -> Bool
- isLiftedTypeKind :: Kind -> Bool
- splitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type])
- partitionInvisibleTypes :: TyCon -> [Type] -> ([Type], [Type])
- tyConSkolem :: TyCon -> Bool
- checkRecTc :: RecTcChecker -> TyCon -> Maybe RecTcChecker
- setRecTcMaxBound :: Int -> RecTcChecker -> RecTcChecker
- defaultRecTcMaxBound :: Int
- initRecTc :: RecTcChecker
- pprPromotionQuote :: TyCon -> SDoc
- tcFlavourIsOpen :: TyConFlavour -> Bool
- tyConFlavour :: TyCon -> TyConFlavour
- mkTyConTagMap :: TyCon -> NameEnv ConTag
- tyConRuntimeRepInfo :: TyCon -> RuntimeRepInfo
- tyConFamilyCoercion_maybe :: TyCon -> Maybe (CoAxiom Unbranched)
- tyConFamInst_maybe :: TyCon -> Maybe (TyCon, [Type])
- tyConFamInstSig_maybe :: TyCon -> Maybe (TyCon, [Type], CoAxiom Unbranched)
- isFamInstTyCon :: TyCon -> Bool
- tyConATs :: TyCon -> [TyCon]
- tyConClass_maybe :: TyCon -> Maybe Class
- isClassTyCon :: TyCon -> Bool
- famTyConFlav_maybe :: TyCon -> Maybe FamTyConFlav
- synTyConRhs_maybe :: TyCon -> Maybe Type
- synTyConDefn_maybe :: TyCon -> Maybe ([TyVar], Type)
- tyConStupidTheta :: TyCon -> [PredType]
- newTyConDataCon_maybe :: TyCon -> Maybe DataCon
- newTyConCo :: TyCon -> CoAxiom Unbranched
- newTyConCo_maybe :: TyCon -> Maybe (CoAxiom Unbranched)
- newTyConEtadRhs :: TyCon -> ([TyVar], Type)
- newTyConEtadArity :: TyCon -> Int
- newTyConRhs :: TyCon -> ([TyVar], Type)
- tyConRoles :: TyCon -> [Role]
- tyConFamilyResVar_maybe :: TyCon -> Maybe Name
- algTyConRhs :: TyCon -> AlgTyConRhs
- tyConFamilySize :: TyCon -> Int
- tyConSingleAlgDataCon_maybe :: TyCon -> Maybe DataCon
- tyConSingleDataCon :: TyCon -> DataCon
- tyConSingleDataCon_maybe :: TyCon -> Maybe DataCon
- tyConDataCons_maybe :: TyCon -> Maybe [DataCon]
- tyConDataCons :: TyCon -> [DataCon]
- isTyConWithSrcDataCons :: TyCon -> Bool
- expandSynTyCon_maybe :: TyCon -> [tyco] -> Maybe ([(TyVar, tyco)], Type, [tyco])
- isTcLevPoly :: TyCon -> Bool
- setTcTyConKind :: TyCon -> Kind -> TyCon
- isTcTyCon :: TyCon -> Bool
- tyConCType_maybe :: TyCon -> Maybe CType
- isImplicitTyCon :: TyCon -> Bool
- isLiftedTypeKindTyConName :: Name -> Bool
- isKindTyCon :: TyCon -> Bool
- isPromotedDataCon_maybe :: TyCon -> Maybe DataCon
- isPromotedDataCon :: TyCon -> Bool
- isPromotedTupleTyCon :: TyCon -> Bool
- isUnboxedSumTyCon :: TyCon -> Bool
- isBoxedTupleTyCon :: TyCon -> Bool
- tyConTuple_maybe :: TyCon -> Maybe TupleSort
- tyConFlavourAssoc_maybe :: TyConFlavour -> Maybe TyCon
- tyConAssoc_maybe :: TyCon -> Maybe TyCon
- isTyConAssoc :: TyCon -> Bool
- isBuiltInSynFamTyCon_maybe :: TyCon -> Maybe BuiltInSynFamily
- tyConInjectivityInfo :: TyCon -> Injectivity
- isClosedSynFamilyTyConWithAxiom_maybe :: TyCon -> Maybe (CoAxiom Branched)
- isOpenTypeFamilyTyCon :: TyCon -> Bool
- isDataFamilyTyCon :: TyCon -> Bool
- isTypeFamilyTyCon :: TyCon -> Bool
- isOpenFamilyTyCon :: TyCon -> Bool
- isFamilyTyCon :: TyCon -> Bool
- isEnumerationTyCon :: TyCon -> Bool
- isGadtSyntaxTyCon :: TyCon -> Bool
- mustBeSaturated :: TyCon -> Bool
- isFamFreeTyCon :: TyCon -> Bool
- isTauTyCon :: TyCon -> Bool
- isTypeSynonymTyCon :: TyCon -> Bool
- isDataSumTyCon_maybe :: TyCon -> Maybe [DataCon]
- isDataProductTyCon_maybe :: TyCon -> Maybe DataCon
- isProductTyCon :: TyCon -> Bool
- unwrapNewTyConEtad_maybe :: TyCon -> Maybe ([TyVar], Type, CoAxiom Unbranched)
- unwrapNewTyCon_maybe :: TyCon -> Maybe ([TyVar], Type, CoAxiom Unbranched)
- isNewTyCon :: TyCon -> Bool
- isGenInjAlgRhs :: AlgTyConRhs -> Bool
- isGenerativeTyCon :: TyCon -> Role -> Bool
- isInjectiveTyCon :: TyCon -> Role -> Bool
- isDataTyCon :: TyCon -> Bool
- isVanillaAlgTyCon :: TyCon -> Bool
- isAlgTyCon :: TyCon -> Bool
- isUnliftedTyCon :: TyCon -> Bool
- isPrimTyCon :: TyCon -> Bool
- isAbstractTyCon :: TyCon -> Bool
- mkPromotedDataCon :: DataCon -> Name -> TyConRepName -> [TyConTyCoBinder] -> Kind -> [Role] -> RuntimeRepInfo -> TyCon
- mkFamilyTyCon :: Name -> [TyConBinder] -> Kind -> Maybe Name -> FamTyConFlav -> Maybe Class -> Injectivity -> TyCon
- mkSynonymTyCon :: Name -> [TyConBinder] -> Kind -> [Role] -> Type -> Bool -> Bool -> TyCon
- mkLiftedPrimTyCon :: Name -> [TyConBinder] -> Kind -> [Role] -> TyCon
- mkKindTyCon :: Name -> [TyConBinder] -> Kind -> [Role] -> Name -> TyCon
- mkPrimTyCon :: Name -> [TyConBinder] -> Kind -> [Role] -> TyCon
- noTcTyConScopedTyVars :: [(Name, TcTyVar)]
- mkTcTyCon :: Name -> [TyConBinder] -> Kind -> [(Name, TcTyVar)] -> Bool -> TyConFlavour -> TyCon
- mkSumTyCon :: Name -> [TyConBinder] -> Kind -> Arity -> [TyVar] -> [DataCon] -> AlgTyConFlav -> TyCon
- mkTupleTyCon :: Name -> [TyConBinder] -> Kind -> Arity -> DataCon -> TupleSort -> AlgTyConFlav -> TyCon
- mkClassTyCon :: Name -> [TyConBinder] -> [Role] -> AlgTyConRhs -> Class -> Name -> TyCon
- mkAlgTyCon :: Name -> [TyConBinder] -> Kind -> [Role] -> Maybe CType -> [PredType] -> AlgTyConRhs -> AlgTyConFlav -> Bool -> TyCon
- mkFunTyCon :: Name -> [TyConBinder] -> Name -> TyCon
- lookupTyConFieldLabel :: FieldLabelString -> TyCon -> Maybe FieldLabel
- tyConFieldLabels :: TyCon -> [FieldLabel]
- primRepIsFloat :: PrimRep -> Maybe Bool
- primElemRepSizeB :: PrimElemRep -> Int
- primRepSizeB :: DynFlags -> PrimRep -> Int
- primRepsCompatible :: DynFlags -> [PrimRep] -> [PrimRep] -> Bool
- primRepCompatible :: DynFlags -> PrimRep -> PrimRep -> Bool
- isGcPtrRep :: PrimRep -> Bool
- isVoidRep :: PrimRep -> Bool
- tyConRepModOcc :: Module -> OccName -> (Module, OccName)
- mkPrelTyConRepName :: Name -> TyConRepName
- tyConRepName_maybe :: TyCon -> Maybe TyConRepName
- isNoParent :: AlgTyConFlav -> Bool
- visibleDataCons :: AlgTyConRhs -> [DataCon]
- mkDataTyConRhs :: [DataCon] -> AlgTyConRhs
- tyConVisibleTyVars :: TyCon -> [TyVar]
- tyConTyVarBinders :: [TyConBinder] -> [TyVarBinder]
- mkTyConKind :: [TyConBinder] -> Kind -> Kind
- isInvisibleTyConBinder :: VarBndr tv TyConBndrVis -> Bool
- isVisibleTyConBinder :: VarBndr tv TyConBndrVis -> Bool
- isNamedTyConBinder :: TyConBinder -> Bool
- tyConBndrVisArgFlag :: TyConBndrVis -> ArgFlag
- tyConBinderArgFlag :: TyConBinder -> ArgFlag
- mkRequiredTyConBinder :: TyCoVarSet -> TyVar -> TyConBinder
- mkNamedTyConBinders :: ArgFlag -> [TyVar] -> [TyConBinder]
- mkNamedTyConBinder :: ArgFlag -> TyVar -> TyConBinder
- mkAnonTyConBinders :: AnonArgFlag -> [TyVar] -> [TyConBinder]
- mkAnonTyConBinder :: AnonArgFlag -> TyVar -> TyConBinder
- type TyConBinder = VarBndr TyVar TyConBndrVis
- type TyConTyCoBinder = VarBndr TyCoVar TyConBndrVis
- data TyConBndrVis
- data AlgTyConRhs
- = AbstractTyCon
- | DataTyCon { }
- | TupleTyCon { }
- | SumTyCon {
- data_cons :: [DataCon]
- data_cons_size :: Int
- | NewTyCon {
- data_con :: DataCon
- nt_rhs :: Type
- nt_etad_rhs :: ([TyVar], Type)
- nt_co :: CoAxiom Unbranched
- nt_lev_poly :: Bool
- data RuntimeRepInfo
- = NoRRI
- | RuntimeRep ([Type] -> [PrimRep])
- | VecCount Int
- | VecElem PrimElemRep
- data AlgTyConFlav
- data Injectivity
- = NotInjective
- | Injective [Bool]
- data FamTyConFlav
- type TyConRepName = Name
- data PrimRep
- data PrimElemRep
- data TyConFlavour
- data RecTcChecker
- pprFunDep :: Outputable a => FunDep a -> SDoc
- pprFundeps :: Outputable a => [FunDep a] -> SDoc
- pprDefMethInfo :: DefMethInfo -> SDoc
- isAbstractClass :: Class -> Bool
- classExtraBigSig :: Class -> ([TyVar], [FunDep TyVar], [PredType], [Id], [ClassATItem], [ClassOpItem])
- classBigSig :: Class -> ([TyVar], [PredType], [Id], [ClassOpItem])
- classHasFds :: Class -> Bool
- classTvsFds :: Class -> ([TyVar], [FunDep TyVar])
- classSCTheta :: Class -> [PredType]
- classATItems :: Class -> [ClassATItem]
- classATs :: Class -> [TyCon]
- classOpItems :: Class -> [ClassOpItem]
- classMethods :: Class -> [Id]
- classSCSelId :: Class -> Int -> Id
- classSCSelIds :: Class -> [Id]
- classAllSelIds :: Class -> [Id]
- classArity :: Class -> Arity
- mkAbstractClass :: Name -> [TyVar] -> [FunDep TyVar] -> TyCon -> Class
- mkClass :: Name -> [TyVar] -> [FunDep TyVar] -> [PredType] -> [Id] -> [ClassATItem] -> [ClassOpItem] -> ClassMinimalDef -> TyCon -> Class
- classMinimalDef :: Class -> ClassMinimalDef
- data Class
- type FunDep a = ([a], [a])
- type ClassOpItem = (Id, DefMethInfo)
- type DefMethInfo = Maybe (Name, DefMethSpec Type)
- data ClassATItem = ATI TyCon (Maybe (Type, SrcSpan))
- type ClassMinimalDef = BooleanFormula Name
- data Role
- conLikeName :: ConLike -> Name
- data ConLike
- dataConName :: DataCon -> Name
- dataConTyCon :: DataCon -> TyCon
- dataConExTyCoVars :: DataCon -> [TyCoVar]
- dataConUserTyVars :: DataCon -> [TyVar]
- dataConUserTyVarBinders :: DataCon -> [TyVarBinder]
- dataConSourceArity :: DataCon -> Arity
- dataConFieldLabels :: DataCon -> [FieldLabel]
- dataConInstOrigArgTys :: DataCon -> [Type] -> [Type]
- dataConStupidTheta :: DataCon -> ThetaType
- dataConFullSig :: DataCon -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, [Type], Type)
- isUnboxedSumCon :: DataCon -> Bool
- data DataCon
- data DataConRep
- = NoDataConRep
- | DCR {
- dcr_wrap_id :: Id
- dcr_boxer :: DataConBoxer
- dcr_arg_tys :: [Type]
- dcr_stricts :: [StrictnessMark]
- dcr_bangs :: [HsImplBang]
- data EqSpec
- pprLExpr :: forall (p :: Pass). OutputableBndrId p => LHsExpr (GhcPass p) -> SDoc
- pprExpr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> SDoc
- pprSplice :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SDoc
- pprSpliceDecl :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SpliceExplicitFlag -> SDoc
- pprPatBind :: forall (bndr :: Pass) (p :: Pass) body. (OutputableBndrId bndr, OutputableBndrId p, Outputable body) => LPat (GhcPass bndr) -> GRHSs (GhcPass p) body -> SDoc
- pprFunBind :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc
- data HsExpr p
- = HsVar (XVar p) (Located (IdP p))
- | HsUnboundVar (XUnboundVar p) UnboundVar
- | HsConLikeOut (XConLikeOut p) ConLike
- | HsRecFld (XRecFld p) (AmbiguousFieldOcc p)
- | HsOverLabel (XOverLabel p) (Maybe (IdP p)) FastString
- | HsIPVar (XIPVar p) HsIPName
- | HsOverLit (XOverLitE p) (HsOverLit p)
- | HsLit (XLitE p) (HsLit p)
- | HsLam (XLam p) (MatchGroup p (LHsExpr p))
- | HsLamCase (XLamCase p) (MatchGroup p (LHsExpr p))
- | HsApp (XApp p) (LHsExpr p) (LHsExpr p)
- | HsAppType (XAppTypeE p) (LHsExpr p) (LHsWcType (NoGhcTc p))
- | OpApp (XOpApp p) (LHsExpr p) (LHsExpr p) (LHsExpr p)
- | NegApp (XNegApp p) (LHsExpr p) (SyntaxExpr p)
- | HsPar (XPar p) (LHsExpr p)
- | SectionL (XSectionL p) (LHsExpr p) (LHsExpr p)
- | SectionR (XSectionR p) (LHsExpr p) (LHsExpr p)
- | ExplicitTuple (XExplicitTuple p) [LHsTupArg p] Boxity
- | ExplicitSum (XExplicitSum p) ConTag Arity (LHsExpr p)
- | HsCase (XCase p) (LHsExpr p) (MatchGroup p (LHsExpr p))
- | HsIf (XIf p) (Maybe (SyntaxExpr p)) (LHsExpr p) (LHsExpr p) (LHsExpr p)
- | HsMultiIf (XMultiIf p) [LGRHS p (LHsExpr p)]
- | HsLet (XLet p) (LHsLocalBinds p) (LHsExpr p)
- | HsDo (XDo p) (HsStmtContext Name) (Located [ExprLStmt p])
- | ExplicitList (XExplicitList p) (Maybe (SyntaxExpr p)) [LHsExpr p]
- | RecordCon {
- rcon_ext :: XRecordCon p
- rcon_con_name :: Located (IdP p)
- rcon_flds :: HsRecordBinds p
- | RecordUpd {
- rupd_ext :: XRecordUpd p
- rupd_expr :: LHsExpr p
- rupd_flds :: [LHsRecUpdField p]
- | ExprWithTySig (XExprWithTySig p) (LHsExpr p) (LHsSigWcType (NoGhcTc p))
- | ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) (ArithSeqInfo p)
- | HsSCC (XSCC p) SourceText StringLiteral (LHsExpr p)
- | HsCoreAnn (XCoreAnn p) SourceText StringLiteral (LHsExpr p)
- | HsBracket (XBracket p) (HsBracket p)
- | HsRnBracketOut (XRnBracketOut p) (HsBracket GhcRn) [PendingRnSplice]
- | HsTcBracketOut (XTcBracketOut p) (HsBracket GhcRn) [PendingTcSplice]
- | HsSpliceE (XSpliceE p) (HsSplice p)
- | HsProc (XProc p) (LPat p) (LHsCmdTop p)
- | HsStatic (XStatic p) (LHsExpr p)
- | HsTick (XTick p) (Tickish (IdP p)) (LHsExpr p)
- | HsBinTick (XBinTick p) Int Int (LHsExpr p)
- | HsTickPragma (XTickPragma p) SourceText (StringLiteral, (Int, Int), (Int, Int)) ((SourceText, SourceText), (SourceText, SourceText)) (LHsExpr p)
- | HsWrap (XWrap p) HsWrapper (HsExpr p)
- | XExpr (XXExpr p)
- data HsCmd id
- = HsCmdArrApp (XCmdArrApp id) (LHsExpr id) (LHsExpr id) HsArrAppType Bool
- | HsCmdArrForm (XCmdArrForm id) (LHsExpr id) LexicalFixity (Maybe Fixity) [LHsCmdTop id]
- | HsCmdApp (XCmdApp id) (LHsCmd id) (LHsExpr id)
- | HsCmdLam (XCmdLam id) (MatchGroup id (LHsCmd id))
- | HsCmdPar (XCmdPar id) (LHsCmd id)
- | HsCmdCase (XCmdCase id) (LHsExpr id) (MatchGroup id (LHsCmd id))
- | HsCmdIf (XCmdIf id) (Maybe (SyntaxExpr id)) (LHsExpr id) (LHsCmd id) (LHsCmd id)
- | HsCmdLet (XCmdLet id) (LHsLocalBinds id) (LHsCmd id)
- | HsCmdDo (XCmdDo id) (Located [CmdLStmt id])
- | HsCmdWrap (XCmdWrap id) HsWrapper (HsCmd id)
- | XCmd (XXCmd id)
- data HsSplice id
- = HsTypedSplice (XTypedSplice id) SpliceDecoration (IdP id) (LHsExpr id)
- | HsUntypedSplice (XUntypedSplice id) SpliceDecoration (IdP id) (LHsExpr id)
- | HsQuasiQuote (XQuasiQuote id) (IdP id) (IdP id) SrcSpan FastString
- | HsSpliced (XSpliced id) ThModFinalizers (HsSplicedThing id)
- | HsSplicedT DelayedSplice
- | XSplice (XXSplice id)
- data MatchGroup p body
- = MG { }
- | XMatchGroup (XXMatchGroup p body)
- data GRHSs p body
- = GRHSs {
- grhssExt :: XCGRHSs p body
- grhssGRHSs :: [LGRHS p body]
- grhssLocalBinds :: LHsLocalBinds p
- | XGRHSs (XXGRHSs p body)
- = GRHSs {
- data SyntaxExpr p = SyntaxExpr {
- syn_expr :: HsExpr p
- syn_arg_wraps :: [HsWrapper]
- syn_res_wrap :: HsWrapper
- type LHsExpr p = Located (HsExpr p)
- pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc
- replaceLWrappedName :: LIEWrappedName name1 -> name2 -> LIEWrappedName name2
- replaceWrappedName :: IEWrappedName name1 -> name2 -> IEWrappedName name2
- ieLWrappedName :: LIEWrappedName name -> Located name
- lieWrappedName :: LIEWrappedName name -> name
- ieWrappedName :: IEWrappedName name -> name
- ieNames :: forall (p :: Pass). IE (GhcPass p) -> [IdP (GhcPass p)]
- ieName :: forall (p :: Pass). IE (GhcPass p) -> IdP (GhcPass p)
- simpleImportDecl :: forall (p :: Pass). ModuleName -> ImportDecl (GhcPass p)
- isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool
- importDeclQualifiedStyle :: Maybe (Located a) -> Maybe (Located a) -> ImportDeclQualifiedStyle
- type LImportDecl pass = Located (ImportDecl pass)
- data ImportDeclQualifiedStyle
- data ImportDecl pass
- = ImportDecl {
- ideclExt :: XCImportDecl pass
- ideclSourceSrc :: SourceText
- ideclName :: Located ModuleName
- ideclPkgQual :: Maybe StringLiteral
- ideclSource :: Bool
- ideclSafe :: Bool
- ideclQualified :: ImportDeclQualifiedStyle
- ideclImplicit :: Bool
- ideclAs :: Maybe (Located ModuleName)
- ideclHiding :: Maybe (Bool, Located [LIE pass])
- | XImportDecl (XXImportDecl pass)
- = ImportDecl {
- data IEWrappedName name
- type LIEWrappedName name = Located (IEWrappedName name)
- type LIE pass = Located (IE pass)
- data IE pass
- = IEVar (XIEVar pass) (LIEWrappedName (IdP pass))
- | IEThingAbs (XIEThingAbs pass) (LIEWrappedName (IdP pass))
- | IEThingAll (XIEThingAll pass) (LIEWrappedName (IdP pass))
- | IEThingWith (XIEThingWith pass) (LIEWrappedName (IdP pass)) IEWildcard [LIEWrappedName (IdP pass)] [Located (FieldLbl (IdP pass))]
- | IEModuleContents (XIEModuleContents pass) (Located ModuleName)
- | IEGroup (XIEGroup pass) Int HsDocString
- | IEDoc (XIEDoc pass) HsDocString
- | IEDocNamed (XIEDocNamed pass) String
- | XIE (XXIE pass)
- data IEWildcard
- data Pat p
- = WildPat (XWildPat p)
- | VarPat (XVarPat p) (Located (IdP p))
- | LazyPat (XLazyPat p) (LPat p)
- | AsPat (XAsPat p) (Located (IdP p)) (LPat p)
- | ParPat (XParPat p) (LPat p)
- | BangPat (XBangPat p) (LPat p)
- | ListPat (XListPat p) [LPat p]
- | TuplePat (XTuplePat p) [LPat p] Boxity
- | SumPat (XSumPat p) (LPat p) ConTag Arity
- | ConPatIn (Located (IdP p)) (HsConPatDetails p)
- | ConPatOut { }
- | ViewPat (XViewPat p) (LHsExpr p) (LPat p)
- | SplicePat (XSplicePat p) (HsSplice p)
- | LitPat (XLitPat p) (HsLit p)
- | NPat (XNPat p) (Located (HsOverLit p)) (Maybe (SyntaxExpr p)) (SyntaxExpr p)
- | NPlusKPat (XNPlusKPat p) (Located (IdP p)) (Located (HsOverLit p)) (HsOverLit p) (SyntaxExpr p) (SyntaxExpr p)
- | SigPat (XSigPat p) (LPat p) (LHsSigWcType (NoGhcTc p))
- | CoPat (XCoPat p) HsWrapper (Pat p) Type
- | XPat (XXPat p)
- type LPat p = XRec p Pat
- noExtCon :: NoExtCon -> a
- noExtField :: NoExtField
- data NoExtField = NoExtField
- data NoExtCon
- data GhcPass (c :: Pass)
- data Pass
- = Parsed
- | Renamed
- | Typechecked
- type GhcPs = GhcPass 'Parsed
- type GhcRn = GhcPass 'Renamed
- type GhcTc = GhcPass 'Typechecked
- type GhcTcId = GhcTc
- type family XRec p (f :: Type -> Type) = (r :: Type) | r -> p f
- type family IdP p
- type LIdP p = Located (IdP p)
- type family NoGhcTc p where ...
- type family NoGhcTcPass (p :: Pass) :: Pass where ...
- type family XHsValBinds x x'
- type family XHsIPBinds x x'
- type family XEmptyLocalBinds x x'
- type family XXHsLocalBindsLR x x'
- type ForallXHsLocalBindsLR (c :: Type -> Constraint) x x' = (c (XHsValBinds x x'), c (XHsIPBinds x x'), c (XEmptyLocalBinds x x'), c (XXHsLocalBindsLR x x'))
- type family XValBinds x x'
- type family XXValBindsLR x x'
- type ForallXValBindsLR (c :: Type -> Constraint) x x' = (c (XValBinds x x'), c (XXValBindsLR x x'))
- type family XFunBind x x'
- type family XPatBind x x'
- type family XVarBind x x'
- type family XAbsBinds x x'
- type family XPatSynBind x x'
- type family XXHsBindsLR x x'
- type ForallXHsBindsLR (c :: Type -> Constraint) x x' = (c (XFunBind x x'), c (XPatBind x x'), c (XVarBind x x'), c (XAbsBinds x x'), c (XPatSynBind x x'), c (XXHsBindsLR x x'))
- type family XABE x
- type family XXABExport x
- type ForallXABExport (c :: Type -> Constraint) x = (c (XABE x), c (XXABExport x))
- type family XPSB x x'
- type family XXPatSynBind x x'
- type ForallXPatSynBind (c :: Type -> Constraint) x x' = (c (XPSB x x'), c (XXPatSynBind x x'))
- type family XIPBinds x
- type family XXHsIPBinds x
- type ForallXHsIPBinds (c :: Type -> Constraint) x = (c (XIPBinds x), c (XXHsIPBinds x))
- type family XCIPBind x
- type family XXIPBind x
- type ForallXIPBind (c :: Type -> Constraint) x = (c (XCIPBind x), c (XXIPBind x))
- type family XTypeSig x
- type family XPatSynSig x
- type family XClassOpSig x
- type family XIdSig x
- type family XFixSig x
- type family XInlineSig x
- type family XSpecSig x
- type family XSpecInstSig x
- type family XMinimalSig x
- type family XSCCFunSig x
- type family XCompleteMatchSig x
- type family XXSig x
- type ForallXSig (c :: Type -> Constraint) x = (c (XTypeSig x), c (XPatSynSig x), c (XClassOpSig x), c (XIdSig x), c (XFixSig x), c (XInlineSig x), c (XSpecSig x), c (XSpecInstSig x), c (XMinimalSig x), c (XSCCFunSig x), c (XCompleteMatchSig x), c (XXSig x))
- type family XFixitySig x
- type family XXFixitySig x
- type ForallXFixitySig (c :: Type -> Constraint) x = (c (XFixitySig x), c (XXFixitySig x))
- type family XStandaloneKindSig x
- type family XXStandaloneKindSig x
- type family XTyClD x
- type family XInstD x
- type family XDerivD x
- type family XValD x
- type family XSigD x
- type family XKindSigD x
- type family XDefD x
- type family XForD x
- type family XWarningD x
- type family XAnnD x
- type family XRuleD x
- type family XSpliceD x
- type family XDocD x
- type family XRoleAnnotD x
- type family XXHsDecl x
- type ForallXHsDecl (c :: Type -> Constraint) x = (c (XTyClD x), c (XInstD x), c (XDerivD x), c (XValD x), c (XSigD x), c (XKindSigD x), c (XDefD x), c (XForD x), c (XWarningD x), c (XAnnD x), c (XRuleD x), c (XSpliceD x), c (XDocD x), c (XRoleAnnotD x), c (XXHsDecl x))
- type family XCHsGroup x
- type family XXHsGroup x
- type ForallXHsGroup (c :: Type -> Constraint) x = (c (XCHsGroup x), c (XXHsGroup x))
- type family XSpliceDecl x
- type family XXSpliceDecl x
- type ForallXSpliceDecl (c :: Type -> Constraint) x = (c (XSpliceDecl x), c (XXSpliceDecl x))
- type family XFamDecl x
- type family XSynDecl x
- type family XDataDecl x
- type family XClassDecl x
- type family XXTyClDecl x
- type ForallXTyClDecl (c :: Type -> Constraint) x = (c (XFamDecl x), c (XSynDecl x), c (XDataDecl x), c (XClassDecl x), c (XXTyClDecl x))
- type family XCTyClGroup x
- type family XXTyClGroup x
- type ForallXTyClGroup (c :: Type -> Constraint) x = (c (XCTyClGroup x), c (XXTyClGroup x))
- type family XNoSig x
- type family XCKindSig x
- type family XTyVarSig x
- type family XXFamilyResultSig x
- type ForallXFamilyResultSig (c :: Type -> Constraint) x = (c (XNoSig x), c (XCKindSig x), c (XTyVarSig x), c (XXFamilyResultSig x))
- type family XCFamilyDecl x
- type family XXFamilyDecl x
- type ForallXFamilyDecl (c :: Type -> Constraint) x = (c (XCFamilyDecl x), c (XXFamilyDecl x))
- type family XCHsDataDefn x
- type family XXHsDataDefn x
- type ForallXHsDataDefn (c :: Type -> Constraint) x = (c (XCHsDataDefn x), c (XXHsDataDefn x))
- type family XCHsDerivingClause x
- type family XXHsDerivingClause x
- type ForallXHsDerivingClause (c :: Type -> Constraint) x = (c (XCHsDerivingClause x), c (XXHsDerivingClause x))
- type family XConDeclGADT x
- type family XConDeclH98 x
- type family XXConDecl x
- type ForallXConDecl (c :: Type -> Constraint) x = (c (XConDeclGADT x), c (XConDeclH98 x), c (XXConDecl x))
- type family XCFamEqn x r
- type family XXFamEqn x r
- type ForallXFamEqn (c :: Type -> Constraint) x r = (c (XCFamEqn x r), c (XXFamEqn x r))
- type family XCClsInstDecl x
- type family XXClsInstDecl x
- type ForallXClsInstDecl (c :: Type -> Constraint) x = (c (XCClsInstDecl x), c (XXClsInstDecl x))
- type family XClsInstD x
- type family XDataFamInstD x
- type family XTyFamInstD x
- type family XXInstDecl x
- type ForallXInstDecl (c :: Type -> Constraint) x = (c (XClsInstD x), c (XDataFamInstD x), c (XTyFamInstD x), c (XXInstDecl x))
- type family XCDerivDecl x
- type family XXDerivDecl x
- type ForallXDerivDecl (c :: Type -> Constraint) x = (c (XCDerivDecl x), c (XXDerivDecl x))
- type family XViaStrategy x
- type family XCDefaultDecl x
- type family XXDefaultDecl x
- type ForallXDefaultDecl (c :: Type -> Constraint) x = (c (XCDefaultDecl x), c (XXDefaultDecl x))
- type family XForeignImport x
- type family XForeignExport x
- type family XXForeignDecl x
- type ForallXForeignDecl (c :: Type -> Constraint) x = (c (XForeignImport x), c (XForeignExport x), c (XXForeignDecl x))
- type family XCRuleDecls x
- type family XXRuleDecls x
- type ForallXRuleDecls (c :: Type -> Constraint) x = (c (XCRuleDecls x), c (XXRuleDecls x))
- type family XHsRule x
- type family XXRuleDecl x
- type ForallXRuleDecl (c :: Type -> Constraint) x = (c (XHsRule x), c (XXRuleDecl x))
- type family XCRuleBndr x
- type family XRuleBndrSig x
- type family XXRuleBndr x
- type ForallXRuleBndr (c :: Type -> Constraint) x = (c (XCRuleBndr x), c (XRuleBndrSig x), c (XXRuleBndr x))
- type family XWarnings x
- type family XXWarnDecls x
- type ForallXWarnDecls (c :: Type -> Constraint) x = (c (XWarnings x), c (XXWarnDecls x))
- type family XWarning x
- type family XXWarnDecl x
- type ForallXWarnDecl (c :: Type -> Constraint) x = (c (XWarning x), c (XXWarnDecl x))
- type family XHsAnnotation x
- type family XXAnnDecl x
- type ForallXAnnDecl (c :: Type -> Constraint) x = (c (XHsAnnotation x), c (XXAnnDecl x))
- type family XCRoleAnnotDecl x
- type family XXRoleAnnotDecl x
- type ForallXRoleAnnotDecl (c :: Type -> Constraint) x = (c (XCRoleAnnotDecl x), c (XXRoleAnnotDecl x))
- type family XVar x
- type family XUnboundVar x
- type family XConLikeOut x
- type family XRecFld x
- type family XOverLabel x
- type family XIPVar x
- type family XOverLitE x
- type family XLitE x
- type family XLam x
- type family XLamCase x
- type family XApp x
- type family XAppTypeE x
- type family XOpApp x
- type family XNegApp x
- type family XPar x
- type family XSectionL x
- type family XSectionR x
- type family XExplicitTuple x
- type family XExplicitSum x
- type family XCase x
- type family XIf x
- type family XMultiIf x
- type family XLet x
- type family XDo x
- type family XExplicitList x
- type family XRecordCon x
- type family XRecordUpd x
- type family XExprWithTySig x
- type family XArithSeq x
- type family XSCC x
- type family XCoreAnn x
- type family XBracket x
- type family XRnBracketOut x
- type family XTcBracketOut x
- type family XSpliceE x
- type family XProc x
- type family XStatic x
- type family XTick x
- type family XBinTick x
- type family XTickPragma x
- type family XWrap x
- type family XXExpr x
- type ForallXExpr (c :: Type -> Constraint) x = (c (XVar x), c (XUnboundVar x), c (XConLikeOut x), c (XRecFld x), c (XOverLabel x), c (XIPVar x), c (XOverLitE x), c (XLitE x), c (XLam x), c (XLamCase x), c (XApp x), c (XAppTypeE x), c (XOpApp x), c (XNegApp x), c (XPar x), c (XSectionL x), c (XSectionR x), c (XExplicitTuple x), c (XExplicitSum x), c (XCase x), c (XIf x), c (XMultiIf x), c (XLet x), c (XDo x), c (XExplicitList x), c (XRecordCon x), c (XRecordUpd x), c (XExprWithTySig x), c (XArithSeq x), c (XSCC x), c (XCoreAnn x), c (XBracket x), c (XRnBracketOut x), c (XTcBracketOut x), c (XSpliceE x), c (XProc x), c (XStatic x), c (XTick x), c (XBinTick x), c (XTickPragma x), c (XWrap x), c (XXExpr x))
- type family XUnambiguous x
- type family XAmbiguous x
- type family XXAmbiguousFieldOcc x
- type ForallXAmbiguousFieldOcc (c :: Type -> Constraint) x = (c (XUnambiguous x), c (XAmbiguous x), c (XXAmbiguousFieldOcc x))
- type family XPresent x
- type family XMissing x
- type family XXTupArg x
- type ForallXTupArg (c :: Type -> Constraint) x = (c (XPresent x), c (XMissing x), c (XXTupArg x))
- type family XTypedSplice x
- type family XUntypedSplice x
- type family XQuasiQuote x
- type family XSpliced x
- type family XXSplice x
- type ForallXSplice (c :: Type -> Constraint) x = (c (XTypedSplice x), c (XUntypedSplice x), c (XQuasiQuote x), c (XSpliced x), c (XXSplice x))
- type family XExpBr x
- type family XPatBr x
- type family XDecBrL x
- type family XDecBrG x
- type family XTypBr x
- type family XVarBr x
- type family XTExpBr x
- type family XXBracket x
- type ForallXBracket (c :: Type -> Constraint) x = (c (XExpBr x), c (XPatBr x), c (XDecBrL x), c (XDecBrG x), c (XTypBr x), c (XVarBr x), c (XTExpBr x), c (XXBracket x))
- type family XCmdTop x
- type family XXCmdTop x
- type ForallXCmdTop (c :: Type -> Constraint) x = (c (XCmdTop x), c (XXCmdTop x))
- type family XMG x b
- type family XXMatchGroup x b
- type ForallXMatchGroup (c :: Type -> Constraint) x b = (c (XMG x b), c (XXMatchGroup x b))
- type family XCMatch x b
- type family XXMatch x b
- type ForallXMatch (c :: Type -> Constraint) x b = (c (XCMatch x b), c (XXMatch x b))
- type family XCGRHSs x b
- type family XXGRHSs x b
- type ForallXGRHSs (c :: Type -> Constraint) x b = (c (XCGRHSs x b), c (XXGRHSs x b))
- type family XCGRHS x b
- type family XXGRHS x b
- type ForallXGRHS (c :: Type -> Constraint) x b = (c (XCGRHS x b), c (XXGRHS x b))
- type family XLastStmt x x' b
- type family XBindStmt x x' b
- type family XApplicativeStmt x x' b
- type family XBodyStmt x x' b
- type family XLetStmt x x' b
- type family XParStmt x x' b
- type family XTransStmt x x' b
- type family XRecStmt x x' b
- type family XXStmtLR x x' b
- type ForallXStmtLR (c :: Type -> Constraint) x x' b = (c (XLastStmt x x' b), c (XBindStmt x x' b), c (XApplicativeStmt x x' b), c (XBodyStmt x x' b), c (XLetStmt x x' b), c (XParStmt x x' b), c (XTransStmt x x' b), c (XRecStmt x x' b), c (XXStmtLR x x' b))
- type family XCmdArrApp x
- type family XCmdArrForm x
- type family XCmdApp x
- type family XCmdLam x
- type family XCmdPar x
- type family XCmdCase x
- type family XCmdIf x
- type family XCmdLet x
- type family XCmdDo x
- type family XCmdWrap x
- type family XXCmd x
- type ForallXCmd (c :: Type -> Constraint) x = (c (XCmdArrApp x), c (XCmdArrForm x), c (XCmdApp x), c (XCmdLam x), c (XCmdPar x), c (XCmdCase x), c (XCmdIf x), c (XCmdLet x), c (XCmdDo x), c (XCmdWrap x), c (XXCmd x))
- type family XParStmtBlock x x'
- type family XXParStmtBlock x x'
- type ForallXParStmtBlock (c :: Type -> Constraint) x x' = (c (XParStmtBlock x x'), c (XXParStmtBlock x x'))
- type family XApplicativeArgOne x
- type family XApplicativeArgMany x
- type family XXApplicativeArg x
- type ForallXApplicativeArg (c :: Type -> Constraint) x = (c (XApplicativeArgOne x), c (XApplicativeArgMany x), c (XXApplicativeArg x))
- type family XHsChar x
- type family XHsCharPrim x
- type family XHsString x
- type family XHsStringPrim x
- type family XHsInt x
- type family XHsIntPrim x
- type family XHsWordPrim x
- type family XHsInt64Prim x
- type family XHsWord64Prim x
- type family XHsInteger x
- type family XHsRat x
- type family XHsFloatPrim x
- type family XHsDoublePrim x
- type family XXLit x
- type ForallXHsLit (c :: Type -> Constraint) x = (c (XHsChar x), c (XHsCharPrim x), c (XHsDoublePrim x), c (XHsFloatPrim x), c (XHsInt x), c (XHsInt64Prim x), c (XHsIntPrim x), c (XHsInteger x), c (XHsRat x), c (XHsString x), c (XHsStringPrim x), c (XHsWord64Prim x), c (XHsWordPrim x), c (XXLit x))
- type family XOverLit x
- type family XXOverLit x
- type ForallXOverLit (c :: Type -> Constraint) x = (c (XOverLit x), c (XXOverLit x))
- type family XWildPat x
- type family XVarPat x
- type family XLazyPat x
- type family XAsPat x
- type family XParPat x
- type family XBangPat x
- type family XListPat x
- type family XTuplePat x
- type family XSumPat x
- type family XConPat x
- type family XViewPat x
- type family XSplicePat x
- type family XLitPat x
- type family XNPat x
- type family XNPlusKPat x
- type family XSigPat x
- type family XCoPat x
- type family XXPat x
- type ForallXPat (c :: Type -> Constraint) x = (c (XWildPat x), c (XVarPat x), c (XLazyPat x), c (XAsPat x), c (XParPat x), c (XBangPat x), c (XListPat x), c (XTuplePat x), c (XSumPat x), c (XViewPat x), c (XSplicePat x), c (XLitPat x), c (XNPat x), c (XNPlusKPat x), c (XSigPat x), c (XCoPat x), c (XXPat x))
- type family XHsQTvs x
- type family XXLHsQTyVars x
- type ForallXLHsQTyVars (c :: Type -> Constraint) x = (c (XHsQTvs x), c (XXLHsQTyVars x))
- type family XHsIB x b
- type family XXHsImplicitBndrs x b
- type ForallXHsImplicitBndrs (c :: Type -> Constraint) x b = (c (XHsIB x b), c (XXHsImplicitBndrs x b))
- type family XHsWC x b
- type family XXHsWildCardBndrs x b
- type ForallXHsWildCardBndrs (c :: Type -> Constraint) x b = (c (XHsWC x b), c (XXHsWildCardBndrs x b))
- type family XForAllTy x
- type family XQualTy x
- type family XTyVar x
- type family XAppTy x
- type family XAppKindTy x
- type family XFunTy x
- type family XListTy x
- type family XTupleTy x
- type family XSumTy x
- type family XOpTy x
- type family XParTy x
- type family XIParamTy x
- type family XStarTy x
- type family XKindSig x
- type family XSpliceTy x
- type family XDocTy x
- type family XBangTy x
- type family XRecTy x
- type family XExplicitListTy x
- type family XExplicitTupleTy x
- type family XTyLit x
- type family XWildCardTy x
- type family XXType x
- type ForallXType (c :: Type -> Constraint) x = (c (XForAllTy x), c (XQualTy x), c (XTyVar x), c (XAppTy x), c (XAppKindTy x), c (XFunTy x), c (XListTy x), c (XTupleTy x), c (XSumTy x), c (XOpTy x), c (XParTy x), c (XIParamTy x), c (XStarTy x), c (XKindSig x), c (XSpliceTy x), c (XDocTy x), c (XBangTy x), c (XRecTy x), c (XExplicitListTy x), c (XExplicitTupleTy x), c (XTyLit x), c (XWildCardTy x), c (XXType x))
- type family XUserTyVar x
- type family XKindedTyVar x
- type family XXTyVarBndr x
- type ForallXTyVarBndr (c :: Type -> Constraint) x = (c (XUserTyVar x), c (XKindedTyVar x), c (XXTyVarBndr x))
- type family XConDeclField x
- type family XXConDeclField x
- type ForallXConDeclField (c :: Type -> Constraint) x = (c (XConDeclField x), c (XXConDeclField x))
- type family XCFieldOcc x
- type family XXFieldOcc x
- type ForallXFieldOcc (c :: Type -> Constraint) x = (c (XCFieldOcc x), c (XXFieldOcc x))
- type family XCImportDecl x
- type family XXImportDecl x
- type ForallXImportDecl (c :: Type -> Constraint) x = (c (XCImportDecl x), c (XXImportDecl x))
- type family XIEVar x
- type family XIEThingAbs x
- type family XIEThingAll x
- type family XIEThingWith x
- type family XIEModuleContents x
- type family XIEGroup x
- type family XIEDoc x
- type family XIEDocNamed x
- type family XXIE x
- type ForallXIE (c :: Type -> Constraint) x = (c (XIEVar x), c (XIEThingAbs x), c (XIEThingAll x), c (XIEThingWith x), c (XIEModuleContents x), c (XIEGroup x), c (XIEDoc x), c (XIEDocNamed x), c (XXIE x))
- class Convertable a b | a -> b where
- convert :: a -> b
- type ConvertIdX a b = (XHsDoublePrim a ~ XHsDoublePrim b, XHsFloatPrim a ~ XHsFloatPrim b, XHsRat a ~ XHsRat b, XHsInteger a ~ XHsInteger b, XHsWord64Prim a ~ XHsWord64Prim b, XHsInt64Prim a ~ XHsInt64Prim b, XHsWordPrim a ~ XHsWordPrim b, XHsIntPrim a ~ XHsIntPrim b, XHsInt a ~ XHsInt b, XHsStringPrim a ~ XHsStringPrim b, XHsString a ~ XHsString b, XHsCharPrim a ~ XHsCharPrim b, XHsChar a ~ XHsChar b, XXLit a ~ XXLit b)
- type OutputableX p = (Outputable (XIPBinds p), Outputable (XViaStrategy p), Outputable (XViaStrategy GhcRn))
- type OutputableBndrId (pass :: Pass) = (OutputableBndr (NameOrRdrName (IdP (GhcPass pass))), OutputableBndr (IdP (GhcPass pass)), OutputableBndr (NameOrRdrName (IdP (NoGhcTc (GhcPass pass)))), OutputableBndr (IdP (NoGhcTc (GhcPass pass))), NoGhcTc (GhcPass pass) ~ NoGhcTc (NoGhcTc (GhcPass pass)), OutputableX (GhcPass pass), OutputableX (NoGhcTc (GhcPass pass)))
- placeHolderNamesTc :: NameSet
- type family NameOrRdrName id where ...
- isExportedId :: Var -> Bool
- mustHaveLocalBinding :: Var -> Bool
- isGlobalId :: Var -> Bool
- isLocalVar :: Var -> Bool
- isLocalId :: Var -> Bool
- isNonCoVarId :: Var -> Bool
- isCoVar :: Var -> Bool
- isId :: Var -> Bool
- isTyCoVar :: Var -> Bool
- isTcTyVar :: Var -> Bool
- isTyVar :: Var -> Bool
- setIdNotExported :: Id -> Id
- setIdExported :: Id -> Id
- globaliseId :: Id -> Id
- setIdDetails :: Id -> IdDetails -> Id
- lazySetIdInfo :: Id -> IdInfo -> Var
- mkExportedLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
- mkCoVar :: Name -> Type -> CoVar
- mkLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
- mkGlobalVar :: IdDetails -> Name -> Type -> IdInfo -> Id
- idDetails :: Id -> IdDetails
- idInfo :: HasDebugCallStack => Id -> IdInfo
- setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVar
- tcTyVarDetails :: TyVar -> TcTyVarDetails
- mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar
- mkTyVar :: Name -> Kind -> TyVar
- updateTyVarKindM :: Monad m => (Kind -> m Kind) -> TyVar -> m TyVar
- updateTyVarKind :: (Kind -> Kind) -> TyVar -> TyVar
- setTyVarKind :: TyVar -> Kind -> TyVar
- setTyVarName :: TyVar -> Name -> TyVar
- setTyVarUnique :: TyVar -> Unique -> TyVar
- tyVarKind :: TyVar -> Kind
- tyVarName :: TyVar -> Name
- isTyVarBinder :: TyCoVarBinder -> Bool
- mkTyVarBinders :: ArgFlag -> [TyVar] -> [TyVarBinder]
- mkTyCoVarBinders :: ArgFlag -> [TyCoVar] -> [TyCoVarBinder]
- mkTyVarBinder :: ArgFlag -> TyVar -> TyVarBinder
- mkTyCoVarBinder :: ArgFlag -> TyCoVar -> TyCoVarBinder
- binderType :: VarBndr TyCoVar argf -> Type
- binderArgFlag :: VarBndr tv argf -> argf
- binderVars :: [VarBndr tv argf] -> [tv]
- binderVar :: VarBndr tv argf -> tv
- argToForallVisFlag :: ArgFlag -> ForallVisFlag
- sameVis :: ArgFlag -> ArgFlag -> Bool
- isInvisibleArgFlag :: ArgFlag -> Bool
- isVisibleArgFlag :: ArgFlag -> Bool
- updateVarTypeM :: Monad m => (Type -> m Type) -> Id -> m Id
- updateVarType :: (Type -> Type) -> Id -> Id
- setVarType :: Id -> Type -> Id
- setVarName :: Var -> Name -> Var
- setVarUnique :: Var -> Unique -> Var
- varUnique :: Var -> Unique
- nonDetCmpVar :: Var -> Var -> Ordering
- type Id = Var
- type CoVar = Id
- type NcId = Id
- type TyVar = Var
- type TKVar = Var
- type TcTyVar = Var
- type TypeVar = Var
- type KindVar = Var
- type EvId = Id
- type EvVar = EvId
- type DFunId = Id
- type DictId = EvId
- type IpId = EvId
- type EqVar = EvId
- type JoinId = Id
- type TyCoVar = Id
- type InVar = Var
- type InTyVar = TyVar
- type InCoVar = CoVar
- type InId = Id
- type OutVar = Var
- type OutTyVar = TyVar
- type OutCoVar = CoVar
- type OutId = Id
- data ForallVisFlag
- data VarBndr var argf = Bndr var argf
- type TyCoVarBinder = VarBndr TyCoVar ArgFlag
- type TyVarBinder = VarBndr TyVar ArgFlag
- data Token
- unicodeAnn :: AnnKeywordId -> AnnKeywordId
- getAndRemoveAnnotationComments :: ApiAnns -> SrcSpan -> ([Located AnnotationComment], ApiAnns)
- getAnnotationComments :: ApiAnns -> SrcSpan -> [Located AnnotationComment]
- getAndRemoveAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> ([SrcSpan], ApiAnns)
- getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan]
- type ApiAnns = (Map ApiAnnKey [SrcSpan], Map SrcSpan [Located AnnotationComment])
- data AnnKeywordId
- = AnnAnyclass
- | AnnAs
- | AnnAt
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnClass
- | AnnClose
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | AnnCloseS
- | AnnColon
- | AnnComma
- | AnnCommaTuple
- | AnnDarrow
- | AnnDarrowU
- | AnnData
- | AnnDcolon
- | AnnDcolonU
- | AnnDefault
- | AnnDeriving
- | AnnDo
- | AnnDot
- | AnnDotdot
- | AnnElse
- | AnnEqual
- | AnnExport
- | AnnFamily
- | AnnForall
- | AnnForallU
- | AnnForeign
- | AnnFunId
- | AnnGroup
- | AnnHeader
- | AnnHiding
- | AnnIf
- | AnnImport
- | AnnIn
- | AnnInfix
- | AnnInstance
- | AnnLam
- | AnnLarrow
- | AnnLarrowU
- | AnnLet
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenPE
- | AnnOpenPTE
- | AnnOpenS
- | AnnPackageName
- | AnnPattern
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRarrowU
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnSignature
- | AnnStatic
- | AnnStock
- | AnnThen
- | AnnThIdSplice
- | AnnThIdTySplice
- | AnnThTyQuote
- | AnnTilde
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnVia
- | AnnWhere
- | Annlarrowtail
- | AnnlarrowtailU
- | Annrarrowtail
- | AnnrarrowtailU
- | AnnLarrowtail
- | AnnLarrowtailU
- | AnnRarrowtail
- | AnnRarrowtailU
- | AnnEofPos
- data AnnotationComment
- nilDataConKey :: Unique
- listTyConKey :: Unique
- starInfo :: Bool -> RdrName -> SDoc
- pprNameProvenance :: GlobalRdrElt -> SDoc
- isExplicitItem :: ImpItemSpec -> Bool
- importSpecModule :: ImportSpec -> ModuleName
- importSpecLoc :: ImportSpec -> SrcSpan
- qualSpecOK :: ModuleName -> ImportSpec -> Bool
- unQualSpecOK :: ImportSpec -> Bool
- bestImport :: [ImportSpec] -> ImportSpec
- shadowNames :: GlobalRdrEnv -> [Name] -> GlobalRdrEnv
- extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
- transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv
- mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv
- plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
- pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)]
- pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt]
- unQualOK :: GlobalRdrElt -> Bool
- greLabel :: GlobalRdrElt -> Maybe FieldLabelString
- isOverloadedRecFldGRE :: GlobalRdrElt -> Bool
- isRecFldGRE :: GlobalRdrElt -> Bool
- isLocalGRE :: GlobalRdrElt -> Bool
- getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]]
- lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
- lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt
- lookupGRE_Name :: GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
- lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
- greOccName :: GlobalRdrElt -> OccName
- lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt]
- pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc
- globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt]
- emptyGlobalRdrEnv :: GlobalRdrEnv
- availFromGRE :: GlobalRdrElt -> AvailInfo
- gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo]
- greParent_maybe :: GlobalRdrElt -> Maybe Name
- greSrcSpan :: GlobalRdrElt -> SrcSpan
- greRdrNames :: GlobalRdrElt -> [RdrName]
- greQualModName :: GlobalRdrElt -> ModuleName
- gresFromAvail :: (Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt]
- localGREsFromAvail :: AvailInfo -> [GlobalRdrElt]
- gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt]
- delLocalRdrEnvList :: LocalRdrEnv -> [OccName] -> LocalRdrEnv
- inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool
- localRdrEnvElts :: LocalRdrEnv -> [Name]
- elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool
- lookupLocalRdrOcc :: LocalRdrEnv -> OccName -> Maybe Name
- lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name
- extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv
- extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv
- emptyLocalRdrEnv :: LocalRdrEnv
- isExact_maybe :: RdrName -> Maybe Name
- isExact :: RdrName -> Bool
- isOrig_maybe :: RdrName -> Maybe (Module, OccName)
- isOrig :: RdrName -> Bool
- isQual_maybe :: RdrName -> Maybe (ModuleName, OccName)
- isQual :: RdrName -> Bool
- isUnqual :: RdrName -> Bool
- isSrcRdrName :: RdrName -> Bool
- isRdrTc :: RdrName -> Bool
- isRdrTyVar :: RdrName -> Bool
- isRdrDataCon :: RdrName -> Bool
- nameRdrName :: Name -> RdrName
- getRdrName :: NamedThing thing => thing -> RdrName
- mkQual :: NameSpace -> (FastString, FastString) -> RdrName
- mkVarUnqual :: FastString -> RdrName
- mkUnqual :: NameSpace -> FastString -> RdrName
- mkOrig :: Module -> OccName -> RdrName
- mkRdrQual :: ModuleName -> OccName -> RdrName
- mkRdrUnqual :: OccName -> RdrName
- demoteRdrName :: RdrName -> Maybe RdrName
- rdrNameSpace :: RdrName -> NameSpace
- rdrNameOcc :: RdrName -> OccName
- data RdrName
- data LocalRdrEnv
- type GlobalRdrEnv = OccEnv [GlobalRdrElt]
- data GlobalRdrElt = GRE {}
- data Parent
- data ImportSpec = ImpSpec {}
- data ImpDeclSpec = ImpDeclSpec {
- is_mod :: ModuleName
- is_as :: ModuleName
- is_qual :: Bool
- is_dloc :: SrcSpan
- data ImpItemSpec
- nubAvails :: [AvailInfo] -> [AvailInfo]
- filterAvail :: (Name -> Bool) -> AvailInfo -> [AvailInfo] -> [AvailInfo]
- filterAvails :: (Name -> Bool) -> [AvailInfo] -> [AvailInfo]
- trimAvail :: AvailInfo -> Name -> AvailInfo
- plusAvail :: AvailInfo -> AvailInfo -> AvailInfo
- availNamesWithOccs :: AvailInfo -> [(Name, OccName)]
- availsNamesWithOccs :: [AvailInfo] -> [(Name, OccName)]
- availFlds :: AvailInfo -> [FieldLabel]
- availNonFldNames :: AvailInfo -> [Name]
- availNamesWithSelectors :: AvailInfo -> [Name]
- availNames :: AvailInfo -> [Name]
- availName :: AvailInfo -> Name
- availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
- availsToNameSetWithSelectors :: [AvailInfo] -> NameSet
- availsToNameSet :: [AvailInfo] -> NameSet
- avail :: Name -> AvailInfo
- stableAvailCmp :: AvailInfo -> AvailInfo -> Ordering
- data AvailInfo
- type Avails = [AvailInfo]
- type FieldLabelString = FastString
- type FieldLabel = FieldLbl Name
- data FieldLbl a = FieldLabel {
- flLabel :: FieldLabelString
- flIsOverloaded :: Bool
- flSelector :: a
- emptyArgDocMap :: ArgDocMap
- emptyDeclDocMap :: DeclDocMap
- concatDocs :: [HsDocString] -> Maybe HsDocString
- appendDocs :: HsDocString -> HsDocString -> HsDocString
- ppr_mbDoc :: Maybe LHsDocString -> SDoc
- hsDocStringToByteString :: HsDocString -> ByteString
- unpackHDS :: HsDocString -> String
- mkHsDocStringUtf8ByteString :: ByteString -> HsDocString
- mkHsDocString :: String -> HsDocString
- data HsDocString
- type LHsDocString = Located HsDocString
- newtype DeclDocMap = DeclDocMap (Map Name HsDocString)
- newtype ArgDocMap = ArgDocMap (Map Name (Map Int HsDocString))
- findUses :: DefUses -> Uses -> Uses
- duUses :: DefUses -> Uses
- allUses :: DefUses -> Uses
- duDefs :: DefUses -> Defs
- plusDU :: DefUses -> DefUses -> DefUses
- mkDUs :: [(Defs, Uses)] -> DefUses
- usesOnly :: Uses -> DefUses
- emptyDUs :: DefUses
- intersectFVs :: FreeVars -> FreeVars -> FreeVars
- delFVs :: [Name] -> FreeVars -> FreeVars
- delFV :: Name -> FreeVars -> FreeVars
- unitFV :: Name -> FreeVars
- addOneFV :: FreeVars -> Name -> FreeVars
- mkFVs :: [Name] -> FreeVars
- plusFV :: FreeVars -> FreeVars -> FreeVars
- plusFVs :: [FreeVars] -> FreeVars
- emptyFVs :: FreeVars
- isEmptyFVs :: NameSet -> Bool
- nameSetElemsStable :: NameSet -> [Name]
- nameSetAll :: (Name -> Bool) -> NameSet -> Bool
- nameSetAny :: (Name -> Bool) -> NameSet -> Bool
- intersectsNameSet :: NameSet -> NameSet -> Bool
- delListFromNameSet :: NameSet -> [Name] -> NameSet
- intersectNameSet :: NameSet -> NameSet -> NameSet
- filterNameSet :: (Name -> Bool) -> NameSet -> NameSet
- delFromNameSet :: NameSet -> Name -> NameSet
- elemNameSet :: Name -> NameSet -> Bool
- minusNameSet :: NameSet -> NameSet -> NameSet
- unionNameSets :: [NameSet] -> NameSet
- unionNameSet :: NameSet -> NameSet -> NameSet
- extendNameSet :: NameSet -> Name -> NameSet
- extendNameSetList :: NameSet -> [Name] -> NameSet
- mkNameSet :: [Name] -> NameSet
- unitNameSet :: Name -> NameSet
- emptyNameSet :: NameSet
- isEmptyNameSet :: NameSet -> Bool
- type NameSet = UniqSet Name
- type FreeVars = NameSet
- type Defs = NameSet
- type Uses = NameSet
- type DefUse = (Maybe Defs, Uses)
- type DefUses = OrdList DefUse
- listTyCon :: TyCon
- typeSymbolKind :: Kind
- typeNatKind :: Kind
- mkBoxedTupleTy :: [Type] -> Type
- heqTyCon :: TyCon
- coercibleTyCon :: TyCon
- unitTy :: Type
- liftedTypeKind :: Kind
- constraintKind :: Kind
- vecElemTyCon :: TyCon
- vecCountTyCon :: TyCon
- runtimeRepTyCon :: TyCon
- runtimeRepTy :: Type
- tupleRepDataConTyCon :: TyCon
- vecRepDataConTyCon :: TyCon
- liftedRepDataConTyCon :: TyCon
- doubleRepDataConTy :: Type
- floatRepDataConTy :: Type
- addrRepDataConTy :: Type
- word64RepDataConTy :: Type
- word32RepDataConTy :: Type
- word16RepDataConTy :: Type
- word8RepDataConTy :: Type
- wordRepDataConTy :: Type
- int64RepDataConTy :: Type
- int32RepDataConTy :: Type
- int16RepDataConTy :: Type
- int8RepDataConTy :: Type
- intRepDataConTy :: Type
- unliftedRepDataConTy :: Type
- liftedRepDataConTy :: Type
- vec64DataConTy :: Type
- vec32DataConTy :: Type
- vec16DataConTy :: Type
- vec8DataConTy :: Type
- vec4DataConTy :: Type
- vec2DataConTy :: Type
- doubleElemRepDataConTy :: Type
- floatElemRepDataConTy :: Type
- word64ElemRepDataConTy :: Type
- word32ElemRepDataConTy :: Type
- word16ElemRepDataConTy :: Type
- word8ElemRepDataConTy :: Type
- int64ElemRepDataConTy :: Type
- int32ElemRepDataConTy :: Type
- int16ElemRepDataConTy :: Type
- int8ElemRepDataConTy :: Type
- anyTypeOfKind :: Kind -> Type
- unboxedTupleKind :: [Type] -> Kind
- mkPromotedListTy :: Kind -> [Type] -> Type
- tupleTyConName :: TupleSort -> Arity -> Name
- pprPrefixName :: NamedThing a => a -> SDoc
- pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc
- getOccFS :: NamedThing a => a -> FastString
- getOccString :: NamedThing a => a -> String
- getSrcSpan :: NamedThing a => a -> SrcSpan
- getSrcLoc :: NamedThing a => a -> SrcLoc
- nameStableString :: Name -> String
- pprNameDefnLoc :: Name -> SDoc
- pprDefinedAt :: Name -> SDoc
- pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc
- pprNameUnqualified :: Name -> SDoc
- stableNameCmp :: Name -> Name -> Ordering
- localiseName :: Name -> Name
- tidyNameOcc :: Name -> OccName -> Name
- setNameLoc :: Name -> SrcSpan -> Name
- setNameUnique :: Name -> Unique -> Name
- mkFCallName :: Unique -> String -> Name
- mkSysTvName :: Unique -> FastString -> Name
- mkSystemVarName :: Unique -> FastString -> Name
- mkSystemNameAt :: Unique -> OccName -> SrcSpan -> Name
- mkSystemName :: Unique -> OccName -> Name
- mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name
- mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name
- mkDerivedInternalName :: (OccName -> OccName) -> Unique -> Name -> Name
- mkClonedInternalName :: Unique -> Name -> Name
- mkInternalName :: Unique -> OccName -> SrcSpan -> Name
- isSystemName :: Name -> Bool
- isVarName :: Name -> Bool
- isValName :: Name -> Bool
- isDataConName :: Name -> Bool
- isTyConName :: Name -> Bool
- isTyVarName :: Name -> Bool
- nameIsFromExternalPackage :: UnitId -> Name -> Bool
- nameIsHomePackageImport :: Module -> Name -> Bool
- nameIsHomePackage :: Module -> Name -> Bool
- nameIsLocalOrFrom :: Module -> Name -> Bool
- nameModule_maybe :: Name -> Maybe Module
- nameModule :: HasDebugCallStack => Name -> Module
- isHoleName :: Name -> Bool
- isInternalName :: Name -> Bool
- isExternalName :: Name -> Bool
- isBuiltInSyntax :: Name -> Bool
- wiredInNameTyThing_maybe :: Name -> Maybe TyThing
- isWiredInName :: Name -> Bool
- nameSrcSpan :: Name -> SrcSpan
- nameSrcLoc :: Name -> SrcLoc
- nameNameSpace :: Name -> NameSpace
- nameOccName :: Name -> OccName
- nameUnique :: Name -> Unique
- data BuiltInSyntax
- class NamedThing a where
- getOccName :: a -> OccName
- getName :: a -> Name
- mkFunTy :: AnonArgFlag -> Type -> Type -> Type
- mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type
- data Type
- = TyVarTy Var
- | AppTy Type Type
- | TyConApp TyCon [KindOrType]
- | ForAllTy !TyCoVarBinder Type
- | FunTy { }
- | LitTy TyLit
- | CastTy Type KindCoercion
- | CoercionTy Coercion
- data TyThing
- data Coercion
- = Refl Type
- | GRefl Role Type MCoercionN
- | TyConAppCo Role TyCon [Coercion]
- | AppCo Coercion CoercionN
- | ForAllCo TyCoVar KindCoercion Coercion
- | FunCo Role Coercion Coercion
- | CoVarCo CoVar
- | AxiomInstCo (CoAxiom Branched) BranchIndex [Coercion]
- | AxiomRuleCo CoAxiomRule [Coercion]
- | UnivCo UnivCoProvenance Role Type Type
- | SymCo Coercion
- | TransCo Coercion Coercion
- | NthCo Role Int Coercion
- | LRCo LeftOrRight CoercionN
- | InstCo Coercion CoercionN
- | KindCo Coercion
- | SubCo CoercionN
- | HoleCo CoercionHole
- data UnivCoProvenance
- data TyLit
- data TyCoBinder
- data MCoercion
- type PredType = Type
- type Kind = Type
- type ThetaType = [PredType]
- type CoercionN = Coercion
- type MCoercionN = MCoercion
- data ArgFlag
- data AnonArgFlag
- data Var
- traceCmd :: DynFlags -> String -> String -> IO a -> IO a
- isWarnMsgFatal :: DynFlags -> WarnMsg -> Maybe (Maybe WarningFlag)
- prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a
- logOutput :: DynFlags -> PprStyle -> MsgDoc -> IO ()
- logInfo :: DynFlags -> PprStyle -> MsgDoc -> IO ()
- printOutputForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO ()
- printInfoForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO ()
- putMsg :: DynFlags -> MsgDoc -> IO ()
- debugTraceMsg :: DynFlags -> Int -> MsgDoc -> IO ()
- withTimingSilentD :: (MonadIO m, HasDynFlags m) => SDoc -> (a -> ()) -> m a -> m a
- withTimingSilent :: MonadIO m => DynFlags -> SDoc -> (a -> ()) -> m a -> m a
- withTimingD :: (MonadIO m, HasDynFlags m) => SDoc -> (a -> ()) -> m a -> m a
- withTiming :: MonadIO m => DynFlags -> SDoc -> (a -> ()) -> m a -> m a
- showPass :: DynFlags -> String -> IO ()
- compilationProgressMsg :: DynFlags -> String -> IO ()
- fatalErrorMsg'' :: FatalMessager -> String -> IO ()
- fatalErrorMsg :: DynFlags -> MsgDoc -> IO ()
- warningMsg :: DynFlags -> MsgDoc -> IO ()
- errorMsg :: DynFlags -> MsgDoc -> IO ()
- dumpSDocWithStyle :: PprStyle -> DynFlags -> DumpFlag -> String -> SDoc -> IO ()
- dumpSDocForUser :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO ()
- mkDumpDoc :: String -> SDoc -> SDoc
- dumpIfSet_dyn_printer :: PrintUnqualified -> DynFlags -> DumpFlag -> SDoc -> IO ()
- dumpIfSet_dyn :: DynFlags -> DumpFlag -> String -> SDoc -> IO ()
- dumpIfSet :: DynFlags -> Bool -> String -> SDoc -> IO ()
- doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO ()
- doIfSet :: Bool -> IO () -> IO ()
- ghcExit :: DynFlags -> Int -> IO ()
- pprLocErrMsg :: ErrMsg -> SDoc
- pprErrMsgBagWithLoc :: Bag ErrMsg -> [SDoc]
- formatErrDoc :: DynFlags -> ErrDoc -> SDoc
- printBagOfErrors :: DynFlags -> Bag ErrMsg -> IO ()
- warningsToMessages :: DynFlags -> WarningMessages -> Messages
- errorsFound :: DynFlags -> Messages -> Bool
- isEmptyMessages :: Messages -> Bool
- emptyMessages :: Messages
- mkPlainWarnMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg
- mkWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg
- mkLongWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg
- mkPlainErrMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg
- mkErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg
- mkLongErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg
- mkErrDoc :: DynFlags -> SrcSpan -> PrintUnqualified -> ErrDoc -> ErrMsg
- makeIntoWarning :: WarnReason -> ErrMsg -> ErrMsg
- pprMessageBag :: Bag MsgDoc -> SDoc
- errDoc :: [MsgDoc] -> [MsgDoc] -> [MsgDoc] -> ErrDoc
- unionMessages :: Messages -> Messages -> Messages
- orValid :: Validity -> Validity -> Validity
- getInvalids :: [Validity] -> [MsgDoc]
- allValid :: [Validity] -> Validity
- andValid :: Validity -> Validity -> Validity
- isValid :: Validity -> Bool
- data Validity
- type Messages = (WarningMessages, ErrorMessages)
- type WarningMessages = Bag WarnMsg
- type ErrorMessages = Bag ErrMsg
- data ErrMsg
- data ErrDoc
- type WarnMsg = ErrMsg
- tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName)
- avoidClashesOccEnv :: TidyOccEnv -> [OccName] -> TidyOccEnv
- initTidyOccEnv :: [OccName] -> TidyOccEnv
- emptyTidyOccEnv :: TidyOccEnv
- mkMethodOcc :: OccName -> OccName
- mkDataCOcc :: OccName -> OccSet -> OccName
- mkDataTOcc :: OccName -> OccSet -> OccName
- mkDFunOcc :: String -> Bool -> OccSet -> OccName
- mkInstTyTcOcc :: String -> OccSet -> OccName
- mkLocalOcc :: Unique -> OccName -> OccName
- mkSuperDictSelOcc :: Int -> OccName -> OccName
- mkSuperDictAuxOcc :: Int -> OccName -> OccName
- mkDataConWorkerOcc :: OccName -> OccName
- mkRecFldSelOcc :: String -> OccName
- mkGen1R :: OccName -> OccName
- mkGenR :: OccName -> OccName
- mkTyConRepOcc :: OccName -> OccName
- mkMaxTagOcc :: OccName -> OccName
- mkTag2ConOcc :: OccName -> OccName
- mkCon2TagOcc :: OccName -> OccName
- mkEqPredCoOcc :: OccName -> OccName
- mkInstTyCoOcc :: OccName -> OccName
- mkNewTyCoOcc :: OccName -> OccName
- mkClassDataConOcc :: OccName -> OccName
- mkRepEqOcc :: OccName -> OccName
- mkForeignExportOcc :: OccName -> OccName
- mkSpecOcc :: OccName -> OccName
- mkIPOcc :: OccName -> OccName
- mkDictOcc :: OccName -> OccName
- mkClassOpAuxOcc :: OccName -> OccName
- mkDefaultMethodOcc :: OccName -> OccName
- mkBuilderOcc :: OccName -> OccName
- mkMatcherOcc :: OccName -> OccName
- mkWorkerOcc :: OccName -> OccName
- mkDataConWrapperOcc :: OccName -> OccName
- isTypeableBindOcc :: OccName -> Bool
- isDefaultMethodOcc :: OccName -> Bool
- isDerivedOccName :: OccName -> Bool
- startsWithUnderscore :: OccName -> Bool
- parenSymOcc :: OccName -> SDoc -> SDoc
- isSymOcc :: OccName -> Bool
- isDataSymOcc :: OccName -> Bool
- isDataOcc :: OccName -> Bool
- isValOcc :: OccName -> Bool
- isTcOcc :: OccName -> Bool
- isTvOcc :: OccName -> Bool
- isVarOcc :: OccName -> Bool
- setOccNameSpace :: NameSpace -> OccName -> OccName
- occNameString :: OccName -> String
- filterOccSet :: (OccName -> Bool) -> OccSet -> OccSet
- intersectsOccSet :: OccSet -> OccSet -> Bool
- intersectOccSet :: OccSet -> OccSet -> OccSet
- isEmptyOccSet :: OccSet -> Bool
- elemOccSet :: OccName -> OccSet -> Bool
- minusOccSet :: OccSet -> OccSet -> OccSet
- unionManyOccSets :: [OccSet] -> OccSet
- unionOccSets :: OccSet -> OccSet -> OccSet
- extendOccSetList :: OccSet -> [OccName] -> OccSet
- extendOccSet :: OccSet -> OccName -> OccSet
- mkOccSet :: [OccName] -> OccSet
- unitOccSet :: OccName -> OccSet
- emptyOccSet :: OccSet
- pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc
- alterOccEnv :: (Maybe elt -> Maybe elt) -> OccEnv elt -> OccName -> OccEnv elt
- filterOccEnv :: (elt -> Bool) -> OccEnv elt -> OccEnv elt
- delListFromOccEnv :: OccEnv a -> [OccName] -> OccEnv a
- delFromOccEnv :: OccEnv a -> OccName -> OccEnv a
- mkOccEnv_C :: (a -> a -> a) -> [(OccName, a)] -> OccEnv a
- mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b
- extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b
- extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a
- plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a
- plusOccEnv :: OccEnv a -> OccEnv a -> OccEnv a
- occEnvElts :: OccEnv a -> [a]
- foldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b
- elemOccEnv :: OccName -> OccEnv a -> Bool
- mkOccEnv :: [(OccName, a)] -> OccEnv a
- lookupOccEnv :: OccEnv a -> OccName -> Maybe a
- extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a
- extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a
- unitOccEnv :: OccName -> a -> OccEnv a
- emptyOccEnv :: OccEnv a
- nameSpacesRelated :: NameSpace -> NameSpace -> Bool
- demoteOccName :: OccName -> Maybe OccName
- mkClsOccFS :: FastString -> OccName
- mkClsOcc :: String -> OccName
- mkTcOccFS :: FastString -> OccName
- mkTcOcc :: String -> OccName
- mkTyVarOccFS :: FastString -> OccName
- mkTyVarOcc :: String -> OccName
- mkDataOccFS :: FastString -> OccName
- mkDataOcc :: String -> OccName
- mkVarOccFS :: FastString -> OccName
- mkVarOcc :: String -> OccName
- mkOccNameFS :: NameSpace -> FastString -> OccName
- mkOccName :: NameSpace -> String -> OccName
- pprOccName :: OccName -> SDoc
- pprNameSpaceBrief :: NameSpace -> SDoc
- pprNonVarNameSpace :: NameSpace -> SDoc
- pprNameSpace :: NameSpace -> SDoc
- isValNameSpace :: NameSpace -> Bool
- isVarNameSpace :: NameSpace -> Bool
- isTvNameSpace :: NameSpace -> Bool
- isTcClsNameSpace :: NameSpace -> Bool
- isDataConNameSpace :: NameSpace -> Bool
- tvName :: NameSpace
- srcDataName :: NameSpace
- dataName :: NameSpace
- tcClsName :: NameSpace
- clsName :: NameSpace
- tcName :: NameSpace
- data NameSpace
- class HasOccName name where
- data OccEnv a
- type OccSet = UniqSet OccName
- type TidyOccEnv = UniqFM Int
- emptyFilesToClean :: FilesToClean
- isBmi2Enabled :: DynFlags -> Bool
- isBmiEnabled :: DynFlags -> Bool
- isAvx512pfEnabled :: DynFlags -> Bool
- isAvx512fEnabled :: DynFlags -> Bool
- isAvx512erEnabled :: DynFlags -> Bool
- isAvx512cdEnabled :: DynFlags -> Bool
- isAvx2Enabled :: DynFlags -> Bool
- isAvxEnabled :: DynFlags -> Bool
- isSse4_2Enabled :: DynFlags -> Bool
- isSse2Enabled :: DynFlags -> Bool
- isSseEnabled :: DynFlags -> Bool
- setUnsafeGlobalDynFlags :: DynFlags -> IO ()
- makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Located String])
- tARGET_MAX_WORD :: DynFlags -> Integer
- tARGET_MAX_INT :: DynFlags -> Integer
- tARGET_MIN_INT :: DynFlags -> Integer
- mAX_PTR_TAG :: DynFlags -> Int
- tAG_MASK :: DynFlags -> Int
- wordAlignment :: DynFlags -> Alignment
- wORD_SIZE_IN_BITS :: DynFlags -> Int
- bLOCK_SIZE_W :: DynFlags -> Int
- iLDV_STATE_USE :: DynFlags -> Integer
- iLDV_STATE_CREATE :: DynFlags -> Integer
- iLDV_CREATE_MASK :: DynFlags -> Integer
- lDV_SHIFT :: DynFlags -> Int
- dYNAMIC_BY_DEFAULT :: DynFlags -> Bool
- wORDS_BIGENDIAN :: DynFlags -> Bool
- tAG_BITS :: DynFlags -> Int
- bITMAP_BITS_SHIFT :: DynFlags -> Int
- cLONG_LONG_SIZE :: DynFlags -> Int
- cLONG_SIZE :: DynFlags -> Int
- cINT_SIZE :: DynFlags -> Int
- dOUBLE_SIZE :: DynFlags -> Int
- wORD_SIZE :: DynFlags -> Int
- aP_STACK_SPLIM :: DynFlags -> Int
- rESERVED_STACK_WORDS :: DynFlags -> Int
- rESERVED_C_STACK_BYTES :: DynFlags -> Int
- mAX_Real_Long_REG :: DynFlags -> Int
- mAX_Real_XMM_REG :: DynFlags -> Int
- mAX_Real_Double_REG :: DynFlags -> Int
- mAX_Real_Float_REG :: DynFlags -> Int
- mAX_Real_Vanilla_REG :: DynFlags -> Int
- mAX_XMM_REG :: DynFlags -> Int
- mAX_Long_REG :: DynFlags -> Int
- mAX_Double_REG :: DynFlags -> Int
- mAX_Float_REG :: DynFlags -> Int
- mAX_Vanilla_REG :: DynFlags -> Int
- mUT_ARR_PTRS_CARD_BITS :: DynFlags -> Int
- mAX_CHARLIKE :: DynFlags -> Int
- mIN_CHARLIKE :: DynFlags -> Int
- mAX_INTLIKE :: DynFlags -> Int
- mIN_INTLIKE :: DynFlags -> Int
- mIN_PAYLOAD_SIZE :: DynFlags -> Int
- mAX_SPEC_AP_SIZE :: DynFlags -> Int
- mAX_SPEC_SELECTEE_SIZE :: DynFlags -> Int
- oFFSET_StgFunInfoExtraRev_arity :: DynFlags -> Int
- sIZEOF_StgFunInfoExtraRev :: DynFlags -> Int
- oFFSET_StgFunInfoExtraFwd_arity :: DynFlags -> Int
- oFFSET_StgUpdateFrame_updatee :: DynFlags -> Int
- oFFSET_StgStack_stack :: DynFlags -> Int
- oFFSET_StgStack_sp :: DynFlags -> Int
- oFFSET_StgTSO_stackobj :: DynFlags -> Int
- oFFSET_StgTSO_cccs :: DynFlags -> Int
- oFFSET_StgTSO_alloc_limit :: DynFlags -> Int
- oFFSET_StgArrBytes_bytes :: DynFlags -> Int
- sIZEOF_StgArrBytes_NoHdr :: DynFlags -> Int
- oFFSET_StgSmallMutArrPtrs_ptrs :: DynFlags -> Int
- sIZEOF_StgSmallMutArrPtrs_NoHdr :: DynFlags -> Int
- oFFSET_StgMutArrPtrs_size :: DynFlags -> Int
- oFFSET_StgMutArrPtrs_ptrs :: DynFlags -> Int
- sIZEOF_StgMutArrPtrs_NoHdr :: DynFlags -> Int
- sIZEOF_StgUpdateFrame_NoHdr :: DynFlags -> Int
- oFFSET_StgEntCounter_entry_count :: DynFlags -> Int
- oFFSET_StgEntCounter_link :: DynFlags -> Int
- oFFSET_StgEntCounter_registeredp :: DynFlags -> Int
- oFFSET_StgEntCounter_allocd :: DynFlags -> Int
- oFFSET_StgEntCounter_allocs :: DynFlags -> Int
- sIZEOF_StgSMPThunkHeader :: DynFlags -> Int
- oFFSET_StgHeader_ldvw :: DynFlags -> Int
- oFFSET_StgHeader_ccs :: DynFlags -> Int
- oFFSET_CostCentreStack_scc_count :: DynFlags -> Int
- oFFSET_CostCentreStack_mem_alloc :: DynFlags -> Int
- sIZEOF_CostCentreStack :: DynFlags -> Int
- oFFSET_bdescr_flags :: DynFlags -> Int
- oFFSET_bdescr_blocks :: DynFlags -> Int
- oFFSET_bdescr_free :: DynFlags -> Int
- oFFSET_bdescr_start :: DynFlags -> Int
- oFFSET_Capability_r :: DynFlags -> Int
- oFFSET_stgGCFun :: DynFlags -> Int
- oFFSET_stgGCEnter1 :: DynFlags -> Int
- oFFSET_stgEagerBlackholeInfo :: DynFlags -> Int
- oFFSET_StgRegTable_rHpAlloc :: DynFlags -> Int
- oFFSET_StgRegTable_rCurrentNursery :: DynFlags -> Int
- oFFSET_StgRegTable_rCurrentTSO :: DynFlags -> Int
- oFFSET_StgRegTable_rCCCS :: DynFlags -> Int
- oFFSET_StgRegTable_rHpLim :: DynFlags -> Int
- oFFSET_StgRegTable_rHp :: DynFlags -> Int
- oFFSET_StgRegTable_rSpLim :: DynFlags -> Int
- oFFSET_StgRegTable_rSp :: DynFlags -> Int
- oFFSET_StgRegTable_rL1 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM6 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM5 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM4 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM3 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM2 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM1 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM6 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM5 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM4 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM3 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM2 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM1 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM6 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM5 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM4 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM3 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM2 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM1 :: DynFlags -> Int
- oFFSET_StgRegTable_rD6 :: DynFlags -> Int
- oFFSET_StgRegTable_rD5 :: DynFlags -> Int
- oFFSET_StgRegTable_rD4 :: DynFlags -> Int
- oFFSET_StgRegTable_rD3 :: DynFlags -> Int
- oFFSET_StgRegTable_rD2 :: DynFlags -> Int
- oFFSET_StgRegTable_rD1 :: DynFlags -> Int
- oFFSET_StgRegTable_rF6 :: DynFlags -> Int
- oFFSET_StgRegTable_rF5 :: DynFlags -> Int
- oFFSET_StgRegTable_rF4 :: DynFlags -> Int
- oFFSET_StgRegTable_rF3 :: DynFlags -> Int
- oFFSET_StgRegTable_rF2 :: DynFlags -> Int
- oFFSET_StgRegTable_rF1 :: DynFlags -> Int
- oFFSET_StgRegTable_rR10 :: DynFlags -> Int
- oFFSET_StgRegTable_rR9 :: DynFlags -> Int
- oFFSET_StgRegTable_rR8 :: DynFlags -> Int
- oFFSET_StgRegTable_rR7 :: DynFlags -> Int
- oFFSET_StgRegTable_rR6 :: DynFlags -> Int
- oFFSET_StgRegTable_rR5 :: DynFlags -> Int
- oFFSET_StgRegTable_rR4 :: DynFlags -> Int
- oFFSET_StgRegTable_rR3 :: DynFlags -> Int
- oFFSET_StgRegTable_rR2 :: DynFlags -> Int
- oFFSET_StgRegTable_rR1 :: DynFlags -> Int
- tICKY_BIN_COUNT :: DynFlags -> Int
- bLOCKS_PER_MBLOCK :: DynFlags -> Int
- bLOCK_SIZE :: DynFlags -> Int
- pROF_HDR_SIZE :: DynFlags -> Int
- sTD_HDR_SIZE :: DynFlags -> Int
- cONTROL_GROUP_CONST_291 :: DynFlags -> Int
- compilerInfo :: DynFlags -> [(String, String)]
- picPOpts :: DynFlags -> [String]
- picCCOpts :: DynFlags -> [String]
- setTmpDir :: FilePath -> DynFlags -> DynFlags
- setFlagsFromEnvFile :: FilePath -> String -> DynP ()
- canonicalizeModuleIfHome :: DynFlags -> Module -> Module
- canonicalizeHomeModule :: DynFlags -> ModuleName -> Module
- setUnitId :: String -> DynFlags -> DynFlags
- unSetGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags
- setGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags
- addWay' :: Way -> DynFlags -> DynFlags
- dynamicGhc :: Bool
- rtsIsProfiled :: Bool
- glasgowExtsFlags :: [Extension]
- warningHierarchies :: [[String]]
- warningGroups :: [(String, [WarningFlag])]
- xFlags :: [FlagSpec Extension]
- supportedLanguagesAndExtensions :: PlatformMini -> [String]
- fLangFlags :: [FlagSpec Extension]
- fFlags :: [FlagSpec GeneralFlag]
- wWarningFlags :: [FlagSpec WarningFlag]
- flagsForCompletion :: Bool -> [String]
- flagsPackage :: [Flag (CmdLineP DynFlags)]
- flagsDynamic :: [Flag (CmdLineP DynFlags)]
- flagsAll :: [Flag (CmdLineP DynFlags)]
- allNonDeprecatedFlags :: [String]
- updateWays :: DynFlags -> DynFlags
- putLogMsg :: DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO ()
- parseDynamicFlagsFull :: MonadIO m => [Flag (CmdLineP DynFlags)] -> Bool -> DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- updOptLevel :: Int -> DynFlags -> DynFlags
- addPluginModuleName :: String -> DynFlags -> DynFlags
- thisPackage :: DynFlags -> UnitId
- thisUnitIdInsts :: DynFlags -> [(ModuleName, Module)]
- thisComponentId :: DynFlags -> ComponentId
- getVerbFlags :: DynFlags -> [String]
- getOpts :: DynFlags -> (DynFlags -> [a]) -> [a]
- unsafeFlagsForInfer :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)]
- unsafeFlags :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)]
- safeImplicitImpsReq :: DynFlags -> Bool
- safeDirectImpsReq :: DynFlags -> Bool
- safeImportsOn :: DynFlags -> Bool
- safeInferOn :: DynFlags -> Bool
- safeLanguageOn :: DynFlags -> Bool
- safeHaskellModeEnabled :: DynFlags -> Bool
- safeHaskellOn :: DynFlags -> Bool
- packageTrustOn :: DynFlags -> Bool
- dynFlagDependencies :: DynFlags -> [ModuleName]
- lang_set :: DynFlags -> Maybe Language -> DynFlags
- xopt_set_unlessExplSpec :: Extension -> (DynFlags -> Extension -> DynFlags) -> DynFlags -> DynFlags
- xopt_unset :: DynFlags -> Extension -> DynFlags
- xopt_set :: DynFlags -> Extension -> DynFlags
- xopt :: Extension -> DynFlags -> Bool
- wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags
- wopt_set_fatal :: DynFlags -> WarningFlag -> DynFlags
- wopt_fatal :: WarningFlag -> DynFlags -> Bool
- wopt_unset :: DynFlags -> WarningFlag -> DynFlags
- wopt_set :: DynFlags -> WarningFlag -> DynFlags
- wopt :: WarningFlag -> DynFlags -> Bool
- gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
- gopt_set :: DynFlags -> GeneralFlag -> DynFlags
- gopt :: GeneralFlag -> DynFlags -> Bool
- dopt_unset :: DynFlags -> DumpFlag -> DynFlags
- dopt_set :: DynFlags -> DumpFlag -> DynFlags
- dopt :: DumpFlag -> DynFlags -> Bool
- hasNoOptCoercion :: DynFlags -> Bool
- hasNoStateHack :: DynFlags -> Bool
- languageExtensions :: Maybe Language -> [Extension]
- defaultFlushErr :: FlushErr
- defaultFlushOut :: FlushOut
- defaultLogActionHPutStrDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO ()
- defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO ()
- defaultLogAction :: LogAction
- defaultFatalMessager :: FatalMessager
- interpreterDynamic :: DynFlags -> Bool
- interpreterProfiled :: DynFlags -> Bool
- interpWays :: [Way]
- defaultWays :: Settings -> [Way]
- defaultDynFlags :: Settings -> LlvmConfig -> DynFlags
- initDynFlags :: DynFlags -> IO DynFlags
- dynamicOutputFile :: DynFlags -> FilePath -> FilePath
- dynamicTooMkDynamicDynFlags :: DynFlags -> DynFlags
- whenCannotGenerateDynamicToo :: MonadIO m => DynFlags -> m () -> m ()
- ifGeneratingDynamicToo :: MonadIO m => DynFlags -> m a -> m a -> m a
- whenGeneratingDynamicToo :: MonadIO m => DynFlags -> m () -> m ()
- wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag]
- wayGeneralFlags :: Platform -> Way -> [GeneralFlag]
- wayRTSOnly :: Way -> Bool
- mkBuildTag :: [Way] -> String
- positionIndependent :: DynFlags -> Bool
- defaultObjectTarget :: DynFlags -> HscTarget
- packageFlagsChanged :: DynFlags -> DynFlags -> Bool
- isNoLink :: GhcLink -> Bool
- isOneShot :: GhcMode -> Bool
- targetRetainsAllBindings :: HscTarget -> Bool
- isObjectTarget :: HscTarget -> Bool
- versionedFilePath :: DynFlags -> FilePath
- versionedAppDir :: DynFlags -> MaybeT IO FilePath
- tablesNextToCode :: DynFlags -> Bool
- opt_i :: DynFlags -> [String]
- opt_lc :: DynFlags -> [String]
- opt_lo :: DynFlags -> [String]
- opt_lcc :: DynFlags -> [String]
- opt_windres :: DynFlags -> [String]
- opt_lm :: DynFlags -> [String]
- opt_l :: DynFlags -> [String]
- opt_a :: DynFlags -> [String]
- opt_cxx :: DynFlags -> [String]
- opt_c :: DynFlags -> [String]
- opt_F :: DynFlags -> [String]
- opt_P_signature :: DynFlags -> ([String], Fingerprint)
- opt_P :: DynFlags -> [String]
- opt_L :: DynFlags -> [String]
- pgm_i :: DynFlags -> String
- pgm_lc :: DynFlags -> (String, [Option])
- pgm_lo :: DynFlags -> (String, [Option])
- pgm_ranlib :: DynFlags -> String
- pgm_ar :: DynFlags -> String
- pgm_lcc :: DynFlags -> (String, [Option])
- pgm_libtool :: DynFlags -> String
- pgm_windres :: DynFlags -> String
- pgm_T :: DynFlags -> String
- pgm_dll :: DynFlags -> (String, [Option])
- pgm_lm :: DynFlags -> (String, [Option])
- pgm_l :: DynFlags -> (String, [Option])
- pgm_a :: DynFlags -> (String, [Option])
- pgm_c :: DynFlags -> String
- pgm_F :: DynFlags -> String
- pgm_P :: DynFlags -> (String, [Option])
- pgm_L :: DynFlags -> String
- systemPackageConfig :: DynFlags -> FilePath
- extraGccViaCFlags :: DynFlags -> [String]
- tmpDir :: DynFlags -> String
- topDir :: DynFlags -> FilePath
- ghciUsagePath :: DynFlags -> FilePath
- ghcUsagePath :: DynFlags -> FilePath
- projectVersion :: DynFlags -> String
- programName :: DynFlags -> String
- settings :: DynFlags -> Settings
- backendMaintainsCfg :: DynFlags -> Bool
- flattenIncludes :: IncludeSpecs -> [String]
- addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
- addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs
- optimisationFlags :: EnumSet GeneralFlag
- data WarnReason
- = NoReason
- | Reason !WarningFlag
- | ErrReason !(Maybe WarningFlag)
- data IncludeSpecs = IncludeSpecs {
- includePathsQuote :: [String]
- includePathsGlobal :: [String]
- data WarningFlag
- = Opt_WarnDuplicateExports
- | Opt_WarnDuplicateConstraints
- | Opt_WarnRedundantConstraints
- | Opt_WarnHiShadows
- | Opt_WarnImplicitPrelude
- | Opt_WarnIncompletePatterns
- | Opt_WarnIncompleteUniPatterns
- | Opt_WarnIncompletePatternsRecUpd
- | Opt_WarnOverflowedLiterals
- | Opt_WarnEmptyEnumerations
- | Opt_WarnMissingFields
- | Opt_WarnMissingImportList
- | Opt_WarnMissingMethods
- | Opt_WarnMissingSignatures
- | Opt_WarnMissingLocalSignatures
- | Opt_WarnNameShadowing
- | Opt_WarnOverlappingPatterns
- | Opt_WarnTypeDefaults
- | Opt_WarnMonomorphism
- | Opt_WarnUnusedTopBinds
- | Opt_WarnUnusedLocalBinds
- | Opt_WarnUnusedPatternBinds
- | Opt_WarnUnusedImports
- | Opt_WarnUnusedMatches
- | Opt_WarnUnusedTypePatterns
- | Opt_WarnUnusedForalls
- | Opt_WarnUnusedRecordWildcards
- | Opt_WarnRedundantRecordWildcards
- | Opt_WarnWarningsDeprecations
- | Opt_WarnDeprecatedFlags
- | Opt_WarnMissingMonadFailInstances
- | Opt_WarnSemigroup
- | Opt_WarnDodgyExports
- | Opt_WarnDodgyImports
- | Opt_WarnOrphans
- | Opt_WarnAutoOrphans
- | Opt_WarnIdentities
- | Opt_WarnTabs
- | Opt_WarnUnrecognisedPragmas
- | Opt_WarnDodgyForeignImports
- | Opt_WarnUnusedDoBind
- | Opt_WarnWrongDoBind
- | Opt_WarnAlternativeLayoutRuleTransitional
- | Opt_WarnUnsafe
- | Opt_WarnSafe
- | Opt_WarnTrustworthySafe
- | Opt_WarnMissedSpecs
- | Opt_WarnAllMissedSpecs
- | Opt_WarnUnsupportedCallingConventions
- | Opt_WarnUnsupportedLlvmVersion
- | Opt_WarnMissedExtraSharedLib
- | Opt_WarnInlineRuleShadowing
- | Opt_WarnTypedHoles
- | Opt_WarnPartialTypeSignatures
- | Opt_WarnMissingExportedSignatures
- | Opt_WarnUntickedPromotedConstructors
- | Opt_WarnDerivingTypeable
- | Opt_WarnDeferredTypeErrors
- | Opt_WarnDeferredOutOfScopeVariables
- | Opt_WarnNonCanonicalMonadInstances
- | Opt_WarnNonCanonicalMonadFailInstances
- | Opt_WarnNonCanonicalMonoidInstances
- | Opt_WarnMissingPatternSynonymSignatures
- | Opt_WarnUnrecognisedWarningFlags
- | Opt_WarnSimplifiableClassConstraints
- | Opt_WarnCPPUndef
- | Opt_WarnUnbangedStrictPatterns
- | Opt_WarnMissingHomeModules
- | Opt_WarnPartialFields
- | Opt_WarnMissingExportList
- | Opt_WarnInaccessibleCode
- | Opt_WarnStarIsType
- | Opt_WarnStarBinder
- | Opt_WarnImplicitKindVars
- | Opt_WarnSpaceAfterBang
- | Opt_WarnMissingDerivingStrategies
- | Opt_WarnPrepositiveQualifiedModule
- | Opt_WarnUnusedPackages
- | Opt_WarnInferredSafeImports
- | Opt_WarnMissingSafeHaskellMode
- | Opt_WarnCompatUnqualifiedImports
- | Opt_WarnDerivingDefaults
- data Language
- data SafeHaskellMode
- data CfgWeights = CFGWeights {}
- class HasDynFlags (m :: Type -> Type) where
- getDynFlags :: m DynFlags
- class ContainsDynFlags t where
- extractDynFlags :: t -> DynFlags
- data ProfAuto
- data LlvmTarget = LlvmTarget {
- lDataLayout :: String
- lCPU :: String
- lAttributes :: [String]
- data LlvmConfig = LlvmConfig {
- llvmTargets :: [(String, LlvmTarget)]
- llvmPasses :: [(Int, String)]
- data HscTarget
- data GhcMode
- data GhcLink
- data PackageArg
- data ModRenaming = ModRenaming {}
- newtype IgnorePackageFlag = IgnorePackage String
- data TrustFlag
- data PackageFlag
- data PackageDBFlag
- data DynLibLoader
- data RtsOptsEnabled
- data Way
- type FatalMessager = String -> IO ()
- type LogAction = DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO ()
- newtype FlushOut = FlushOut (IO ())
- newtype FlushErr = FlushErr (IO ())
- data FlagSpec flag = FlagSpec {
- flagSpecName :: String
- flagSpecFlag :: flag
- flagSpecAction :: TurnOnFlag -> DynP ()
- flagSpecGhcMode :: GhcFlagMode
- data PkgConfRef
- data LinkerInfo
- data CompilerInfo
- = GCC
- | Clang
- | AppleClang
- | AppleClang51
- | UnknownCC
- data FilesToClean = FilesToClean {
- ftcGhcSession :: !(Set FilePath)
- ftcCurrentModule :: !(Set FilePath)
- isHsigFile :: HscSource -> Bool
- isHsBootOrSig :: HscSource -> Bool
- hscSourceString :: HscSource -> String
- data HscSource
- data Phase
- unitModuleSet :: Module -> ModuleSet
- unionModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
- delModuleSet :: ModuleSet -> Module -> ModuleSet
- minusModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
- intersectModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
- elemModuleSet :: Module -> ModuleSet -> Bool
- moduleSetElts :: ModuleSet -> [Module]
- emptyModuleSet :: ModuleSet
- extendModuleSetList :: ModuleSet -> [Module] -> ModuleSet
- extendModuleSet :: ModuleSet -> Module -> ModuleSet
- mkModuleSet :: [Module] -> ModuleSet
- isEmptyModuleEnv :: ModuleEnv a -> Bool
- unitModuleEnv :: Module -> a -> ModuleEnv a
- moduleEnvToList :: ModuleEnv a -> [(Module, a)]
- moduleEnvElts :: ModuleEnv a -> [a]
- moduleEnvKeys :: ModuleEnv a -> [Module]
- emptyModuleEnv :: ModuleEnv a
- mkModuleEnv :: [(Module, a)] -> ModuleEnv a
- mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b
- lookupWithDefaultModuleEnv :: ModuleEnv a -> a -> Module -> a
- lookupModuleEnv :: ModuleEnv a -> Module -> Maybe a
- plusModuleEnv :: ModuleEnv a -> ModuleEnv a -> ModuleEnv a
- delModuleEnv :: ModuleEnv a -> Module -> ModuleEnv a
- delModuleEnvList :: ModuleEnv a -> [Module] -> ModuleEnv a
- plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a
- extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a
- extendModuleEnvList :: ModuleEnv a -> [(Module, a)] -> ModuleEnv a
- extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a
- extendModuleEnv :: ModuleEnv a -> Module -> a -> ModuleEnv a
- elemModuleEnv :: Module -> ModuleEnv a -> Bool
- filterModuleEnv :: (Module -> a -> Bool) -> ModuleEnv a -> ModuleEnv a
- wiredInUnitIds :: [UnitId]
- isHoleModule :: Module -> Bool
- isInteractiveModule :: Module -> Bool
- mainUnitId :: UnitId
- interactiveUnitId :: UnitId
- thisGhcUnitId :: UnitId
- thUnitId :: UnitId
- rtsUnitId :: UnitId
- baseUnitId :: UnitId
- integerUnitId :: UnitId
- primUnitId :: UnitId
- parseModSubst :: ReadP [(ModuleName, Module)]
- parseModuleId :: ReadP Module
- parseComponentId :: ReadP ComponentId
- parseUnitId :: ReadP UnitId
- parseModuleName :: ReadP ModuleName
- generalizeIndefModule :: IndefModule -> IndefModule
- generalizeIndefUnitId :: IndefUnitId -> IndefUnitId
- splitUnitIdInsts :: UnitId -> (InstalledUnitId, Maybe IndefUnitId)
- splitModuleInsts :: Module -> (InstalledModule, Maybe IndefModule)
- renameHoleUnitId' :: PackageConfigMap -> ShHoleSubst -> UnitId -> UnitId
- renameHoleModule' :: PackageConfigMap -> ShHoleSubst -> Module -> Module
- renameHoleUnitId :: DynFlags -> ShHoleSubst -> UnitId -> UnitId
- renameHoleModule :: DynFlags -> ShHoleSubst -> Module -> Module
- stringToUnitId :: String -> UnitId
- fsToUnitId :: FastString -> UnitId
- newSimpleUnitId :: ComponentId -> UnitId
- stableUnitIdCmp :: UnitId -> UnitId -> Ordering
- newUnitId :: ComponentId -> [(ModuleName, Module)] -> UnitId
- hashUnitId :: ComponentId -> [(ModuleName, Module)] -> FastString
- unitIdIsDefinite :: UnitId -> Bool
- unitIdFreeHoles :: UnitId -> UniqDSet ModuleName
- delInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> InstalledModuleEnv a
- filterInstalledModuleEnv :: (InstalledModule -> a -> Bool) -> InstalledModuleEnv a -> InstalledModuleEnv a
- extendInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> a -> InstalledModuleEnv a
- lookupInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> Maybe a
- emptyInstalledModuleEnv :: InstalledModuleEnv a
- installedUnitIdEq :: InstalledUnitId -> UnitId -> Bool
- installedModuleEq :: InstalledModule -> Module -> Bool
- stringToInstalledUnitId :: String -> InstalledUnitId
- componentIdToInstalledUnitId :: ComponentId -> InstalledUnitId
- fsToInstalledUnitId :: FastString -> InstalledUnitId
- installedUnitIdString :: InstalledUnitId -> String
- toInstalledUnitId :: UnitId -> InstalledUnitId
- indefModuleToModule :: DynFlags -> IndefModule -> Module
- indefUnitIdToUnitId :: DynFlags -> IndefUnitId -> UnitId
- newIndefUnitId :: ComponentId -> [(ModuleName, Module)] -> IndefUnitId
- unitIdKey :: UnitId -> Unique
- unitIdFS :: UnitId -> FastString
- pprModule :: Module -> SDoc
- mkModule :: UnitId -> ModuleName -> Module
- stableModuleCmp :: Module -> Module -> Ordering
- mkHoleModule :: ModuleName -> Module
- moduleIsDefinite :: Module -> Bool
- moduleFreeHoles :: Module -> UniqDSet ModuleName
- moduleNameColons :: ModuleName -> String
- moduleNameSlashes :: ModuleName -> String
- mkModuleNameFS :: FastString -> ModuleName
- mkModuleName :: String -> ModuleName
- moduleStableString :: Module -> String
- moduleNameString :: ModuleName -> String
- moduleNameFS :: ModuleName -> FastString
- pprModuleName :: ModuleName -> SDoc
- stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering
- addBootSuffixLocnOut :: ModLocation -> ModLocation
- addBootSuffixLocn :: ModLocation -> ModLocation
- addBootSuffix_maybe :: Bool -> FilePath -> FilePath
- addBootSuffix :: FilePath -> FilePath
- data ModLocation = ModLocation {}
- class ContainsModule t where
- extractModule :: t -> Module
- class HasModule (m :: Type -> Type) where
- data IndefUnitId = IndefUnitId {}
- data IndefModule = IndefModule {}
- data InstalledModule = InstalledModule {}
- newtype DefUnitId = DefUnitId {}
- data InstalledModuleEnv elt
- type ShHoleSubst = ModuleNameEnv Module
- data ModuleEnv elt
- type ModuleSet = Set NDModule
- type ModuleNameEnv elt = UniqFM elt
- type DModuleNameEnv elt = UniqDFM elt
- mkFsEnv :: [(FastString, a)] -> FastStringEnv a
- lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a
- extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a
- emptyFsEnv :: FastStringEnv a
- type FastStringEnv a = UniqFM a
- initExitJoinUnique :: Unique
- mkTcOccUnique :: FastString -> Unique
- mkTvOccUnique :: FastString -> Unique
- mkDataOccUnique :: FastString -> Unique
- mkVarOccUnique :: FastString -> Unique
- mkCostCentreUnique :: Int -> Unique
- mkRegClassUnique :: Int -> Unique
- mkRegPairUnique :: Int -> Unique
- mkRegSubUnique :: Int -> Unique
- mkRegSingleUnique :: Int -> Unique
- mkPseudoUniqueH :: Int -> Unique
- mkPseudoUniqueE :: Int -> Unique
- mkPseudoUniqueD :: Int -> Unique
- mkBuiltinUnique :: Int -> Unique
- initTyVarUnique :: Unique
- mkPreludeMiscIdUnique :: Int -> Unique
- mkPrimOpWrapperUnique :: Int -> Unique
- mkPrimOpIdUnique :: Int -> Unique
- dataConTyRepNameUnique :: Unique -> Unique
- dataConWorkerUnique :: Unique -> Unique
- mkPreludeDataConUnique :: Arity -> Unique
- tyConRepNameUnique :: Unique -> Unique
- mkPreludeTyConUnique :: Int -> Unique
- mkPreludeClassUnique :: Int -> Unique
- mkCoVarUnique :: Int -> Unique
- mkAlphaTyVarUnique :: Int -> Unique
- pprUniqueAlways :: Unique -> SDoc
- nonDetCmpUnique :: Unique -> Unique -> Ordering
- ltUnique :: Unique -> Unique -> Bool
- eqUnique :: Unique -> Unique -> Bool
- hasKey :: Uniquable a => a -> Unique -> Bool
- isValidKnownKeyUnique :: Unique -> Bool
- unpkUnique :: Unique -> (Char, Int)
- mkUnique :: Char -> Int -> Unique
- newTagUnique :: Unique -> Char -> Unique
- deriveUnique :: Unique -> Int -> Unique
- getKey :: Unique -> Int
- mkUniqueGrimily :: Int -> Unique
- uNIQUE_BITS :: Int
- data Unique
- class Uniquable a where
- isKindLevel :: TypeOrKind -> Bool
- isTypeLevel :: TypeOrKind -> Bool
- mkIntWithInf :: Int -> IntWithInf
- treatZeroAsInf :: Int -> IntWithInf
- intGtLimit :: Int -> IntWithInf -> Bool
- infinity :: IntWithInf
- integralFractionalLit :: Bool -> Integer -> FractionalLit
- negateFractionalLit :: FractionalLit -> FractionalLit
- mkFractionalLit :: Real a => a -> FractionalLit
- negateIntegralLit :: IntegralLit -> IntegralLit
- mkIntegralLit :: Integral a => a -> IntegralLit
- isEarlyActive :: Activation -> Bool
- isAlwaysActive :: Activation -> Bool
- isNeverActive :: Activation -> Bool
- competesWith :: Activation -> Activation -> Bool
- isActiveIn :: PhaseNum -> Activation -> Bool
- isActive :: CompilerPhase -> Activation -> Bool
- pprInlineDebug :: InlinePragma -> SDoc
- pprInline :: InlinePragma -> SDoc
- setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma
- setInlinePragmaActivation :: InlinePragma -> Activation -> InlinePragma
- inlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo
- inlinePragmaActivation :: InlinePragma -> Activation
- inlinePragmaSat :: InlinePragma -> Maybe Arity
- isAnyInlinePragma :: InlinePragma -> Bool
- isInlinablePragma :: InlinePragma -> Bool
- isInlinePragma :: InlinePragma -> Bool
- isDefaultInlinePragma :: InlinePragma -> Bool
- dfunInlinePragma :: InlinePragma
- inlinePragmaSpec :: InlinePragma -> InlineSpec
- neverInlinePragma :: InlinePragma
- alwaysInlinePragma :: InlinePragma
- defaultInlinePragma :: InlinePragma
- noUserInlineSpec :: InlineSpec -> Bool
- isFunLike :: RuleMatchInfo -> Bool
- isConLike :: RuleMatchInfo -> Bool
- activeDuringFinal :: Activation
- activeAfterInitial :: Activation
- pprWithSourceText :: SourceText -> SDoc -> SDoc
- failed :: SuccessFlag -> Bool
- succeeded :: SuccessFlag -> Bool
- successIf :: Bool -> SuccessFlag
- zapFragileOcc :: OccInfo -> OccInfo
- isOneOcc :: OccInfo -> Bool
- isDeadOcc :: OccInfo -> Bool
- isStrongLoopBreaker :: OccInfo -> Bool
- isWeakLoopBreaker :: OccInfo -> Bool
- weakLoopBreaker :: OccInfo
- strongLoopBreaker :: OccInfo
- isAlwaysTailCalled :: OccInfo -> Bool
- zapOccTailCallInfo :: OccInfo -> OccInfo
- tailCallInfo :: OccInfo -> TailCallInfo
- notOneBranch :: OneBranch
- oneBranch :: OneBranch
- notInsideLam :: InsideLam
- insideLam :: InsideLam
- seqOccInfo :: OccInfo -> ()
- isManyOccs :: OccInfo -> Bool
- noOccInfo :: OccInfo
- pprAlternative :: (a -> SDoc) -> a -> ConTag -> Arity -> SDoc
- sumParens :: SDoc -> SDoc
- tupleParens :: TupleSort -> SDoc -> SDoc
- boxityTupleSort :: Boxity -> TupleSort
- tupleSortBoxity :: TupleSort -> Boxity
- maybeParen :: PprPrec -> PprPrec -> SDoc -> SDoc
- appPrec :: PprPrec
- opPrec :: PprPrec
- funPrec :: PprPrec
- sigPrec :: PprPrec
- topPrec :: PprPrec
- hasOverlappingFlag :: OverlapMode -> Bool
- hasOverlappableFlag :: OverlapMode -> Bool
- hasIncoherentFlag :: OverlapMode -> Bool
- setOverlapModeMaybe :: OverlapFlag -> Maybe OverlapMode -> OverlapFlag
- isGenerated :: Origin -> Bool
- boolToRecFlag :: Bool -> RecFlag
- isNonRec :: RecFlag -> Bool
- isRec :: RecFlag -> Bool
- isBoxed :: Boxity -> Bool
- isTopLevel :: TopLevelFlag -> Bool
- isNotTopLevel :: TopLevelFlag -> Bool
- compareFixity :: Fixity -> Fixity -> (Bool, Bool)
- funTyFixity :: Fixity
- negateFixity :: Fixity
- defaultFixity :: Fixity
- minPrecedence :: Int
- maxPrecedence :: Int
- pprRuleName :: RuleName -> SDoc
- pprWarningTxtForMsg :: WarningTxt -> SDoc
- initialVersion :: Version
- bumpVersion :: Version -> Version
- isPromoted :: PromotionFlag -> Bool
- unSwap :: SwapFlag -> (a -> a -> b) -> a -> a -> b
- isSwapped :: SwapFlag -> Bool
- flipSwap :: SwapFlag -> SwapFlag
- bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
- worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
- hasNoOneShotInfo :: OneShotInfo -> Bool
- isOneShotInfo :: OneShotInfo -> Bool
- noOneShotInfo :: OneShotInfo
- alignmentOf :: Int -> Alignment
- mkAlignment :: Int -> Alignment
- fIRST_TAG :: ConTag
- pickLR :: LeftOrRight -> (a, a) -> a
- data LeftOrRight
- type Arity = Int
- type RepArity = Int
- type JoinArity = Int
- type ConTag = Int
- type ConTagZ = Int
- data Alignment
- data OneShotInfo
- data SwapFlag
- data PromotionFlag
- data FunctionOrData
- = IsFunction
- | IsData
- type Version = Int
- data StringLiteral = StringLiteral {
- sl_st :: SourceText
- sl_fs :: FastString
- data WarningTxt
- type RuleName = FastString
- data Fixity = Fixity SourceText Int FixityDirection
- data FixityDirection
- data LexicalFixity
- data TopLevelFlag
- data Boxity
- data RecFlag
- data Origin
- data OverlapFlag = OverlapFlag {}
- data OverlapMode
- newtype PprPrec = PprPrec Int
- data TupleSort
- data EP a = EP {}
- data OccInfo
- = ManyOccs {
- occ_tail :: !TailCallInfo
- | IAmDead
- | OneOcc { }
- | IAmALoopBreaker {
- occ_rules_only :: !RulesOnly
- occ_tail :: !TailCallInfo
- = ManyOccs {
- type InterestingCxt = Bool
- type InsideLam = Bool
- type OneBranch = Bool
- data TailCallInfo
- data DefMethSpec ty
- data SuccessFlag
- data SourceText
- type PhaseNum = Int
- data CompilerPhase
- data Activation
- data RuleMatchInfo
- data InlinePragma = InlinePragma {}
- data InlineSpec
- data IntegralLit = IL {}
- data FractionalLit = FL {}
- data IntWithInf
- data SpliceExplicitFlag
- data TypeOrKind
- mkLocMessage :: Severity -> SrcSpan -> MsgDoc -> MsgDoc
- mkLocMessageAnn :: Maybe String -> Severity -> SrcSpan -> MsgDoc -> MsgDoc
- getCaretDiagnostic :: Severity -> SrcSpan -> IO MsgDoc
- dumpSDoc :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO ()
- data Severity
- type MsgDoc = SDoc
- unRealSrcSpan :: RealLocated a -> a
- getRealSrcSpan :: RealLocated a -> RealSrcSpan
- liftL :: (HasSrcSpan a, HasSrcSpan b, Monad m) => (SrcSpanLess a -> m (SrcSpanLess b)) -> a -> m b
- onHasSrcSpan :: (HasSrcSpan a, HasSrcSpan b) => (SrcSpanLess a -> SrcSpanLess b) -> a -> b
- cL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
- dL :: HasSrcSpan a => a -> Located (SrcSpanLess a)
- isSubspanOf :: SrcSpan -> SrcSpan -> Bool
- spans :: SrcSpan -> (Int, Int) -> Bool
- leftmost_largest :: SrcSpan -> SrcSpan -> Ordering
- leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering
- rightmost :: SrcSpan -> SrcSpan -> Ordering
- cmpLocated :: (HasSrcSpan a, Ord (SrcSpanLess a)) => a -> a -> Ordering
- eqLocated :: (HasSrcSpan a, Eq (SrcSpanLess a)) => a -> a -> Bool
- addCLoc :: (HasSrcSpan a, HasSrcSpan b, HasSrcSpan c) => a -> b -> SrcSpanLess c -> c
- combineLocs :: (HasSrcSpan a, HasSrcSpan b) => a -> b -> SrcSpan
- mkGeneralLocated :: HasSrcSpan e => String -> SrcSpanLess e -> e
- noLoc :: HasSrcSpan a => SrcSpanLess a -> a
- getLoc :: HasSrcSpan a => a -> SrcSpan
- unLoc :: HasSrcSpan a => a -> SrcSpanLess a
- mapLoc :: (a -> b) -> GenLocated l a -> GenLocated l b
- pprUserRealSpan :: Bool -> RealSrcSpan -> SDoc
- srcSpanFileName_maybe :: SrcSpan -> Maybe FastString
- realSrcSpanEnd :: RealSrcSpan -> RealSrcLoc
- realSrcSpanStart :: RealSrcSpan -> RealSrcLoc
- srcSpanEnd :: SrcSpan -> SrcLoc
- srcSpanStart :: SrcSpan -> SrcLoc
- srcSpanEndCol :: RealSrcSpan -> Int
- srcSpanStartCol :: RealSrcSpan -> Int
- srcSpanEndLine :: RealSrcSpan -> Int
- srcSpanStartLine :: RealSrcSpan -> Int
- containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool
- isOneLineSpan :: SrcSpan -> Bool
- isGoodSrcSpan :: SrcSpan -> Bool
- srcSpanFirstCharacter :: SrcSpan -> SrcSpan
- combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan
- mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
- mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan
- realSrcLocSpan :: RealSrcLoc -> RealSrcSpan
- srcLocSpan :: SrcLoc -> SrcSpan
- mkGeneralSrcSpan :: FastString -> SrcSpan
- interactiveSrcSpan :: SrcSpan
- wiredInSrcSpan :: SrcSpan
- noSrcSpan :: SrcSpan
- sortLocated :: HasSrcSpan a => [a] -> [a]
- advanceSrcLoc :: RealSrcLoc -> Char -> RealSrcLoc
- srcLocCol :: RealSrcLoc -> Int
- srcLocLine :: RealSrcLoc -> Int
- srcLocFile :: RealSrcLoc -> FastString
- mkGeneralSrcLoc :: FastString -> SrcLoc
- interactiveSrcLoc :: SrcLoc
- generatedSrcLoc :: SrcLoc
- noSrcLoc :: SrcLoc
- mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc
- mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
- pattern LL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
- data RealSrcLoc
- data SrcLoc
- data RealSrcSpan
- data SrcSpan
- data GenLocated l e = L l e
- type Located = GenLocated SrcSpan
- type RealLocated = GenLocated RealSrcSpan
- type family SrcSpanLess a
- class HasSrcSpan a where
- composeSrcSpan :: Located (SrcSpanLess a) -> a
- decomposeSrcSpan :: a -> Located (SrcSpanLess a)
- alwaysQualify :: PrintUnqualified
- data PrintUnqualified
- unitIdString :: UnitId -> String
- data Module = Module {
- moduleUnitId :: !UnitId
- moduleName :: !ModuleName
- data ModuleName
- data UnitId
- newtype InstalledUnitId = InstalledUnitId {}
- newtype ComponentId = ComponentId FastString
- fsLit :: String -> FastString
- sLit :: String -> PtrString
- lengthPS :: PtrString -> Int
- unpackPtrString :: PtrString -> String
- mkPtrString :: String -> PtrString
- mkPtrString# :: Addr# -> PtrString
- hPutFS :: Handle -> FastString -> IO ()
- getFastStringZEncCounter :: IO Int
- getFastStringTable :: IO [[[FastString]]]
- isUnderscoreFS :: FastString -> Bool
- nilFS :: FastString
- uniqueOfFS :: FastString -> Int
- consFS :: Char -> FastString -> FastString
- tailFS :: FastString -> FastString
- headFS :: FastString -> Char
- concatFS :: [FastString] -> FastString
- appendFS :: FastString -> FastString -> FastString
- zEncodeFS :: FastString -> FastZString
- unpackFS :: FastString -> String
- nullFS :: FastString -> Bool
- lengthFS :: FastString -> Int
- mkFastStringByteList :: [Word8] -> FastString
- mkFastString :: String -> FastString
- mkFastStringByteString :: ByteString -> FastString
- mkFastStringForeignPtr :: Ptr Word8 -> ForeignPtr Word8 -> Int -> IO FastString
- mkFastStringBytes :: Ptr Word8 -> Int -> FastString
- mkFastString# :: Addr# -> FastString
- lengthFZS :: FastZString -> Int
- zString :: FastZString -> String
- hPutFZS :: Handle -> FastZString -> IO ()
- unsafeMkByteString :: String -> ByteString
- fastZStringToByteString :: FastZString -> ByteString
- fastStringToByteString :: FastString -> ByteString
- bytesFS :: FastString -> ByteString
- data FastZString
- data FastString = FastString {
- uniq :: !Int
- n_chars :: !Int
- fs_bs :: !ByteString
- fs_zenc :: FastZString
- data PtrString = PtrString !(Ptr Word8) !Int
- isTupleTyCon :: TyCon -> Bool
- isUnboxedTupleTyCon :: TyCon -> Bool
- isFunTyCon :: TyCon -> Bool
- data TyCon
- sGhcRtsWithLibdw :: Settings -> Bool
- sGhcDebugged :: Settings -> Bool
- sGhcThreaded :: Settings -> Bool
- sLibFFI :: Settings -> Bool
- sLeadingUnderscore :: Settings -> Bool
- sTablesNextToCode :: Settings -> Bool
- sGhcRTSWays :: Settings -> String
- sGhcWithSMP :: Settings -> Bool
- sGhcWithNativeCodeGen :: Settings -> Bool
- sGhcWithInterpreter :: Settings -> Bool
- sIntegerLibraryType :: Settings -> IntegerLibrary
- sIntegerLibrary :: Settings -> String
- sTargetPlatformString :: Settings -> String
- sExtraGccViaCFlags :: Settings -> [String]
- sOpt_i :: Settings -> [String]
- sOpt_lcc :: Settings -> [String]
- sOpt_lc :: Settings -> [String]
- sOpt_lo :: Settings -> [String]
- sOpt_windres :: Settings -> [String]
- sOpt_lm :: Settings -> [String]
- sOpt_l :: Settings -> [String]
- sOpt_a :: Settings -> [String]
- sOpt_cxx :: Settings -> [String]
- sOpt_c :: Settings -> [String]
- sOpt_F :: Settings -> [String]
- sOpt_P_fingerprint :: Settings -> Fingerprint
- sOpt_P :: Settings -> [String]
- sOpt_L :: Settings -> [String]
- sPgm_i :: Settings -> String
- sPgm_lcc :: Settings -> (String, [Option])
- sPgm_lc :: Settings -> (String, [Option])
- sPgm_lo :: Settings -> (String, [Option])
- sPgm_ranlib :: Settings -> String
- sPgm_ar :: Settings -> String
- sPgm_libtool :: Settings -> String
- sPgm_windres :: Settings -> String
- sPgm_T :: Settings -> String
- sPgm_dll :: Settings -> (String, [Option])
- sPgm_lm :: Settings -> (String, [Option])
- sPgm_l :: Settings -> (String, [Option])
- sPgm_a :: Settings -> (String, [Option])
- sPgm_c :: Settings -> String
- sPgm_F :: Settings -> String
- sPgm_P :: Settings -> (String, [Option])
- sPgm_L :: Settings -> String
- sGccSupportsNoPie :: Settings -> Bool
- sLdIsGnuLd :: Settings -> Bool
- sLdSupportsFilelist :: Settings -> Bool
- sLdSupportsBuildId :: Settings -> Bool
- sLdSupportsCompactUnwind :: Settings -> Bool
- sSystemPackageConfig :: Settings -> FilePath
- sTmpDir :: Settings -> String
- sTopDir :: Settings -> FilePath
- sToolDir :: Settings -> Maybe FilePath
- sGhciUsagePath :: Settings -> FilePath
- sGhcUsagePath :: Settings -> FilePath
- sProjectVersion :: Settings -> String
- sProgramName :: Settings -> String
- data Settings = Settings {}
- data PlatformConstants = PlatformConstants {
- pc_CONTROL_GROUP_CONST_291 :: Int
- pc_STD_HDR_SIZE :: Int
- pc_PROF_HDR_SIZE :: Int
- pc_BLOCK_SIZE :: Int
- pc_BLOCKS_PER_MBLOCK :: Int
- pc_TICKY_BIN_COUNT :: Int
- pc_OFFSET_StgRegTable_rR1 :: Int
- pc_OFFSET_StgRegTable_rR2 :: Int
- pc_OFFSET_StgRegTable_rR3 :: Int
- pc_OFFSET_StgRegTable_rR4 :: Int
- pc_OFFSET_StgRegTable_rR5 :: Int
- pc_OFFSET_StgRegTable_rR6 :: Int
- pc_OFFSET_StgRegTable_rR7 :: Int
- pc_OFFSET_StgRegTable_rR8 :: Int
- pc_OFFSET_StgRegTable_rR9 :: Int
- pc_OFFSET_StgRegTable_rR10 :: Int
- pc_OFFSET_StgRegTable_rF1 :: Int
- pc_OFFSET_StgRegTable_rF2 :: Int
- pc_OFFSET_StgRegTable_rF3 :: Int
- pc_OFFSET_StgRegTable_rF4 :: Int
- pc_OFFSET_StgRegTable_rF5 :: Int
- pc_OFFSET_StgRegTable_rF6 :: Int
- pc_OFFSET_StgRegTable_rD1 :: Int
- pc_OFFSET_StgRegTable_rD2 :: Int
- pc_OFFSET_StgRegTable_rD3 :: Int
- pc_OFFSET_StgRegTable_rD4 :: Int
- pc_OFFSET_StgRegTable_rD5 :: Int
- pc_OFFSET_StgRegTable_rD6 :: Int
- pc_OFFSET_StgRegTable_rXMM1 :: Int
- pc_OFFSET_StgRegTable_rXMM2 :: Int
- pc_OFFSET_StgRegTable_rXMM3 :: Int
- pc_OFFSET_StgRegTable_rXMM4 :: Int
- pc_OFFSET_StgRegTable_rXMM5 :: Int
- pc_OFFSET_StgRegTable_rXMM6 :: Int
- pc_OFFSET_StgRegTable_rYMM1 :: Int
- pc_OFFSET_StgRegTable_rYMM2 :: Int
- pc_OFFSET_StgRegTable_rYMM3 :: Int
- pc_OFFSET_StgRegTable_rYMM4 :: Int
- pc_OFFSET_StgRegTable_rYMM5 :: Int
- pc_OFFSET_StgRegTable_rYMM6 :: Int
- pc_OFFSET_StgRegTable_rZMM1 :: Int
- pc_OFFSET_StgRegTable_rZMM2 :: Int
- pc_OFFSET_StgRegTable_rZMM3 :: Int
- pc_OFFSET_StgRegTable_rZMM4 :: Int
- pc_OFFSET_StgRegTable_rZMM5 :: Int
- pc_OFFSET_StgRegTable_rZMM6 :: Int
- pc_OFFSET_StgRegTable_rL1 :: Int
- pc_OFFSET_StgRegTable_rSp :: Int
- pc_OFFSET_StgRegTable_rSpLim :: Int
- pc_OFFSET_StgRegTable_rHp :: Int
- pc_OFFSET_StgRegTable_rHpLim :: Int
- pc_OFFSET_StgRegTable_rCCCS :: Int
- pc_OFFSET_StgRegTable_rCurrentTSO :: Int
- pc_OFFSET_StgRegTable_rCurrentNursery :: Int
- pc_OFFSET_StgRegTable_rHpAlloc :: Int
- pc_OFFSET_stgEagerBlackholeInfo :: Int
- pc_OFFSET_stgGCEnter1 :: Int
- pc_OFFSET_stgGCFun :: Int
- pc_OFFSET_Capability_r :: Int
- pc_OFFSET_bdescr_start :: Int
- pc_OFFSET_bdescr_free :: Int
- pc_OFFSET_bdescr_blocks :: Int
- pc_OFFSET_bdescr_flags :: Int
- pc_SIZEOF_CostCentreStack :: Int
- pc_OFFSET_CostCentreStack_mem_alloc :: Int
- pc_REP_CostCentreStack_mem_alloc :: Int
- pc_OFFSET_CostCentreStack_scc_count :: Int
- pc_REP_CostCentreStack_scc_count :: Int
- pc_OFFSET_StgHeader_ccs :: Int
- pc_OFFSET_StgHeader_ldvw :: Int
- pc_SIZEOF_StgSMPThunkHeader :: Int
- pc_OFFSET_StgEntCounter_allocs :: Int
- pc_REP_StgEntCounter_allocs :: Int
- pc_OFFSET_StgEntCounter_allocd :: Int
- pc_REP_StgEntCounter_allocd :: Int
- pc_OFFSET_StgEntCounter_registeredp :: Int
- pc_OFFSET_StgEntCounter_link :: Int
- pc_OFFSET_StgEntCounter_entry_count :: Int
- pc_SIZEOF_StgUpdateFrame_NoHdr :: Int
- pc_SIZEOF_StgMutArrPtrs_NoHdr :: Int
- pc_OFFSET_StgMutArrPtrs_ptrs :: Int
- pc_OFFSET_StgMutArrPtrs_size :: Int
- pc_SIZEOF_StgSmallMutArrPtrs_NoHdr :: Int
- pc_OFFSET_StgSmallMutArrPtrs_ptrs :: Int
- pc_SIZEOF_StgArrBytes_NoHdr :: Int
- pc_OFFSET_StgArrBytes_bytes :: Int
- pc_OFFSET_StgTSO_alloc_limit :: Int
- pc_OFFSET_StgTSO_cccs :: Int
- pc_OFFSET_StgTSO_stackobj :: Int
- pc_OFFSET_StgStack_sp :: Int
- pc_OFFSET_StgStack_stack :: Int
- pc_OFFSET_StgUpdateFrame_updatee :: Int
- pc_OFFSET_StgFunInfoExtraFwd_arity :: Int
- pc_REP_StgFunInfoExtraFwd_arity :: Int
- pc_SIZEOF_StgFunInfoExtraRev :: Int
- pc_OFFSET_StgFunInfoExtraRev_arity :: Int
- pc_REP_StgFunInfoExtraRev_arity :: Int
- pc_MAX_SPEC_SELECTEE_SIZE :: Int
- pc_MAX_SPEC_AP_SIZE :: Int
- pc_MIN_PAYLOAD_SIZE :: Int
- pc_MIN_INTLIKE :: Int
- pc_MAX_INTLIKE :: Int
- pc_MIN_CHARLIKE :: Int
- pc_MAX_CHARLIKE :: Int
- pc_MUT_ARR_PTRS_CARD_BITS :: Int
- pc_MAX_Vanilla_REG :: Int
- pc_MAX_Float_REG :: Int
- pc_MAX_Double_REG :: Int
- pc_MAX_Long_REG :: Int
- pc_MAX_XMM_REG :: Int
- pc_MAX_Real_Vanilla_REG :: Int
- pc_MAX_Real_Float_REG :: Int
- pc_MAX_Real_Double_REG :: Int
- pc_MAX_Real_XMM_REG :: Int
- pc_MAX_Real_Long_REG :: Int
- pc_RESERVED_C_STACK_BYTES :: Int
- pc_RESERVED_STACK_WORDS :: Int
- pc_AP_STACK_SPLIM :: Int
- pc_WORD_SIZE :: Int
- pc_DOUBLE_SIZE :: Int
- pc_CINT_SIZE :: Int
- pc_CLONG_SIZE :: Int
- pc_CLONG_LONG_SIZE :: Int
- pc_BITMAP_BITS_SHIFT :: Int
- pc_TAG_BITS :: Int
- pc_WORDS_BIGENDIAN :: Bool
- pc_DYNAMIC_BY_DEFAULT :: Bool
- pc_LDV_SHIFT :: Int
- pc_ILDV_CREATE_MASK :: Integer
- pc_ILDV_STATE_CREATE :: Integer
- pc_ILDV_STATE_USE :: Integer
- withSignalHandlers :: (ExceptionMonad m, MonadIO m) => m a -> m a
- showGhcException :: GhcException -> ShowS
- data GhcException
- data OccName
- data Name
- showOpt :: Option -> String
- data Option
- unsafeGlobalDynFlags :: DynFlags
- useUnicodeSyntax :: DynFlags -> Bool
- useStarIsType :: DynFlags -> Bool
- shouldUseColor :: DynFlags -> Bool
- shouldUseHexWordLiterals :: DynFlags -> Bool
- hasPprDebug :: DynFlags -> Bool
- hasNoDebugOutput :: DynFlags -> Bool
- data DynFlags = DynFlags {
- ghcMode :: GhcMode
- ghcLink :: GhcLink
- hscTarget :: HscTarget
- ghcNameVersion :: !GhcNameVersion
- fileSettings :: !FileSettings
- targetPlatform :: Platform
- toolSettings :: !ToolSettings
- platformMisc :: !PlatformMisc
- platformConstants :: PlatformConstants
- rawSettings :: [(String, String)]
- integerLibrary :: IntegerLibrary
- llvmConfig :: LlvmConfig
- verbosity :: Int
- optLevel :: Int
- debugLevel :: Int
- simplPhases :: Int
- maxSimplIterations :: Int
- ruleCheck :: Maybe String
- inlineCheck :: Maybe String
- strictnessBefore :: [Int]
- parMakeCount :: Maybe Int
- enableTimeStats :: Bool
- ghcHeapSize :: Maybe Int
- maxRelevantBinds :: Maybe Int
- maxValidHoleFits :: Maybe Int
- maxRefHoleFits :: Maybe Int
- refLevelHoleFits :: Maybe Int
- maxUncoveredPatterns :: Int
- maxPmCheckModels :: Int
- simplTickFactor :: Int
- specConstrThreshold :: Maybe Int
- specConstrCount :: Maybe Int
- specConstrRecursive :: Int
- binBlobThreshold :: Word
- liberateCaseThreshold :: Maybe Int
- floatLamArgs :: Maybe Int
- liftLamsRecArgs :: Maybe Int
- liftLamsNonRecArgs :: Maybe Int
- liftLamsKnown :: Bool
- cmmProcAlignment :: Maybe Int
- historySize :: Int
- importPaths :: [FilePath]
- mainModIs :: Module
- mainFunIs :: Maybe String
- reductionDepth :: IntWithInf
- solverIterations :: IntWithInf
- thisInstalledUnitId :: InstalledUnitId
- thisComponentId_ :: Maybe ComponentId
- thisUnitIdInsts_ :: Maybe [(ModuleName, Module)]
- ways :: [Way]
- buildTag :: String
- splitInfo :: Maybe (String, Int)
- objectDir :: Maybe String
- dylibInstallName :: Maybe String
- hiDir :: Maybe String
- hieDir :: Maybe String
- stubDir :: Maybe String
- dumpDir :: Maybe String
- objectSuf :: String
- hcSuf :: String
- hiSuf :: String
- hieSuf :: String
- canGenerateDynamicToo :: IORef Bool
- dynObjectSuf :: String
- dynHiSuf :: String
- outputFile :: Maybe String
- dynOutputFile :: Maybe String
- outputHi :: Maybe String
- dynLibLoader :: DynLibLoader
- dumpPrefix :: Maybe FilePath
- dumpPrefixForce :: Maybe FilePath
- ldInputs :: [Option]
- includePaths :: IncludeSpecs
- libraryPaths :: [String]
- frameworkPaths :: [String]
- cmdlineFrameworks :: [String]
- rtsOpts :: Maybe String
- rtsOptsEnabled :: RtsOptsEnabled
- rtsOptsSuggestions :: Bool
- hpcDir :: String
- pluginModNames :: [ModuleName]
- pluginModNameOpts :: [(ModuleName, String)]
- frontendPluginOpts :: [String]
- cachedPlugins :: [LoadedPlugin]
- staticPlugins :: [StaticPlugin]
- hooks :: Hooks
- depMakefile :: FilePath
- depIncludePkgDeps :: Bool
- depIncludeCppDeps :: Bool
- depExcludeMods :: [ModuleName]
- depSuffixes :: [String]
- packageDBFlags :: [PackageDBFlag]
- ignorePackageFlags :: [IgnorePackageFlag]
- packageFlags :: [PackageFlag]
- pluginPackageFlags :: [PackageFlag]
- trustFlags :: [TrustFlag]
- packageEnv :: Maybe FilePath
- pkgDatabase :: Maybe [(FilePath, [PackageConfig])]
- pkgState :: PackageState
- filesToClean :: IORef FilesToClean
- dirsToClean :: IORef (Map FilePath FilePath)
- nextTempSuffix :: IORef Int
- generatedDumps :: IORef (Set FilePath)
- dumpFlags :: EnumSet DumpFlag
- generalFlags :: EnumSet GeneralFlag
- warningFlags :: EnumSet WarningFlag
- fatalWarningFlags :: EnumSet WarningFlag
- language :: Maybe Language
- safeHaskell :: SafeHaskellMode
- safeInfer :: Bool
- safeInferred :: Bool
- thOnLoc :: SrcSpan
- newDerivOnLoc :: SrcSpan
- overlapInstLoc :: SrcSpan
- incoherentOnLoc :: SrcSpan
- pkgTrustOnLoc :: SrcSpan
- warnSafeOnLoc :: SrcSpan
- warnUnsafeOnLoc :: SrcSpan
- trustworthyOnLoc :: SrcSpan
- extensions :: [OnOff Extension]
- extensionFlags :: EnumSet Extension
- ufCreationThreshold :: Int
- ufUseThreshold :: Int
- ufFunAppDiscount :: Int
- ufDictDiscount :: Int
- ufKeenessFactor :: Float
- ufDearOp :: Int
- ufVeryAggressive :: Bool
- maxWorkerArgs :: Int
- ghciHistSize :: Int
- log_action :: LogAction
- flushOut :: FlushOut
- flushErr :: FlushErr
- ghcVersionFile :: Maybe FilePath
- haddockOptions :: Maybe String
- ghciScripts :: [String]
- pprUserLength :: Int
- pprCols :: Int
- useUnicode :: Bool
- useColor :: OverridingBool
- canUseColor :: Bool
- colScheme :: Scheme
- profAuto :: ProfAuto
- interactivePrint :: Maybe String
- nextWrapperNum :: IORef (ModuleEnv Int)
- sseVersion :: Maybe SseVersion
- bmiVersion :: Maybe BmiVersion
- avx :: Bool
- avx2 :: Bool
- avx512cd :: Bool
- avx512er :: Bool
- avx512f :: Bool
- avx512pf :: Bool
- rtldInfo :: IORef (Maybe LinkerInfo)
- rtccInfo :: IORef (Maybe CompilerInfo)
- maxInlineAllocSize :: Int
- maxInlineMemcpyInsns :: Int
- maxInlineMemsetInsns :: Int
- reverseErrors :: Bool
- maxErrors :: Maybe Int
- initialUnique :: Int
- uniqueIncrement :: Int
- cfgWeightInfo :: CfgWeights
- data DumpFlag
- = Opt_D_dump_cmm
- | Opt_D_dump_cmm_from_stg
- | Opt_D_dump_cmm_raw
- | Opt_D_dump_cmm_verbose_by_proc
- | Opt_D_dump_cmm_verbose
- | Opt_D_dump_cmm_cfg
- | Opt_D_dump_cmm_cbe
- | Opt_D_dump_cmm_switch
- | Opt_D_dump_cmm_proc
- | Opt_D_dump_cmm_sp
- | Opt_D_dump_cmm_sink
- | Opt_D_dump_cmm_caf
- | Opt_D_dump_cmm_procmap
- | Opt_D_dump_cmm_split
- | Opt_D_dump_cmm_info
- | Opt_D_dump_cmm_cps
- | Opt_D_dump_cfg_weights
- | Opt_D_dump_asm
- | Opt_D_dump_asm_native
- | Opt_D_dump_asm_liveness
- | Opt_D_dump_asm_regalloc
- | Opt_D_dump_asm_regalloc_stages
- | Opt_D_dump_asm_conflicts
- | Opt_D_dump_asm_stats
- | Opt_D_dump_asm_expanded
- | Opt_D_dump_llvm
- | Opt_D_dump_core_stats
- | Opt_D_dump_deriv
- | Opt_D_dump_ds
- | Opt_D_dump_ds_preopt
- | Opt_D_dump_foreign
- | Opt_D_dump_inlinings
- | Opt_D_dump_rule_firings
- | Opt_D_dump_rule_rewrites
- | Opt_D_dump_simpl_trace
- | Opt_D_dump_occur_anal
- | Opt_D_dump_parsed
- | Opt_D_dump_parsed_ast
- | Opt_D_dump_rn
- | Opt_D_dump_rn_ast
- | Opt_D_dump_simpl
- | Opt_D_dump_simpl_iterations
- | Opt_D_dump_spec
- | Opt_D_dump_prep
- | Opt_D_dump_stg
- | Opt_D_dump_stg_unarised
- | Opt_D_dump_stg_final
- | Opt_D_dump_call_arity
- | Opt_D_dump_exitify
- | Opt_D_dump_stranal
- | Opt_D_dump_str_signatures
- | Opt_D_dump_tc
- | Opt_D_dump_tc_ast
- | Opt_D_dump_types
- | Opt_D_dump_rules
- | Opt_D_dump_cse
- | Opt_D_dump_worker_wrapper
- | Opt_D_dump_rn_trace
- | Opt_D_dump_rn_stats
- | Opt_D_dump_opt_cmm
- | Opt_D_dump_simpl_stats
- | Opt_D_dump_cs_trace
- | Opt_D_dump_tc_trace
- | Opt_D_dump_ec_trace
- | Opt_D_dump_if_trace
- | Opt_D_dump_vt_trace
- | Opt_D_dump_splices
- | Opt_D_th_dec_file
- | Opt_D_dump_BCOs
- | Opt_D_dump_ticked
- | Opt_D_dump_rtti
- | Opt_D_source_stats
- | Opt_D_verbose_stg2stg
- | Opt_D_dump_hi
- | Opt_D_dump_hi_diffs
- | Opt_D_dump_mod_cycles
- | Opt_D_dump_mod_map
- | Opt_D_dump_timings
- | Opt_D_dump_view_pattern_commoning
- | Opt_D_verbose_core2core
- | Opt_D_dump_debug
- | Opt_D_dump_json
- | Opt_D_ppr_debug
- | Opt_D_no_debug_output
- data GeneralFlag
- = Opt_DumpToFile
- | Opt_D_faststring_stats
- | Opt_D_dump_minimal_imports
- | Opt_DoCoreLinting
- | Opt_DoStgLinting
- | Opt_DoCmmLinting
- | Opt_DoAsmLinting
- | Opt_DoAnnotationLinting
- | Opt_NoLlvmMangler
- | Opt_FastLlvm
- | Opt_NoTypeableBinds
- | Opt_WarnIsError
- | Opt_ShowWarnGroups
- | Opt_HideSourcePaths
- | Opt_PrintExplicitForalls
- | Opt_PrintExplicitKinds
- | Opt_PrintExplicitCoercions
- | Opt_PrintExplicitRuntimeReps
- | Opt_PrintEqualityRelations
- | Opt_PrintAxiomIncomps
- | Opt_PrintUnicodeSyntax
- | Opt_PrintExpandedSynonyms
- | Opt_PrintPotentialInstances
- | Opt_PrintTypecheckerElaboration
- | Opt_CallArity
- | Opt_Exitification
- | Opt_Strictness
- | Opt_LateDmdAnal
- | Opt_KillAbsence
- | Opt_KillOneShot
- | Opt_FullLaziness
- | Opt_FloatIn
- | Opt_LateSpecialise
- | Opt_Specialise
- | Opt_SpecialiseAggressively
- | Opt_CrossModuleSpecialise
- | Opt_StaticArgumentTransformation
- | Opt_CSE
- | Opt_StgCSE
- | Opt_StgLiftLams
- | Opt_LiberateCase
- | Opt_SpecConstr
- | Opt_SpecConstrKeen
- | Opt_DoLambdaEtaExpansion
- | Opt_IgnoreAsserts
- | Opt_DoEtaReduction
- | Opt_CaseMerge
- | Opt_CaseFolding
- | Opt_UnboxStrictFields
- | Opt_UnboxSmallStrictFields
- | Opt_DictsCheap
- | Opt_EnableRewriteRules
- | Opt_EnableThSpliceWarnings
- | Opt_RegsGraph
- | Opt_RegsIterative
- | Opt_PedanticBottoms
- | Opt_LlvmTBAA
- | Opt_LlvmFillUndefWithGarbage
- | Opt_IrrefutableTuples
- | Opt_CmmSink
- | Opt_CmmElimCommonBlocks
- | Opt_AsmShortcutting
- | Opt_OmitYields
- | Opt_FunToThunk
- | Opt_DictsStrict
- | Opt_DmdTxDictSel
- | Opt_Loopification
- | Opt_CfgBlocklayout
- | Opt_WeightlessBlocklayout
- | Opt_CprAnal
- | Opt_WorkerWrapper
- | Opt_SolveConstantDicts
- | Opt_AlignmentSanitisation
- | Opt_CatchBottoms
- | Opt_NumConstantFolding
- | Opt_SimplPreInlining
- | Opt_IgnoreInterfacePragmas
- | Opt_OmitInterfacePragmas
- | Opt_ExposeAllUnfoldings
- | Opt_WriteInterface
- | Opt_WriteHie
- | Opt_AutoSccsOnIndividualCafs
- | Opt_ProfCountEntries
- | Opt_Pp
- | Opt_ForceRecomp
- | Opt_IgnoreOptimChanges
- | Opt_IgnoreHpcChanges
- | Opt_ExcessPrecision
- | Opt_EagerBlackHoling
- | Opt_NoHsMain
- | Opt_SplitSections
- | Opt_StgStats
- | Opt_HideAllPackages
- | Opt_HideAllPluginPackages
- | Opt_PrintBindResult
- | Opt_Haddock
- | Opt_HaddockOptions
- | Opt_BreakOnException
- | Opt_BreakOnError
- | Opt_PrintEvldWithShow
- | Opt_PrintBindContents
- | Opt_GenManifest
- | Opt_EmbedManifest
- | Opt_SharedImplib
- | Opt_BuildingCabalPackage
- | Opt_IgnoreDotGhci
- | Opt_GhciSandbox
- | Opt_GhciHistory
- | Opt_GhciLeakCheck
- | Opt_ValidateHie
- | Opt_LocalGhciHistory
- | Opt_NoIt
- | Opt_HelpfulErrors
- | Opt_DeferTypeErrors
- | Opt_DeferTypedHoles
- | Opt_DeferOutOfScopeVariables
- | Opt_PIC
- | Opt_PIE
- | Opt_PICExecutable
- | Opt_ExternalDynamicRefs
- | Opt_SccProfilingOn
- | Opt_Ticky
- | Opt_Ticky_Allocd
- | Opt_Ticky_LNE
- | Opt_Ticky_Dyn_Thunk
- | Opt_RPath
- | Opt_RelativeDynlibPaths
- | Opt_Hpc
- | Opt_FlatCache
- | Opt_ExternalInterpreter
- | Opt_OptimalApplicativeDo
- | Opt_VersionMacros
- | Opt_WholeArchiveHsLibs
- | Opt_SingleLibFolder
- | Opt_KeepCAFs
- | Opt_KeepGoing
- | Opt_ByteCode
- | Opt_ErrorSpans
- | Opt_DeferDiagnostics
- | Opt_DiagnosticsShowCaret
- | Opt_PprCaseAsLet
- | Opt_PprShowTicks
- | Opt_ShowHoleConstraints
- | Opt_ShowValidHoleFits
- | Opt_SortValidHoleFits
- | Opt_SortBySizeHoleFits
- | Opt_SortBySubsumHoleFits
- | Opt_AbstractRefHoleFits
- | Opt_UnclutterValidHoleFits
- | Opt_ShowTypeAppOfHoleFits
- | Opt_ShowTypeAppVarsOfHoleFits
- | Opt_ShowDocsOfHoleFits
- | Opt_ShowTypeOfHoleFits
- | Opt_ShowProvOfHoleFits
- | Opt_ShowMatchesOfHoleFits
- | Opt_ShowLoadedModules
- | Opt_HexWordLiterals
- | Opt_SuppressCoercions
- | Opt_SuppressVarKinds
- | Opt_SuppressModulePrefixes
- | Opt_SuppressTypeApplications
- | Opt_SuppressIdInfo
- | Opt_SuppressUnfoldings
- | Opt_SuppressTypeSignatures
- | Opt_SuppressUniques
- | Opt_SuppressStgExts
- | Opt_SuppressTicks
- | Opt_SuppressTimestamps
- | Opt_AutoLinkPackages
- | Opt_ImplicitImportQualified
- | Opt_KeepHscppFiles
- | Opt_KeepHiDiffs
- | Opt_KeepHcFiles
- | Opt_KeepSFiles
- | Opt_KeepTmpFiles
- | Opt_KeepRawTokenStream
- | Opt_KeepLlvmFiles
- | Opt_KeepHiFiles
- | Opt_KeepOFiles
- | Opt_BuildDynamicToo
- | Opt_DistrustAllPackages
- | Opt_PackageTrust
- | Opt_PluginTrustworthy
- | Opt_G_NoStateHack
- | Opt_G_NoOptCoercion
- gfinally :: ExceptionMonad m => m a -> m b -> m a
- gcatch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m a
- gbracket :: ExceptionMonad m => m a -> (a -> m b) -> (a -> m c) -> m c
- data FileSettings = FileSettings {}
- data GhcNameVersion = GhcNameVersion {}
- type ForeignHValue = ForeignRef HValue
- data HValue
- data IntegerLibrary
- data PlatformMisc = PlatformMisc {
- platformMisc_targetPlatformString :: String
- platformMisc_integerLibrary :: String
- platformMisc_integerLibraryType :: IntegerLibrary
- platformMisc_ghcWithInterpreter :: Bool
- platformMisc_ghcWithNativeCodeGen :: Bool
- platformMisc_ghcWithSMP :: Bool
- platformMisc_ghcRTSWays :: String
- platformMisc_tablesNextToCode :: Bool
- platformMisc_leadingUnderscore :: Bool
- platformMisc_libFFI :: Bool
- platformMisc_ghcThreaded :: Bool
- platformMisc_ghcDebugged :: Bool
- platformMisc_ghcRtsWithLibdw :: Bool
- platformMisc_llvmTarget :: String
- data ForeignSrcLang
- coreModule :: DesugaredMod m => m -> ModGuts
- tyConRealArity :: TyCon -> Int
- dataConExTyVars :: DataCon -> [TyVar]
Documentation
Arguments
| :: String | Haskell module source text (full Unicode is supported) |
| -> DynFlags | the flags |
| -> FilePath | the filename (for source locations) |
| -> (WarningMessages, Either ErrorMessages (Located (HsModule GhcPs))) |
A pure interface to the module parser.
getHistorySpan :: GhcMonad m => History -> m SrcSpan #
getGHCiMonad :: GhcMonad m => m Name #
Get the monad GHCi lifts user statements into.
setGHCiMonad :: GhcMonad m => String -> m () #
Set the monad GHCi lifts user statements into.
Checks that a type (in string form) is an instance of the
GHC.GHCi.GHCiSandboxIO type class. Sets it to be the GHCi monad if it is,
throws an error otherwise.
moduleTrustReqs :: GhcMonad m => Module -> m (Bool, Set InstalledUnitId) #
Return if a module is trusted and the pkgs it depends on to be trusted.
isModuleTrusted :: GhcMonad m => Module -> m Bool #
Check that a module is safe to import (according to Safe Haskell).
We return True to indicate the import is safe and False otherwise although in the False case an error may be thrown first.
lookupModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module #
Like findModule, but differs slightly when the module refers to
a source file, and the file has not been loaded via load. In
this case, findModule will throw an error (module not loaded),
but lookupModule will check to see whether the module can also be
found in a package, and if so, that package Module will be
returned. If not, the usual module-not-found error will be thrown.
findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module #
Takes a ModuleName and possibly a UnitId, and consults the
filesystem and package database to find the corresponding Module,
using the algorithm that is used for an import declaration.
showRichTokenStream :: [(Located Token, String)] -> String #
Take a rich token stream such as produced from getRichTokenStream and
return source code almost identical to the original code (except for
insignificant whitespace.)
addSourceToTokens :: RealSrcLoc -> StringBuffer -> [Located Token] -> [(Located Token, String)] #
Given a source location and a StringBuffer corresponding to this location, return a rich token stream with the source associated to the tokens.
getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)] #
Give even more information on the source than getTokenStream
This function allows reconstructing the source completely with
showRichTokenStream.
getTokenStream :: GhcMonad m => Module -> m [Located Token] #
Return module source as token stream, including comments.
The module must be in the module graph and its source must be available.
Throws a SourceError on parse error.
pprParenSymName :: NamedThing a => a -> SDoc #
print a NamedThing, adding parentheses if the name is an operator.
dataConType :: DataCon -> Type #
Arguments
| :: GhcMonad m | |
| => [Module] | visible modules. An orphan instance will be returned if it is visible from at least one module in the list. |
| -> Maybe [Module] | modules to load. If this is not specified, we load modules for everything that is in scope unqualified. |
| -> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) |
Retrieve all type and family instances in the environment, indexed
by Name. Each name's lists will contain every instance in which that name
is mentioned in the instance head.
getGRE :: GhcMonad m => m GlobalRdrEnv #
get the GlobalRdrEnv for a session
lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing) #
Looks up a global name: that is, any top-level name in any
visible module. Unlike lookupName, lookupGlobalName does not use
the interactive context, and therefore does not require a preceding
setContext.
isDictonaryId :: Id -> Bool #
modInfoModBreaks :: ModuleInfo -> ModBreaks #
modInfoSafe :: ModuleInfo -> SafeHaskellMode #
Retrieve module safe haskell mode
modInfoIface :: ModuleInfo -> Maybe ModIface #
modInfoLookupName :: GhcMonad m => ModuleInfo -> Name -> m (Maybe TyThing) #
mkPrintUnqualifiedForModule :: GhcMonad m => ModuleInfo -> m (Maybe PrintUnqualified) #
modInfoIsExportedName :: ModuleInfo -> Name -> Bool #
modInfoInstances :: ModuleInfo -> [ClsInst] #
Returns the instances defined by the specified module. Warning: currently unimplemented for package modules.
modInfoExportsWithSelectors :: ModuleInfo -> [Name] #
modInfoExports :: ModuleInfo -> [Name] #
modInfoTopLevelScope :: ModuleInfo -> Maybe [Name] #
modInfoTyThings :: ModuleInfo -> [TyThing] #
The list of top-level entities defined in a module
getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo) #
Request information about a loaded Module
getPrintUnqual :: GhcMonad m => m PrintUnqualified #
getInsts :: GhcMonad m => m ([ClsInst], [FamInst]) #
Return the instances for the current interactive session.
getBindings :: GhcMonad m => m [TyThing] #
Return the bindings for the current interactive session.
getModuleGraph :: GhcMonad m => m ModuleGraph #
Get the module dependency graph.
compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule #
Like compileToCoreModule, but invokes the simplifier, so as to return simplified and tidied Core.
compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule #
This is the way to get access to the Core bindings corresponding
to a module. compileToCore parses, typechecks, and
desugars the module, then returns the resulting Core module (consisting of
the module name, type declarations, and function declarations) if
successful.
loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod #
Load a module. Input doesn't need to be desugared.
A module must be loaded before dependent modules can be typechecked. This
always includes generating a ModIface and, depending on the
hscTarget, may also include code generation.
This function will always cause recompilation and will always overwrite previous compilation results (potentially files on disk).
desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule #
Desugar a typechecked module.
typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule #
Typecheck and rename a parsed module.
Throws a SourceError if either fails.
parseModule :: GhcMonad m => ModSummary -> m ParsedModule #
Parse a module.
Throws a SourceError on parse error.
getModSummary :: GhcMonad m => ModuleName -> m ModSummary #
Return the ModSummary of a module with the given name.
The module must be part of the module graph (see hsc_mod_graph and
ModuleGraph). If this is not the case, this function will throw a
GhcApiError.
This function ignores boot modules and requires that there is only one non-boot module with the given name.
workingDirectoryChanged :: GhcMonad m => m () #
Inform GHC that the working directory has changed. GHC will flush its cache of module locations, since it may no longer be valid.
Note: Before changing the working directory make sure all threads running in the same session have stopped. If you change the working directory, you should also unload the current program (set targets to empty, followed by load).
guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target #
Attempts to guess what Target a string refers to. This function
implements the --make/GHCi command-line syntax for filenames:
- if the string looks like a Haskell source filename, then interpret it as such
- if adding a .hs or .lhs suffix yields the name of an existing file, then use that
- otherwise interpret the string as a module name
removeTarget :: GhcMonad m => TargetId -> m () #
Remove a target
getTargets :: GhcMonad m => m [Target] #
Returns the current set of targets
setTargets :: GhcMonad m => [Target] -> m () #
Sets the targets for this session. Each target may be a module name
or a filename. The targets correspond to the set of root modules for
the program/library. Unloading the current program is achieved by
setting the current set of targets to be empty, followed by load.
parseDynamicFlags :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn]) #
getInteractiveDynFlags :: GhcMonad m => m DynFlags #
Get the DynFlags used to evaluate interactive expressions.
setInteractiveDynFlags :: GhcMonad m => DynFlags -> m () #
Set the DynFlags used to evaluate interactive expressions.
Note: this cannot be used for changes to packages. Use
setSessionDynFlags, or setProgramDynFlags and then copy the
pkgState into the interactive DynFlags.
getProgramDynFlags :: GhcMonad m => m DynFlags #
Returns the program DynFlags.
setLogAction :: GhcMonad m => LogAction -> m () #
Set the action taken when the compiler produces a message. This
can also be accomplished using setProgramDynFlags, but using
setLogAction avoids invalidating the cached module graph.
setProgramDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId] #
setSessionDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId] #
Updates both the interactive and program DynFlags in a Session. This also reads the package database (unless it has already been read), and prepares the compilers knowledge about packages. It can be called again to load new packages: just add new package flags to (packageFlags dflags).
Returns a list of new packages that may need to be linked in using
the dynamic linker (see linkPackages) as a result of new package
flags. If you are not doing linking or doing static linking, you
can ignore the list of packages returned.
initGhcMonad :: GhcMonad m => Maybe FilePath -> m () #
Initialise a GHC session.
If you implement a custom GhcMonad you must call this function in the
monad run function. It will initialise the session variable and clear all
warnings.
The first argument should point to the directory where GHC's library files
reside. More precisely, this should be the output of ghc --print-libdir
of the version of GHC the module using this API is compiled with. For
portability, you should use the ghc-paths package, available at
http://hackage.haskell.org/package/ghc-paths.
withCleanupSession :: GhcMonad m => m a -> m a #
Arguments
| :: ExceptionMonad m | |
| => Maybe FilePath | See argument to |
| -> GhcT m a | The action to perform. |
| -> m a |
Run function for GhcT monad transformer.
It initialises the GHC session and warnings via initGhcMonad. Each call
to this function will create a new session which should not be shared among
several threads.
Arguments
| :: Maybe FilePath | See argument to |
| -> Ghc a | The action to perform. |
| -> IO a |
Run function for the Ghc monad.
It initialises the GHC session and warnings via initGhcMonad. Each call
to this function will create a new session which should not be shared among
several threads.
Any errors not handled inside the Ghc action are propagated as IO
exceptions.
defaultCleanupHandler :: ExceptionMonad m => DynFlags -> m a -> m a #
This function is no longer necessary, cleanup is now done by runGhc/runGhcT.
defaultErrorHandler :: ExceptionMonad m => FatalMessager -> FlushOut -> m a -> m a #
Install some default exception handlers and run the inner computation. Unless you want to handle exceptions yourself, you should wrap this around the top level of your program. The default handlers output the error message(s) to stderr and exit cleanly.
Minimal complete definition
modSummary, parsedSource
Methods
parsedSource :: m -> ParsedSource #
Instances
| ParsedMod ParsedModule | |
Defined in GHC | |
| ParsedMod TypecheckedModule | |
Defined in GHC Methods | |
| ParsedMod DesugaredModule | |
Defined in GHC | |
class ParsedMod m => TypecheckedMod m where #
Minimal complete definition
renamedSource, typecheckedSource, moduleInfo, tm_internals
Methods
renamedSource :: m -> Maybe RenamedSource #
typecheckedSource :: m -> TypecheckedSource #
moduleInfo :: m -> ModuleInfo #
Instances
| TypecheckedMod TypecheckedModule | |
Defined in GHC Methods renamedSource :: TypecheckedModule -> Maybe RenamedSource # typecheckedSource :: TypecheckedModule -> TypecheckedSource # moduleInfo :: TypecheckedModule -> ModuleInfo # tm_internals :: TypecheckedModule -> (TcGblEnv, ModDetails) | |
| TypecheckedMod DesugaredModule | |
Defined in GHC Methods renamedSource :: DesugaredModule -> Maybe RenamedSource # typecheckedSource :: DesugaredModule -> TypecheckedSource # moduleInfo :: DesugaredModule -> ModuleInfo # tm_internals :: DesugaredModule -> (TcGblEnv, ModDetails) | |
data ParsedModule #
The result of successful parsing.
Constructors
| ParsedModule | |
Fields | |
Instances
| ParsedMod ParsedModule | |
Defined in GHC | |
data TypecheckedModule #
The result of successful typechecking. It also contains the parser result.
Constructors
| TypecheckedModule | |
Instances
| ParsedMod TypecheckedModule | |
Defined in GHC Methods | |
| TypecheckedMod TypecheckedModule | |
Defined in GHC Methods renamedSource :: TypecheckedModule -> Maybe RenamedSource # typecheckedSource :: TypecheckedModule -> TypecheckedSource # moduleInfo :: TypecheckedModule -> ModuleInfo # tm_internals :: TypecheckedModule -> (TcGblEnv, ModDetails) | |
data DesugaredModule #
The result of successful desugaring (i.e., translation to core). Also contains all the information of a typechecked module.
Constructors
| DesugaredModule | |
Fields | |
Instances
| ParsedMod DesugaredModule | |
Defined in GHC | |
| TypecheckedMod DesugaredModule | |
Defined in GHC Methods renamedSource :: DesugaredModule -> Maybe RenamedSource # typecheckedSource :: DesugaredModule -> TypecheckedSource # moduleInfo :: DesugaredModule -> ModuleInfo # tm_internals :: DesugaredModule -> (TcGblEnv, ModDetails) | |
| DesugaredMod DesugaredModule | |
Defined in GHC Methods coreModule :: DesugaredModule -> ModGuts # | |
type ParsedSource = Located (HsModule GhcPs) #
type RenamedSource = (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString) #
type TypecheckedSource = LHsBinds GhcTc #
data CoreModule #
A CoreModule consists of just the fields of a ModGuts that are needed for
the compileToCoreModule interface.
Constructors
| CoreModule | |
Fields
| |
Instances
| Outputable CoreModule | |
Defined in GHC | |
data ModuleInfo #
Container for information about a Module.
cyclicModuleErr :: [ModSummary] -> SDoc #
Arguments
| :: Bool | Drop hi-boot nodes? (see below) |
| -> ModuleGraph | |
| -> Maybe ModuleName | Root module name. If |
| -> [SCC ModSummary] |
Topological sort of the module graph
Calculate SCCs of the module graph, possibly dropping the hi-boot nodes The resulting list of strongly-connected-components is in topologically sorted order, starting with the module(s) at the bottom of the dependency graph (ie compile them first) and ending with the ones at the top.
Drop hi-boot nodes (first boolean arg)?
False: treat the hi-boot summaries as nodes of the graph, so the graph must be acyclicTrue: eliminate the hi-boot nodes, and instead pretend the a source-import of Foo is an import of Foo The resulting graph has no hi-boot nodes, but can be cyclic
load :: GhcMonad m => LoadHowMuch -> m SuccessFlag #
Try to load the program. See LoadHowMuch for the different modes.
This function implements the core of GHC's --make mode. It preprocesses,
compiles and loads the specified modules, avoiding re-compilation wherever
possible. Depending on the target (see hscTarget) compiling
and loading may result in files being created on disk.
Calls the defaultWarnErrLogger after each compiling each module, whether
successful or not.
Throw a SourceError if errors are encountered before the actual
compilation starts (e.g., during dependency analysis). All other errors
are reported using the defaultWarnErrLogger.
Arguments
| :: GhcMonad m | |
| => [ModuleName] | excluded modules |
| -> Bool | allow duplicate roots |
| -> m ModuleGraph |
Perform a dependency analysis starting from the current targets and update the session with the new module graph.
Dependency analysis entails parsing the import directives and may
therefore require running certain preprocessors.
Note that each ModSummary in the module graph caches its DynFlags.
These DynFlags are determined by the current session DynFlags and the
OPTIONS and LANGUAGE pragmas of the parsed module. Thus if you want
changes to the DynFlags to take effect you need to call this function
again.
data LoadHowMuch #
Describes which modules of the module graph need to be loaded.
Constructors
| LoadAllTargets | Load all targets and its dependencies. |
| LoadUpTo ModuleName | Load only the given module and its dependencies. |
| LoadDependenciesOf ModuleName | Load only the dependencies of the given module, but not the module itself. |
moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool #
showModule :: GhcMonad m => ModSummary -> m String #
dynCompileExpr :: GhcMonad m => String -> m Dynamic #
Compile an expression, run it and return the result as a Dynamic.
compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue #
Compile a parsed expression (before renaming), run it, and deliver the resulting HValue.
compileExprRemote :: GhcMonad m => String -> m ForeignHValue #
Compile an expression, run it, and deliver the resulting HValue.
compileExpr :: GhcMonad m => String -> m HValue #
Compile an expression, run it, and deliver the resulting HValue.
parseExpr :: GhcMonad m => String -> m (LHsExpr GhcPs) #
Parse an expression, the parsed expression can be further processed and passed to compileParsedExpr.
parseInstanceHead :: GhcMonad m => String -> m Type #
getInstancesForType :: GhcMonad m => Type -> m [ClsInst] #
exprType :: GhcMonad m => TcRnExprMode -> String -> m Type #
Get the type of an expression
Returns the type as described by TcRnExprMode
getDocs :: GhcMonad m => Name -> m (Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)) #
isDecl :: DynFlags -> String -> Bool #
Returns True if passed string is a declaration but not a splice.
parseName :: GhcMonad m => String -> m [Name] #
Parses a string as an identifier, and returns the list of Names that
the identifier can refer to in the current interactive context.
getRdrNamesInScope :: GhcMonad m => m [RdrName] #
Returns all RdrNames in scope in the current interactive
context, excluding any that are internally-generated.
getNamesInScope :: GhcMonad m => m [Name] #
Returns all names in scope in the current interactive context
getInfo :: GhcMonad m => Bool -> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)) #
Looks up an identifier in the current interactive context (for :info) Filter the instances by the ones whose tycons (or clases resp) are in scope (qualified or otherwise). Otherwise we list a whole lot too many! The exact choice of which ones to show, and which to hide, is a judgement call. (see #1581)
moduleIsInterpreted :: GhcMonad m => Module -> m Bool #
Returns True if the specified module is interpreted, and hence has
its full top-level scope available.
getContext :: GhcMonad m => m [InteractiveImport] #
Get the interactive evaluation context, consisting of a pair of the set of modules from which we take the full top-level scope, and the set of modules from which we take just the exports respectively.
setContext :: GhcMonad m => [InteractiveImport] -> m () #
Set the interactive evaluation context.
(setContext imports) sets the ic_imports field (which in turn
determines what is in scope at the prompt) to imports, and
constructs the ic_rn_glb_env environment to reflect it.
We retain in scope all the things defined at the prompt, and kept in ic_tythings. (Indeed, they shadow stuff from ic_imports.)
abandonAll :: GhcMonad m => m Bool #
resumeExec :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> m ExecResult #
parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) #
runParsedDecls :: GhcMonad m => [LHsDecl GhcPs] -> m [Name] #
Like runDeclsWithLocation, but takes parsed declarations as argument.
Useful when doing preprocessing on the AST before execution, e.g. in GHCi
(see GHCi.UI.runStmt).
runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name] #
Run some declarations and return any user-visible names that were brought into scope.
execStmt' :: GhcMonad m => GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult #
Like execStmt, but takes a parsed statement as argument. Useful when
doing preprocessing on the AST before execution, e.g. in GHCi (see
GHCi.UI.runStmt).
Arguments
| :: GhcMonad m | |
| => String | a statement (bind or expression) |
| -> ExecOptions | |
| -> m ExecResult |
Run a statement in the current interactive context.
default ExecOptions
getHistoryModule :: History -> Module #
getResumeContext :: GhcMonad m => m [Resume] #
data GetDocsFailure #
Failure modes for getDocs.
Constructors
| NameHasNoModule Name |
|
| NoDocsInIface Module Bool |
|
| InteractiveName | The |
Instances
| Outputable GetDocsFailure | |
Defined in InteractiveEval | |
showModuleIndex :: (Int, Int) -> String #
dumpIfaceStats :: HscEnv -> IO () #
hscCompileCoreExpr' :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue #
hscCompileCoreExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue #
Arguments
| :: HscEnv | |
| -> Bool | Normalise the type |
| -> String | The type as a string |
| -> IO (Type, Kind) | Resulting type (possibly normalised) and kind |
Find the kind of a type, after generalisation
Arguments
| :: HscEnv | |
| -> TcRnExprMode | |
| -> String | The expression |
| -> IO Type |
Typecheck an expression (but don't run it)
hscAddSptEntries :: HscEnv -> [SptEntry] -> IO () #
Load the given static-pointer table entries into the interpreter. See Note [Grand plan for static forms] in StaticPtrTable.
hscParsedDecls :: HscEnv -> [LHsDecl GhcPs] -> IO ([TyThing], InteractiveContext) #
Arguments
| :: HscEnv | |
| -> String | The statement |
| -> String | The source |
| -> Int | Starting line |
| -> IO ([TyThing], InteractiveContext) |
Compile a decls
Arguments
| :: HscEnv | |
| -> String | The statement |
| -> IO ([TyThing], InteractiveContext) |
Compile a decls
Arguments
| :: HscEnv | |
| -> String | The statement |
| -> String | The source |
| -> Int | Starting line |
| -> IO (Maybe ([Id], ForeignHValue, FixityEnv)) |
Compile a stmt all the way to an HValue, but don't run it
We return Nothing to indicate an empty statement (or comment only), not a parse error.
hscStmt :: HscEnv -> String -> IO (Maybe ([Id], ForeignHValue, FixityEnv)) #
Compile a stmt all the way to an HValue, but don't run it
We return Nothing to indicate an empty statement (or comment only), not a parse error.
hscInteractive :: HscEnv -> CgGuts -> ModLocation -> IO (Maybe FilePath, CompiledByteCode, [SptEntry]) #
Arguments
| :: HscEnv | |
| -> CgGuts | |
| -> ModLocation | |
| -> FilePath | |
| -> IO (FilePath, Maybe FilePath, [(ForeignSrcLang, FilePath)]) |
|
Compile to hard-code.
hscSimpleIface' :: TcGblEnv -> Maybe Fingerprint -> Hsc (ModIface, Maybe Fingerprint, ModDetails) #
hscGetSafe :: HscEnv -> Module -> SrcSpan -> IO (Bool, Set InstalledUnitId) #
Return if a module is trusted and the pkgs it depends on to be trusted.
hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO Bool #
Check that a module is safe to import.
We return True to indicate the import is safe and False otherwise although in the False case an exception may be thrown first.
hscFileFrontEnd :: ModSummary -> Hsc TcGblEnv #
Given a ModSummary, parses and typechecks it, returning the
TcGblEnv resulting from type-checking.
oneShotMsg :: HscEnv -> RecompileRequired -> IO () #
hscMaybeWriteIface :: DynFlags -> ModIface -> Maybe Fingerprint -> ModLocation -> IO () #
hscIncrementalCompile :: Bool -> Maybe TcGblEnv -> Maybe Messager -> HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> (Int, Int) -> IO (HscStatus, ModDetails, DynFlags) #
Used by both OneShot and batch mode. Runs the pipeline HsSyn and Core parts of the pipeline. We return a interface if we already had an old one around and recompilation was not needed. Otherwise it will be created during later passes when we run the compilation pipeline.
makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails #
Make a ModDetails from the results of typechecking. Used when
typechecking only, as opposed to full compilation.
hscDesugar' :: ModLocation -> TcGblEnv -> Hsc ModGuts #
hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts #
Convert a typechecked module to Core
tcRnModule' :: ModSummary -> Bool -> HsParsedModule -> Hsc TcGblEnv #
hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff) #
Rename and typecheck a module, additionally returning the renamed syntax
hscParse' :: ModSummary -> Hsc HsParsedModule #
hscParse :: HscEnv -> ModSummary -> IO HsParsedModule #
parse a file, returning the abstract syntax
hscRnImportDecls :: HscEnv -> [LImportDecl GhcPs] -> IO GlobalRdrEnv #
Rename some import declarations
hscTcRnLookupRdrName :: HscEnv -> Located RdrName -> IO [Name] #
Lookup things in the compiler's environment
ioMsgMaybe :: IO (Messages, Maybe a) -> Hsc a #
Deal with errors and warnings returned by a compilation step
In order to reduce dependencies to other parts of the compiler, functions
outside the "main" parts of GHC return warnings and errors as a parameter
and signal success via by wrapping the result in a Maybe type. This
function logs the returned warnings and propagates errors as exceptions
(of type SourceError).
This function assumes the following invariants:
- If the second result indicates success (is of the form 'Just x'), there must be no error messages in the first result.
- If there are no error messages, but the second result indicates failure
there should be warnings in the first result. That is, if the action
failed, it must have been due to the warnings (i.e.,
-Werror).
type Messager = HscEnv -> (Int, Int) -> RecompileRequired -> ModSummary -> IO () #
data TcRnExprMode #
How should we infer a type? See Note [TcRnExprMode]
Constructors
| TM_Inst | Instantiate the type fully (:type) |
| TM_NoInst | Do not instantiate the type (:type +v) |
| TM_Default | Default the type eagerly (:type +d) |
pprFamInst :: FamInst -> SDoc #
Pretty-prints a FamInst (type/data family instance) with its defining location.
printException :: GhcMonad m => SourceError -> m () #
Print the error message and all warnings. Useful inside exception handlers. Clears warnings after printing.
getSessionDynFlags :: GhcMonad m => m DynFlags #
Grabs the DynFlags from the Session
class (Functor m, MonadIO m, ExceptionMonad m, HasDynFlags m) => GhcMonad (m :: Type -> Type) where #
A monad that has all the features needed by GHC API calls.
In short, a GHC monad
- allows embedding of IO actions,
- can log warnings,
- allows handling of (extensible) exceptions, and
- maintains a current session.
If you do not use Ghc or GhcT, make sure to call initGhcMonad
before any call to the GHC API functions can occur.
A minimal implementation of a GhcMonad. If you need a custom monad,
e.g., to maintain additional state consider wrapping this monad or using
GhcT.
data GhcT (m :: Type -> Type) a #
A monad transformer to add GHC specific features to another monad.
Note that the wrapped monad must support IO and handling of exceptions.
Instances
| Monad m => Monad (GhcT m) | |
| Functor m => Functor (GhcT m) | |
| Applicative m => Applicative (GhcT m) | |
| MonadIO m => MonadIO (GhcT m) | |
| ExceptionMonad m => GhcMonad (GhcT m) | |
Defined in GhcMonad | |
| MonadIO m => HasDynFlags (GhcT m) | |
Defined in GhcMonad Methods getDynFlags :: GhcT m DynFlags # | |
| ExceptionMonad m => ExceptionMonad (GhcT m) | |
| (ExceptionMonad m, GhcMonadLike m) => GhcMonadLike (GhcT m) Source # | |
Defined in Language.Haskell.Liquid.GHC.GhcMonadLike | |
| (ExceptionMonad m, HasHscEnv m) => HasHscEnv (GhcT m) Source # | |
type WarnErrLogger = forall (m :: Type -> Type). GhcMonad m => Maybe SourceError -> m () #
A function called to log warnings and errors.
phaseForeignLanguage :: Phase -> Maybe ForeignSrcLang #
Foreign language of the phase if the phase deals with a foreign code
byteCodeOfObject :: Unlinked -> CompiledByteCode #
Retrieve the compiled byte-code if possible. Panic if it is a file-based linkable
nameOfObject :: Unlinked -> FilePath #
Retrieve the filename of the linkable if possible. Panic if it is a byte-code object
isInterpretable :: Unlinked -> Bool #
Is this a bytecode linkable with no file on disk?
linkableObjs :: Linkable -> [FilePath] #
isObjectLinkable :: Linkable -> Bool #
numToTrustInfo :: Word8 -> IfaceTrustInfo #
trustInfoToNum :: IfaceTrustInfo -> Word8 #
isHpcUsed :: HpcInfo -> AnyHpcUsage #
Find out if HPC is used by this module or any of the modules it depends upon
emptyHpcInfo :: AnyHpcUsage -> HpcInfo #
showModMsg :: DynFlags -> HscTarget -> Bool -> ModSummary -> String #
isBootSummary :: ModSummary -> Bool #
Did this ModSummary originate from a hs-boot file?
msObjFilePath :: ModSummary -> FilePath #
msHiFilePath :: ModSummary -> FilePath #
msHsFilePath :: ModSummary -> FilePath #
ms_home_imps :: ModSummary -> [Located ModuleName] #
All of the (possibly) home module imports from a
ModSummary; that is to say, each of these module names
could be a home import if an appropriately named file
existed. (This is in contrast to package qualified
imports, which are guaranteed not to be home imports.)
ms_home_srcimps :: ModSummary -> [Located ModuleName] #
Like ms_home_imps, but for SOURCE imports.
ms_home_allimps :: ModSummary -> [ModuleName] #
home_imps :: [(Maybe FastString, Located ModuleName)] -> [Located ModuleName] #
ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)] #
ms_mod_name :: ModSummary -> ModuleName #
mkModuleGraph :: [ModSummary] -> ModuleGraph #
extendMG :: ModuleGraph -> ModSummary -> ModuleGraph #
Add a ModSummary to ModuleGraph. Assumes that the new ModSummary is not an element of the ModuleGraph.
emptyMG :: ModuleGraph #
mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary #
Look up a ModSummary in the ModuleGraph
mgElemModule :: ModuleGraph -> Module -> Bool #
mgModSummaries :: ModuleGraph -> [ModSummary] #
mgBootModules :: ModuleGraph -> ModuleSet #
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph #
Map a function f over all the ModSummaries.
To preserve invariants f can't change the isBoot status.
needsTemplateHaskellOrQQ :: ModuleGraph -> Bool #
Determines whether a set of modules requires Template Haskell or Quasi Quotes
Note that if the session's DynFlags enabled Template Haskell when
depanal was called, then each module in the returned module graph will
have Template Haskell enabled whether it is actually needed or not.
mkHsSOName :: Platform -> FilePath -> FilePath #
lookupFixity :: FixityEnv -> Name -> Fixity #
mkIfaceWarnCache :: Warnings -> OccName -> Maybe WarningTxt #
Constructs the cache for the mi_warn_fn field of a ModIface
tyThingConLike :: TyThing -> ConLike #
tyThingDataCon :: TyThing -> DataCon #
tyThingCoAxiom :: TyThing -> CoAxiom Branched #
tyThingTyCon :: TyThing -> TyCon #
lookupTypeHscEnv :: HscEnv -> Name -> IO (Maybe TyThing) #
As lookupType, but with a marginally easier-to-use interface
if you have a HscEnv
lookupType :: DynFlags -> HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing #
Find the TyThing for the given Name by using all the resources
at our disposal: the compiled modules in the HomePackageTable and the
compiled modules in other packages that live in PackageTypeEnv. Note
that this does NOT look up the TyThing in the module being compiled: you
have to do that yourself, if desired
plusTypeEnv :: TypeEnv -> TypeEnv -> TypeEnv #
extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv #
extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv #
extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv #
mkTypeEnvWithImplicits :: [TyThing] -> TypeEnv #
typeEnvClasses :: TypeEnv -> [Class] #
typeEnvDataCons :: TypeEnv -> [DataCon] #
typeEnvPatSyns :: TypeEnv -> [PatSyn] #
typeEnvIds :: TypeEnv -> [Id] #
typeEnvCoAxioms :: TypeEnv -> [CoAxiom Branched] #
typeEnvTyCons :: TypeEnv -> [TyCon] #
typeEnvElts :: TypeEnv -> [TyThing] #
emptyTypeEnv :: TypeEnv #
tyThingAvailInfo :: TyThing -> [AvailInfo] #
The Names that a TyThing should bring into scope. Used to build the GlobalRdrEnv for the InteractiveContext.
tyThingsTyCoVars :: [TyThing] -> TyCoVarSet #
tyThingParent_maybe :: TyThing -> Maybe TyThing #
tyThingParent_maybe x returns (Just p) when pprTyThingInContext should print a declaration for p (albeit with some "..." in it) when asked to show x It returns the *immediate* parent. So a datacon returns its tycon but the tycon could be the associated type of a class, so it in turn might have a parent.
isImplicitTyThing :: TyThing -> Bool #
Returns True if there should be no interface-file declaration
for this thing on its own: either it is built-in, or it is part
of some other declaration, or it is generated implicitly by some
other declaration.
implicitTyConThings :: TyCon -> [TyThing] #
implicitClassThings :: Class -> [TyThing] #
implicitTyThings :: TyThing -> [TyThing] #
pkgQual :: DynFlags -> PrintUnqualified #
A function which only qualifies package names if necessary; but qualifies all other identifiers.
mkQualPackage :: DynFlags -> QueryQualifyPackage #
Creates a function for formatting packages based on two heuristics: (1) don't qualify if the package in question is "main", and (2) only qualify with a unit id if the package ID would be ambiguous.
mkQualModule :: DynFlags -> QueryQualifyModule #
Creates a function for formatting modules based on two heuristics: (1) if the module is the current module, don't qualify, and (2) if there is only one exposed package which exports this module, don't qualify.
mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified #
Creates some functions that work out the best ways to format names for the user according to a set of heuristics.
icExtendGblRdrEnv :: GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv #
Add TyThings to the GlobalRdrEnv, earlier ones in the list shadowing later ones, and shadowing existing entries in the GlobalRdrEnv.
setInteractivePackage :: HscEnv -> HscEnv #
extendInteractiveContext :: InteractiveContext -> [TyThing] -> [ClsInst] -> [FamInst] -> Maybe [Type] -> FixityEnv -> InteractiveContext #
extendInteractiveContext is called with new TyThings recently defined to update the InteractiveContext to include them. Ids are easily removed when shadowed, but Classes and TyCons are not. Some work could be done to determine whether they are entirely shadowed, but as you could still have references to them (e.g. instances for classes or values of the type for TyCons), it's not clear whether removing them is even the appropriate behavior.
icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified #
Get the PrintUnqualified function based on the flags and this InteractiveContext
icInScopeTTs :: InteractiveContext -> [TyThing] #
This function returns the list of visible TyThings (useful for e.g. showBindings)
emptyInteractiveContext :: DynFlags -> InteractiveContext #
Constructs an empty InteractiveContext.
appendStubC :: ForeignStubs -> SDoc -> ForeignStubs #
importedByUser :: [ImportedBy] -> [ImportedModsVal] #
emptyModDetails :: ModDetails #
Constructs an empty ModDetails
mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> OccName -> Maybe (OccName, Fingerprint) #
Constructs cache for the mi_hash_fn field of a ModIface
emptyFullModIface :: Module -> ModIface #
renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName #
Given a set of free holes, and a unit identifier, rename
the free holes according to the instantiation of the unit
identifier. For example, if we have A and B free, and
our unit identity is p[A=C,B=impl:B], the renamed free
holes are just C.
mi_free_holes :: ModIface -> UniqDSet ModuleName #
The "precise" free holes, e.g., the signatures that this
ModIface depends on.
mi_semantic_module :: forall (a :: ModIfacePhase). ModIface_ a -> Module #
The semantic module for this interface; e.g., if it's a interface
for a signature, if mi_module is p[A=A]:A, mi_semantic_module
will be A.
mi_fix :: ModIface -> OccName -> Fixity #
Lookups up a (possibly cached) fixity from a ModIface. If one cannot be
found, defaultFixity is returned instead.
Old-style accessor for whether or not the ModIface came from an hs-boot file.
prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv #
Deal with gathering annotations in from all possible places
and combining them into a single AnnEnv
metaRequestAW :: Functor f => MetaHook f -> LHsExpr GhcTc -> f Serialized #
hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule] #
Get rules from modules "below" this one (in the dependency sense)
hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst]) #
Find all the instance declarations (of classes and families) from
the Home Package Table filtered by the provided predicate function.
Used in tcRnImports, to select the instances that are in the
transitive closure of imports from the currently compiled module.
hptCompleteSigs :: HscEnv -> [CompleteMatch] #
lookupIfaceByModule :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface #
lookupHptByModule :: HomePackageTable -> Module -> Maybe HomeModInfo #
listToHpt :: [(ModuleName, HomeModInfo)] -> HomePackageTable #
addListToHpt :: HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable #
addToHpt :: HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable #
mapHpt :: (HomeModInfo -> HomeModInfo) -> HomePackageTable -> HomePackageTable #
allHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> Bool #
filterHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> HomePackageTable #
eltsHpt :: HomePackageTable -> [HomeModInfo] #
lookupHptDirectly :: HomePackageTable -> Unique -> Maybe HomeModInfo #
lookupHpt :: HomePackageTable -> ModuleName -> Maybe HomeModInfo #
pprHPT :: HomePackageTable -> SDoc #
emptyPackageIfaceTable :: PackageIfaceTable #
Constructs an empty PackageIfaceTable
emptyHomePackageTable :: HomePackageTable #
Constructs an empty HomePackageTable
pprTargetId :: TargetId -> SDoc #
hscEPS :: HscEnv -> IO ExternalPackageState #
Retrieve the ExternalPackageState cache.
handleFlagWarnings :: DynFlags -> [Warn] -> IO () #
printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO () #
Given a bag of warnings, turn them into an exception if -Werror is enabled, or print them out otherwise.
Arguments
| :: ExceptionMonad m | |
| => (SourceError -> m a) | exception handler |
| -> m a | action to perform |
| -> m a |
Perform the given action and call the exception handler if the action
throws a SourceError. See SourceError for more information.
throwOneError :: MonadIO io => ErrMsg -> io a #
throwErrors :: MonadIO io => ErrorMessages -> io a #
mkApiErr :: DynFlags -> SDoc -> GhcApiError #
mkSrcErr :: ErrorMessages -> SourceError #
runInteractiveHsc :: HscEnv -> Hsc a -> IO a #
mkInteractiveHscEnv :: HscEnv -> HscEnv #
Status of a compilation to hard-code
Constructors
| HscNotGeneratingCode ModIface | Nothing to do. |
| HscUpToDate ModIface | Nothing to do because code already exists. |
| HscUpdateBoot ModIface | Update boot file result. |
| HscUpdateSig ModIface | Generate signature file (backpack) |
| HscRecomp | Recompile this module. |
Fields
| |
Constructors
| Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages)) |
Instances
| Monad Hsc | |
| Functor Hsc | |
| Applicative Hsc | |
| MonadIO Hsc | |
| HasDynFlags Hsc | |
Defined in HscTypes Methods getDynFlags :: Hsc DynFlags # | |
| GhcMonadLike Hsc Source # | |
Defined in Language.Haskell.Liquid.GHC.GhcMonadLike | |
| HasHscEnv Hsc Source # | |
data SourceError #
A source error is an error that is caused by one or more errors in the
source code. A SourceError is thrown by many functions in the
compilation pipeline. Inside GHC these errors are merely printed via
log_action, but API clients may treat them differently, for example,
insert them into a list box. If you want the default behaviour, use the
idiom:
handleSourceError printExceptionAndWarnings $ do ... api calls that may fail ...
The SourceErrors error messages can be accessed via srcErrorMessages.
This list may be empty if the compiler failed due to -Werror
(Opt_WarnIsError).
See printExceptionAndWarnings for more information on what to take care
of when writing a custom error handler.
Instances
| Show SourceError | |
Defined in HscTypes Methods showsPrec :: Int -> SourceError -> ShowS # show :: SourceError -> String # showList :: [SourceError] -> ShowS # | |
| Exception SourceError | |
Defined in HscTypes Methods toException :: SourceError -> SomeException # fromException :: SomeException -> Maybe SourceError # displayException :: SourceError -> String # | |
| PPrint SourceError Source # | |
Defined in Language.Haskell.Liquid.Types.PrettyPrint | |
| Result SourceError Source # | |
Defined in Language.Haskell.Liquid.GHC.Interface | |
data GhcApiError #
An error thrown if the GHC API is used in an incorrect fashion.
Instances
| Show GhcApiError | |
Defined in HscTypes Methods showsPrec :: Int -> GhcApiError -> ShowS # show :: GhcApiError -> String # showList :: [GhcApiError] -> ShowS # | |
| Exception GhcApiError | |
Defined in HscTypes Methods toException :: GhcApiError -> SomeException # fromException :: SomeException -> Maybe GhcApiError # displayException :: GhcApiError -> String # | |
HscEnv is like Session, except that some of the fields are immutable.
An HscEnv is used to compile a single module from plain Haskell source
code (after preprocessing) to either C, assembly or C--. It's also used
to store the dynamic linker state to allow for multiple linkers in the
same address space.
Things like the module graph don't change during a single compilation.
Historical note: "hsc" used to be the name of the compiler binary, when there was a separate driver and compiler. To compile a single module, the driver would invoke hsc on the source code... so nowadays we think of hsc as the layer of the compiler that deals with compiling a single module.
Constructors
| HscEnv | |
Fields
| |
Constructors
| IServ | |
Fields
| |
A compilation target.
A target may be supplied with the actual text of the module. If so, use this instead of the file contents (this is for use in an IDE where the file hasn't been saved by the user yet).
Constructors
| Target | |
Fields
| |
Constructors
| TargetModule ModuleName | A module name: search for the file |
| TargetFile FilePath (Maybe Phase) | A filename: preprocess & parse it to find the module name. If specified, the Phase indicates how to compile this file (which phase to start from). Nothing indicates the starting phase should be determined from the suffix of the filename. |
type InputFileBuffer = StringBuffer #
type HomePackageTable = DModuleNameEnv HomeModInfo #
Helps us find information about modules in the home package
type PackageIfaceTable = ModuleEnv ModIface #
Helps us find information about modules in the imported packages
data HomeModInfo #
Information about modules in the package being compiled
Constructors
| HomeModInfo | |
Fields
| |
data MetaRequest #
The supported metaprogramming result types
Constructors
| MetaE (LHsExpr GhcPs -> MetaResult) | |
| MetaP (LPat GhcPs -> MetaResult) | |
| MetaT (LHsType GhcPs -> MetaResult) | |
| MetaD ([LHsDecl GhcPs] -> MetaResult) | |
| MetaAW (Serialized -> MetaResult) |
data MetaResult #
data constructors not exported to ensure correct result type
type MetaHook (f :: Type -> Type) = MetaRequest -> LHsExpr GhcTc -> f MetaResult #
type FinderCache = InstalledModuleEnv InstalledFindResult #
The FinderCache maps modules to the result of
searching for that module. It records the results of searching for
modules along the search path. On :load, we flush the entire
contents of this cache.
data InstalledFindResult #
data FindResult #
The result of searching for an imported module.
NB: FindResult manages both user source-import lookups
(which can result in Module) as well as direct imports
for interfaces (which always result in InstalledModule).
Constructors
| Found ModLocation Module | The module was found |
| NoPackage UnitId | The requested package was not found |
| FoundMultiple [(Module, ModuleOrigin)] | _Error_: both in multiple packages |
| NotFound | Not found |
Fields
| |
type PartialModIface = ModIface_ 'ModIfaceCore #
data ModIfaceBackend #
Extends a PartialModIface with information which is either: * Computed after codegen * Or computed just before writing the iface to disk. (Hashes) In order to fully instantiate it.
Constructors
| ModIfaceBackend | |
Fields
| |
data ModIface_ (phase :: ModIfacePhase) #
A ModIface plus a ModDetails summarises everything we know
about a compiled module. The ModIface is the stuff *before* linking,
and can be written out to an interface file. The 'ModDetails is after
linking and can be completely recovered from just the ModIface.
When we read an interface file, we also construct a ModIface from it,
except that we explicitly make the mi_decls and a few other fields empty;
as when reading we consolidate the declarations etc. into a number of indexed
maps and environments in the ExternalPackageState.
Constructors
| ModIface | |
Fields
| |
type IfaceExport = AvailInfo #
The original names declared of a certain module that are exported
data ModDetails #
The ModDetails is essentially a cache for information in the ModIface
for home modules only. Information relating to packages will be loaded into
global environments in ExternalPackageState.
Constructors
| ModDetails | |
Fields
| |
type ImportedMods = ModuleEnv [ImportedBy] #
Records the modules directly imported by a module for extracting e.g. usage information, and also to give better error message
data ImportedBy #
If a module was "imported" by the user, we associate it with
more detailed usage information ImportedModsVal; a module
imported by the system only gets used for usage information.
Constructors
| ImportedByUser ImportedModsVal | |
| ImportedBySystem |
data ImportedModsVal #
Constructors
| ImportedModsVal | |
Fields
| |
A ModGuts is carried through the compiler, accumulating stuff as it goes
There is only one ModGuts at any time, the one for the module
being compiled right now. Once it is compiled, a ModIface and
ModDetails are extracted and the ModGuts is discarded.
Constructors
| ModGuts | |
Fields
| |
A restricted form of ModGuts for code generation purposes
Constructors
| CgGuts | |
Fields
| |
data ForeignStubs #
Foreign export stubs
Constructors
| NoStubs | We don't have any stubs |
| ForeignStubs SDoc SDoc | There are some stubs. Parameters: 1) Header file prototypes for "foreign exported" functions 2) C stubs to use when calling "foreign exported" functions |
data InteractiveContext #
Interactive context, recording information about the state of the context in which statements are executed in a GHCi session.
Constructors
| InteractiveContext | |
Fields
| |
data InteractiveImport #
Constructors
| IIDecl (ImportDecl GhcPs) | Bring the exports of a particular module (filtered by an import decl) into scope |
| IIModule ModuleName | Bring into scope the entire top-level envt of of this module, including the things imported into it. |
Instances
| Outputable InteractiveImport | |
Defined in HscTypes | |
class Monad m => MonadThings (m :: Type -> Type) where #
Class that abstracts out the common ability of the monads in GHC
to lookup a TyThing in the monadic environment by Name. Provides
a number of related convenience functions for accessing particular
kinds of TyThing
Minimal complete definition
Warning information for a module
Constructors
| NoWarnings | Nothing deprecated |
| WarnAll WarningTxt | Whole module deprecated |
| WarnSome [(OccName, WarningTxt)] | Some specific things deprecated |
Fixity information for an Name. We keep the OccName in the range
so that we can generate an interface from it
type WhetherHasOrphans = Bool #
Records whether a module has orphans. An "orphan" is one of:
- An instance declaration in a module other than the definition module for one of the type constructors or classes in the instance head
- A transformation rule in a module other than the one defining the function in the head of the rule
type IsBootInterface = Bool #
Did this module originate from a *-boot file?
data Dependencies #
Dependency information about ALL modules and packages below this one in the import hierarchy.
Invariant: the dependencies of a module M never includes M.
Invariant: none of the lists contain duplicates.
Constructors
| Deps | |
Fields
| |
Instances
| Eq Dependencies | |
Defined in HscTypes | |
| Binary Dependencies | |
Defined in HscTypes Methods put_ :: BinHandle -> Dependencies -> IO () # put :: BinHandle -> Dependencies -> IO (Bin Dependencies) # get :: BinHandle -> IO Dependencies # | |
Records modules for which changes may force recompilation of this module See wiki: https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/recompilation-avoidance
This differs from Dependencies. A module X may be in the dep_mods of this module (via an import chain) but if we don't use anything from X it won't appear in our Usage
Constructors
| UsagePackageModule | Module from another package |
Fields
| |
| UsageHomeModule | Module from the current package
| A file upon which the module depends, e.g. a CPP #include, or using TH's
|
Fields
| |
| UsageFile | |
Fields
| |
| UsageMergedRequirement | A requirement which was merged into this one. |
Fields
| |
type PackageTypeEnv = TypeEnv #
type PackageRuleBase = RuleBase #
type PackageInstEnv = InstEnv #
type PackageFamInstEnv = FamInstEnv #
data ExternalPackageState #
Information about other packages that we have slurped in by reading their interface files
Constructors
| EPS | |
Fields
| |
Accumulated statistics about what we are putting into the ExternalPackageState.
"In" means stuff that is just read from interface files,
"Out" means actually sucked in and type-checked
Constructors
| EpsStats | |
Fields
| |
data ModuleGraph #
A ModuleGraph contains all the nodes from the home package (only). There will be a node for each source module, plus a node for each hi-boot module.
The graph is not necessarily stored in topologically-sorted order. Use
topSortModuleGraph and flattenSCC to achieve this.
data ModSummary #
A single node in a ModuleGraph. The nodes of the module graph
are one of:
- A regular Haskell source module
- A hi-boot source module
Constructors
| ModSummary | |
Fields
| |
Instances
| Outputable ModSummary | |
Defined in HscTypes | |
data SourceModified #
Indicates whether a given module's source has been modified since it was last compiled.
Constructors
| SourceModified | the source has been modified |
| SourceUnmodified | the source has not been modified. Compilation may or may not be necessary, depending on whether any dependencies have changed since we last compiled. |
| SourceUnmodifiedAndStable | the source has not been modified, and furthermore all of its (transitive) dependencies are up to date; it definitely does not need to be recompiled. This is important for two reasons: (a) we can omit the version check in checkOldIface, and (b) if the module used TH splices we don't need to force recompilation. |
Information about a modules use of Haskell Program Coverage
Constructors
| HpcInfo | |
Fields
| |
| NoHpcInfo | |
Fields
| |
type AnyHpcUsage = Bool #
This is used to signal if one of my imports used HPC instrumentation even if there is no module-local HPC usage
type IsSafeImport = Bool #
Is an import a safe import?
data IfaceTrustInfo #
Safe Haskell information for ModIface
Simply a wrapper around SafeHaskellMode to sepperate iface and flags
Instances
| Binary IfaceTrustInfo | |
Defined in HscTypes Methods put_ :: BinHandle -> IfaceTrustInfo -> IO () # put :: BinHandle -> IfaceTrustInfo -> IO (Bin IfaceTrustInfo) # get :: BinHandle -> IO IfaceTrustInfo # | |
| Outputable IfaceTrustInfo | |
Defined in HscTypes | |
data HsParsedModule #
Constructors
| HsParsedModule | |
Fields
| |
data CompleteMatch #
A list of conlikes which represents a complete pattern match.
These arise from COMPLETE signatures.
Constructors
| CompleteMatch | |
Fields
| |
Instances
| Outputable CompleteMatch | |
Defined in HscTypes | |
type CompleteMatchMap = UniqFM [CompleteMatch] #
A map keyed by the completeMatchTyCon.
Haskell Module
All we actually declare here is the top-level structure for a module.
Constructors
| HsModule | |
Fields
| |
Instances
| Data (HsModule GhcPs) | |
Defined in GHC.Hs Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcPs -> c (HsModule GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcPs) # toConstr :: HsModule GhcPs -> Constr # dataTypeOf :: HsModule GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsModule GhcPs -> HsModule GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) # | |
| Data (HsModule GhcRn) | |
Defined in GHC.Hs Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcRn -> c (HsModule GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcRn) # toConstr :: HsModule GhcRn -> Constr # dataTypeOf :: HsModule GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsModule GhcRn -> HsModule GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) # | |
| Data (HsModule GhcTc) | |
Defined in GHC.Hs Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcTc -> c (HsModule GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcTc) # toConstr :: HsModule GhcTc -> Constr # dataTypeOf :: HsModule GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsModule GhcTc -> HsModule GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) # | |
| OutputableBndrId p => Outputable (HsModule (GhcPass p)) | |
hsValBindsImplicits :: forall (idR :: Pass). HsValBindsLR GhcRn (GhcPass idR) -> [(SrcSpan, [Name])] #
lStmtsImplicits :: forall (idR :: Pass) body. [LStmtLR GhcRn (GhcPass idR) (Located (body (GhcPass idR)))] -> [(SrcSpan, [Name])] #
hsDataFamInstBinders :: forall (p :: Pass). DataFamInstDecl (GhcPass p) -> ([Located (IdP (GhcPass p))], [LFieldOcc (GhcPass p)]) #
the SrcLoc returned are for the whole declarations, not just the names
getPatSynBinds :: [(RecFlag, LHsBinds id)] -> [PatSynBind id id] #
hsPatSynSelectors :: forall (p :: Pass). HsValBinds (GhcPass p) -> [IdP (GhcPass p)] #
Collects record pattern-synonym selectors only; the pattern synonym names are collected by collectHsValBinders.
hsForeignDeclsBinders :: [LForeignDecl pass] -> [Located (IdP pass)] #
See Note [SrcSpan for binders]
hsLTyClDeclBinders :: forall (p :: Pass). Located (TyClDecl (GhcPass p)) -> ([Located (IdP (GhcPass p))], [LFieldOcc (GhcPass p)]) #
Returns all the binding names of the decl. The first one is guaranteed to be the name of the decl. The first component represents all binding names except record fields; the second represents field occurrences. For record fields mentioned in multiple constructors, the SrcLoc will be from the first occurrence.
Each returned (Located name) has a SrcSpan for the whole declaration. See Note [SrcSpan for binders]
hsTyClForeignBinders :: [TyClGroup GhcRn] -> [LForeignDecl GhcRn] -> [Name] #
hsGroupBinders :: HsGroup GhcRn -> [Name] #
collectStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. StmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] #
collectLStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. LStmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] #
collectStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. [StmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] #
collectLStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. [LStmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] #
collectMethodBinders :: LHsBindsLR idL idR -> [Located (IdP idL)] #
Used exclusively for the bindings of an instance decl which are all FunBinds
collectHsBindListBinders :: forall (p :: Pass) idR. [LHsBindLR (GhcPass p) idR] -> [IdP (GhcPass p)] #
Same as collectHsBindsBinders, but works over a list of bindings
collectHsBindsBinders :: forall (p :: Pass) idR. LHsBindsLR (GhcPass p) idR -> [IdP (GhcPass p)] #
collectHsBindBinders :: (SrcSpanLess (LPat p) ~ Pat p, HasSrcSpan (LPat p)) => HsBindLR p idR -> [IdP p] #
Collect both Ids and pattern-synonym binders
collectHsValBinders :: forall (idL :: Pass) (idR :: Pass). HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] #
Collect Id binders only, or Ids + pattern synonyms, respectively
collectHsIdBinders :: forall (idL :: Pass) (idR :: Pass). HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] #
Collect Id binders only, or Ids + pattern synonyms, respectively
collectLocalBinders :: forall (idL :: Pass) (idR :: Pass). HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] #
isBangedHsBind :: HsBind GhcTc -> Bool #
Is a binding a strict variable or pattern bind (e.g. !x = ...)?
isUnliftedHsBind :: HsBind GhcTc -> Bool #
Should we treat this as an unlifted bind? This will be true for any bind that binds an unlifted variable, but we must be careful around AbsBinds. See Note [Unlifted id check in isUnliftedHsBind]. For usage information, see Note [Strict binds check] is DsBinds.
mkMatch :: forall (p :: Pass). HsMatchContext (NameOrRdrName (IdP (GhcPass p))) -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> Located (HsLocalBinds (GhcPass p)) -> LMatch (GhcPass p) (LHsExpr (GhcPass p)) #
mkPrefixFunRhs :: Located id -> HsMatchContext id #
Make a prefix, non-strict function HsMatchContext
mkSimpleGeneratedFunBind :: SrcSpan -> RdrName -> [LPat GhcPs] -> LHsExpr GhcPs -> LHsBind GhcPs #
Convenience function using mkFunBind.
This is for generated bindings only, do not use for user-written code.
isInfixFunBind :: HsBindLR id1 id2 -> Bool #
mkPatSynBind :: Located RdrName -> HsPatSynDetails (Located RdrName) -> LPat GhcPs -> HsPatSynDir GhcPs -> HsBind GhcPs #
mkTopFunBind :: Origin -> Located Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn #
In Name-land, with empty bind_fvs
mkFunBind :: Origin -> Located RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> HsBind GhcPs #
Not infix, with place holders for coercion and free vars
mkHsWrapPatCo :: forall (id :: Pass). TcCoercionN -> Pat (GhcPass id) -> Type -> Pat (GhcPass id) #
mkLHsWrapCo :: forall (id :: Pass). TcCoercionN -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
mkHsWrapCoR :: forall (id :: Pass). TcCoercionR -> HsExpr (GhcPass id) -> HsExpr (GhcPass id) #
mkHsWrapCo :: forall (id :: Pass). TcCoercionN -> HsExpr (GhcPass id) -> HsExpr (GhcPass id) #
mkHsWrap :: forall (id :: Pass). HsWrapper -> HsExpr (GhcPass id) -> HsExpr (GhcPass id) #
Avoid (HsWrap co (HsWrap co' _)). See Note [Detecting forced eta expansion] in DsExpr
typeToLHsType :: Type -> LHsType GhcPs #
Converting a Type to an HsType RdrName This is needed to implement GeneralizedNewtypeDeriving.
Note that we use getRdrName extensively, which
generates Exact RdrNames rather than strings.
mkClassOpSigs :: [LSig GhcPs] -> [LSig GhcPs] #
Convert TypeSig to ClassOpSig The former is what is parsed, but the latter is what we need in class/instance declarations
mkLHsSigWcType :: LHsType GhcPs -> LHsSigWcType GhcPs #
mkLHsSigType :: LHsType GhcPs -> LHsSigType GhcPs #
Split a list into lists that are small enough to have a corresponding
tuple arity. The sub-lists of the result all have length <= mAX_TUPLE_SIZE
But there may be more than mAX_TUPLE_SIZE sub-lists
Arguments
| :: ([a] -> a) | "Small" constructor function, of maximum input arity |
| -> [a] | Possible "big" list of things to construct from |
| -> a | Constructed thing made possible by recursive decomposition |
Lifts a "small" constructor into a "big" constructor by recursive decompositon
mkBigLHsVarTup :: forall (id :: Pass). [IdP (GhcPass id)] -> LHsExpr (GhcPass id) #
The Big equivalents for the source tuple expressions
nlHsAppKindTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsKind (GhcPass p) -> LHsType (GhcPass p) #
nlHsTyConApp :: forall (p :: Pass). IdP (GhcPass p) -> [LHsType (GhcPass p)] -> LHsType (GhcPass p) #
nlHsFunTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
nlHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
nlHsIf :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
Note [Rebindable nlHsIf] nlHsIf should generate if-expressions which are NOT subject to RebindableSyntax, so the first field of HsIf is Nothing. (#12080)
nlWildPatName :: LPat GhcRn #
Wildcard pattern - after renaming
nlWildConPat :: DataCon -> LPat GhcPs #
nlHsVarApps :: forall (id :: Pass). IdP (GhcPass id) -> [IdP (GhcPass id)] -> LHsExpr (GhcPass id) #
nlHsApps :: forall (id :: Pass). IdP (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) #
nlHsSyntaxApps :: forall (id :: Pass). SyntaxExpr (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) #
nlHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
nlHsDataCon :: DataCon -> LHsExpr GhcTc #
NB: Only for LHsExpr **Id**
mkHsStringPrimLit :: forall (p :: Pass). FastString -> HsLit (GhcPass p) #
mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsSplice GhcPs #
mkTypedSplice :: SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs #
mkUntypedSplice :: SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs #
mkHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> HsExpr GhcPs #
A useful function for building OpApps. The operator is always a
variable, and we don't know the fixity yet.
mkRecStmt :: forall (idL :: Pass) bodyR. [LStmtLR (GhcPass idL) GhcPs bodyR] -> StmtLR (GhcPass idL) GhcPs bodyR #
emptyRecStmtId :: StmtLR GhcTc GhcTc bodyR #
emptyRecStmtName :: StmtLR GhcRn GhcRn bodyR #
mkBindStmt :: forall (idL :: Pass) (idR :: Pass) bodyR. XBindStmt (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) ~ NoExtField => LPat (GhcPass idL) -> Located (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) #
mkBodyStmt :: forall bodyR (idL :: Pass). Located (bodyR GhcPs) -> StmtLR (GhcPass idL) GhcPs (Located (bodyR GhcPs)) #
mkLastStmt :: forall bodyR (idR :: Pass) (idL :: Pass). Located (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) #
mkGroupByUsingStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) #
mkTransformByStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) #
mkHsCmdIf :: forall (p :: Pass). LHsExpr (GhcPass p) -> LHsCmd (GhcPass p) -> LHsCmd (GhcPass p) -> HsCmd (GhcPass p) #
mkHsIf :: forall (p :: Pass). LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) -> HsExpr (GhcPass p) #
mkHsIsString :: SourceText -> FastString -> HsOverLit GhcPs #
mkHsIntegral :: IntegralLit -> HsOverLit GhcPs #
mkLHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
Wrap in parens if (hsExprNeedsParens appPrec) says it needs them So 'f x' becomes '(f x)', but '3' stays as '3'
nlHsTyApps :: forall (id :: Pass). IdP (GhcPass id) -> [Type] -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) #
mkHsCaseAlt :: forall (p :: Pass) body. LPat (GhcPass p) -> Located (body (GhcPass p)) -> LMatch (GhcPass p) (Located (body (GhcPass p))) #
A simple case alternative with a single pattern, no binds, no guards; pre-typechecking
mkHsLam :: forall (p :: Pass). XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ NoExtField => [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) #
mkHsAppType :: forall (id :: Pass). NoGhcTc (GhcPass id) ~ GhcRn => LHsExpr (GhcPass id) -> LHsWcType GhcRn -> LHsExpr (GhcPass id) #
mkHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
mkMatchGroup :: XMG name (Located (body name)) ~ NoExtField => Origin -> [LMatch name (Located (body name))] -> MatchGroup name (Located (body name)) #
unguardedRHS :: forall body (p :: Pass). SrcSpan -> Located (body (GhcPass p)) -> [LGRHS (GhcPass p) (Located (body (GhcPass p)))] #
unguardedGRHSs :: forall body (p :: Pass). Located (body (GhcPass p)) -> GRHSs (GhcPass p) (Located (body (GhcPass p))) #
mkSimpleMatch :: forall (p :: Pass) body. HsMatchContext (NameOrRdrName (IdP (GhcPass p))) -> [LPat (GhcPass p)] -> Located (body (GhcPass p)) -> LMatch (GhcPass p) (Located (body (GhcPass p))) #
pprStmtInCtxt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => HsStmtContext (IdP (GhcPass idL)) -> StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc #
pprMatchInCtxt :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable (NameOrRdrName (NameOrRdrName (IdP (GhcPass idR)))), Outputable body) => Match (GhcPass idR) body -> SDoc #
matchContextErrString :: Outputable id => HsMatchContext id -> SDoc #
pprStmtContext :: (Outputable id, Outputable (NameOrRdrName id)) => HsStmtContext id -> SDoc #
pprAStmtContext :: (Outputable id, Outputable (NameOrRdrName id)) => HsStmtContext id -> SDoc #
pprMatchContextNoun :: (Outputable (NameOrRdrName id), Outputable id) => HsMatchContext id -> SDoc #
pprMatchContext :: (Outputable (NameOrRdrName id), Outputable id) => HsMatchContext id -> SDoc #
matchSeparator :: HsMatchContext id -> SDoc #
isMonadCompContext :: HsStmtContext id -> Bool #
isMonadFailStmtContext :: HsStmtContext id -> Bool #
Should pattern match failure in a HsStmtContext be desugared using
MonadFail?
isComprehensionContext :: HsStmtContext id -> Bool #
isPatSynCtxt :: HsMatchContext id -> Bool #
thTyBrackets :: SDoc -> SDoc #
thBrackets :: SDoc -> SDoc -> SDoc #
pprHsBracket :: forall (p :: Pass). OutputableBndrId p => HsBracket (GhcPass p) -> SDoc #
isTypedBracket :: HsBracket id -> Bool #
ppr_splice :: forall (p :: Pass). OutputableBndrId p => SDoc -> IdP (GhcPass p) -> LHsExpr (GhcPass p) -> SDoc -> SDoc #
ppr_quasi :: OutputableBndr p => p -> p -> FastString -> SDoc #
ppr_splice_decl :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SDoc #
pprPendingSplice :: forall (p :: Pass). OutputableBndrId p => SplicePointName -> LHsExpr (GhcPass p) -> SDoc #
isTypedSplice :: HsSplice id -> Bool #
pprQuals :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body) => [LStmt (GhcPass p) body] -> SDoc #
pprComp :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body) => [LStmt (GhcPass p) body] -> SDoc #
ppr_do_stmts :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => [LStmtLR (GhcPass idL) (GhcPass idR) body] -> SDoc #
pprDo :: forall (p :: Pass) body any. (OutputableBndrId p, Outputable body) => HsStmtContext any -> [LStmt (GhcPass p) body] -> SDoc #
pprBy :: Outputable body => Maybe body -> SDoc #
pprTransStmt :: Outputable body => Maybe body -> body -> TransForm -> SDoc #
pprTransformStmt :: forall (p :: Pass). OutputableBndrId p => [IdP (GhcPass p)] -> LHsExpr (GhcPass p) -> Maybe (LHsExpr (GhcPass p)) -> SDoc #
pprArg :: forall (idL :: Pass). OutputableBndrId idL => ApplicativeArg (GhcPass idL) -> SDoc #
pprStmt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc #
pp_rhs :: Outputable body => HsMatchContext idL -> body -> SDoc #
pprGRHS :: forall (idR :: Pass) body idL. (OutputableBndrId idR, Outputable body) => HsMatchContext idL -> GRHS (GhcPass idR) body -> SDoc #
pprGRHSs :: forall (idR :: Pass) body idL. (OutputableBndrId idR, Outputable body) => HsMatchContext idL -> GRHSs (GhcPass idR) body -> SDoc #
pprMatch :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> SDoc #
pprMatches :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc #
matchGroupArity :: forall (id :: Pass) body. MatchGroup (GhcPass id) body -> Arity #
isSingletonMatchGroup :: [LMatch id body] -> Bool #
Is there only one RHS in this list of matches?
isEmptyMatchGroup :: MatchGroup id body -> Bool #
isInfixMatch :: Match id body -> Bool #
isQuietHsCmd :: HsCmd id -> Bool #
isAtomicHsExpr :: HsExpr id -> Bool #
parenthesizeHsExpr :: forall (p :: Pass). PprPrec -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) #
checks if parenthesizeHsExpr p e is true,
and if so, surrounds hsExprNeedsParens p ee with an HsPar. Otherwise, it simply returns e.
hsExprNeedsParens :: PprPrec -> HsExpr p -> Bool #
returns hsExprNeedsParens p eTrue if the expression e needs
parentheses under precedence p.
pprParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> HsExpr (GhcPass p) -> SDoc #
pprParendLExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc #
pprDebugParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc #
pprExternalSrcLoc :: (StringLiteral, (Int, Int), (Int, Int)) -> SDoc #
ppr_apps :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> [Either (LHsExpr (GhcPass p)) (LHsWcType (NoGhcTc (GhcPass p)))] -> SDoc #
ppr_infix_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> Maybe SDoc #
pprBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> SDoc #
isQuietHsExpr :: HsExpr id -> Bool #
tupArgPresent :: LHsTupArg id -> Bool #
unboundVarOcc :: UnboundVar -> OccName #
mkRnSyntaxExpr :: Name -> SyntaxExpr GhcRn #
Make a 'SyntaxExpr Name' (the "rn" is because this is used in the renamer), missing its HsWrappers.
mkSyntaxExpr :: forall (p :: Pass). HsExpr (GhcPass p) -> SyntaxExpr (GhcPass p) #
Make a 'SyntaxExpr (HsExpr _)', missing its HsWrappers.
noSyntaxExpr :: forall (p :: Pass). SyntaxExpr (GhcPass p) #
noExpr :: forall (p :: Pass). HsExpr (GhcPass p) #
This is used for rebindable-syntax pieces that are too polymorphic for tcSyntaxOp (trS_fmap and the mzip in ParStmt)
type PostTcExpr = HsExpr GhcTc #
Post-Type checking Expression
PostTcExpr is an evidence expression attached to the syntax tree by the type checker (c.f. postTcType).
type PostTcTable = [(Name, PostTcExpr)] #
Post-Type checking Table
We use a PostTcTable where there are a bunch of pieces of evidence, more than is convenient to keep individually.
type CmdSyntaxTable p = [(Name, HsExpr p)] #
Command Syntax Table (for Arrow syntax)
data UnboundVar #
An unbound variable; used for treating out-of-scope variables as expression holes
Either "x", "y" Plain OutOfScope or "_", "_x" A TrueExprHole
Both forms indicate an out-of-scope variable, but the latter indicates that the user expects it to be out of scope, and just wants GHC to report its type
Constructors
| OutOfScope OccName GlobalRdrEnv | An (unqualified) out-of-scope variable, together with the GlobalRdrEnv with respect to which it is unbound |
| TrueExprHole OccName | A "true" expression hole (_ or _x) |
Instances
| Data UnboundVar | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnboundVar -> c UnboundVar # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnboundVar # toConstr :: UnboundVar -> Constr # dataTypeOf :: UnboundVar -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnboundVar) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnboundVar) # gmapT :: (forall b. Data b => b -> b) -> UnboundVar -> UnboundVar # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnboundVar -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnboundVar -> r # gmapQ :: (forall d. Data d => d -> u) -> UnboundVar -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnboundVar -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnboundVar -> m UnboundVar # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnboundVar -> m UnboundVar # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnboundVar -> m UnboundVar # | |
| Outputable UnboundVar | |
Defined in GHC.Hs.Expr | |
data RecordConTc #
Extra data fields for a RecordCon, added by the type checker
Constructors
| RecordConTc | |
Fields | |
data RecordUpdTc #
Extra data fields for a RecordUpd, added by the type checker
Constructors
| RecordUpdTc | |
Fields
| |
Instances
| Data RecordUpdTc | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecordUpdTc -> c RecordUpdTc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecordUpdTc # toConstr :: RecordUpdTc -> Constr # dataTypeOf :: RecordUpdTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecordUpdTc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecordUpdTc) # gmapT :: (forall b. Data b => b -> b) -> RecordUpdTc -> RecordUpdTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordUpdTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordUpdTc -> r # gmapQ :: (forall d. Data d => d -> u) -> RecordUpdTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordUpdTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordUpdTc -> m RecordUpdTc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordUpdTc -> m RecordUpdTc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordUpdTc -> m RecordUpdTc # | |
type LHsTupArg id = Located (HsTupArg id) #
Located Haskell Tuple Argument
HsTupArg is used for tuple sections
(,a,) is represented by
ExplicitTuple [Missing ty1, Present a, Missing ty3]
Which in turn stands for (x:ty1 y:ty2. (x,a,y))
Haskell Tuple Argument
data HsArrAppType #
Haskell Array Application Type
Constructors
| HsHigherOrderApp | |
| HsFirstOrderApp |
Instances
| Data HsArrAppType | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrAppType -> c HsArrAppType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsArrAppType # toConstr :: HsArrAppType -> Constr # dataTypeOf :: HsArrAppType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsArrAppType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsArrAppType) # gmapT :: (forall b. Data b => b -> b) -> HsArrAppType -> HsArrAppType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrAppType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrAppType -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArrAppType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrAppType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrAppType -> m HsArrAppType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrAppType -> m HsArrAppType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrAppType -> m HsArrAppType # | |
type LHsCmdTop p = Located (HsCmdTop p) #
Top-level command, introducing a new arrow. This may occur inside a proc (where the stack is empty) or as an argument of a command-forming operator.
Located Haskell Top-level Command
Haskell Top-level Command
type HsRecordBinds p = HsRecFields p (LHsExpr p) #
Haskell Record Bindings
data MatchGroupTc #
Constructors
| MatchGroupTc | |
Fields
| |
Instances
| Data MatchGroupTc | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroupTc -> c MatchGroupTc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MatchGroupTc # toConstr :: MatchGroupTc -> Constr # dataTypeOf :: MatchGroupTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MatchGroupTc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MatchGroupTc) # gmapT :: (forall b. Data b => b -> b) -> MatchGroupTc -> MatchGroupTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroupTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroupTc -> r # gmapQ :: (forall d. Data d => d -> u) -> MatchGroupTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroupTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroupTc -> m MatchGroupTc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroupTc -> m MatchGroupTc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroupTc -> m MatchGroupTc # | |
type LMatch id body = Located (Match id body) #
Located Match
May have AnnKeywordId : AnnSemi when in a
list
Constructors
| Match | |
Fields
| |
| XMatch (XXMatch p body) | |
Instances
| (OutputableBndrId pr, Outputable body) => Outputable (Match (GhcPass pr) body) | |
Guarded Right Hand Side.
Constructors
| GRHS (XCGRHS p body) [GuardLStmt p] body | |
| XGRHS (XXGRHS p body) |
type LStmtLR idL idR body = Located (StmtLR idL idR body) #
Located Statement with separate Left and Right id's
type GuardLStmt id = LStmt id (LHsExpr id) #
Guard Located Statement
API Annotations when in qualifier lists or guards
- AnnKeywordId : AnnVbar,
AnnComma,AnnThen,
AnnBy,AnnBy,
AnnGroup,AnnUsing
Constructors
| LastStmt (XLastStmt idL idR body) body Bool (SyntaxExpr idR) | |
| BindStmt (XBindStmt idL idR body) (LPat idL) body (SyntaxExpr idR) (SyntaxExpr idR) | |
| ApplicativeStmt (XApplicativeStmt idL idR body) [(SyntaxExpr idR, ApplicativeArg idL)] (Maybe (SyntaxExpr idR)) |
For full details, see Note [ApplicativeDo] in RnExpr |
| BodyStmt (XBodyStmt idL idR body) body (SyntaxExpr idR) (SyntaxExpr idR) | |
| LetStmt (XLetStmt idL idR body) (LHsLocalBindsLR idL idR) |
|
| ParStmt (XParStmt idL idR body) [ParStmtBlock idL idR] (HsExpr idR) (SyntaxExpr idR) | |
| TransStmt | |
| RecStmt | |
Fields
| |
| XStmtLR (XXStmtLR idL idR body) | |
Instances
| (OutputableBndrId pl, OutputableBndrId pr, Outputable body) => Outputable (StmtLR (GhcPass pl) (GhcPass pr) body) | |
Constructors
| RecStmtTc | |
Fields
| |
Instances
| Data TransForm | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransForm -> c TransForm # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransForm # toConstr :: TransForm -> Constr # dataTypeOf :: TransForm -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TransForm) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransForm) # gmapT :: (forall b. Data b => b -> b) -> TransForm -> TransForm # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransForm -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransForm -> r # gmapQ :: (forall d. Data d => d -> u) -> TransForm -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TransForm -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransForm -> m TransForm # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransForm -> m TransForm # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransForm -> m TransForm # | |
data ParStmtBlock idL idR #
Parenthesised Statement Block
Constructors
| ParStmtBlock (XParStmtBlock idL idR) [ExprLStmt idL] [IdP idR] (SyntaxExpr idR) | |
| XParStmtBlock (XXParStmtBlock idL idR) |
Instances
| (Outputable (StmtLR idL idL (LHsExpr idL)), Outputable (XXParStmtBlock idL idR)) => Outputable (ParStmtBlock idL idR) | |
Defined in GHC.Hs.Expr | |
data ApplicativeArg idL #
Applicative Argument
Constructors
| ApplicativeArgOne | |
Fields
| |
| ApplicativeArgMany | |
Fields
| |
| XApplicativeArg (XXApplicativeArg idL) | |
Instances
| OutputableBndrId idL => Outputable (ApplicativeArg (GhcPass idL)) | |
Defined in GHC.Hs.Expr | |
data SpliceDecoration #
A splice can appear with various decorations wrapped around it. This data type captures explicitly how it was originally written, for use in the pretty printer.
Instances
newtype ThModFinalizers #
Finalizers produced by a splice with
addModFinalizer
See Note [Delaying modFinalizers in untyped splices] in RnSplice. For how this is used.
Constructors
| ThModFinalizers [ForeignRef (Q ())] |
Instances
| Data ThModFinalizers | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ThModFinalizers -> c ThModFinalizers # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ThModFinalizers # toConstr :: ThModFinalizers -> Constr # dataTypeOf :: ThModFinalizers -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ThModFinalizers) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThModFinalizers) # gmapT :: (forall b. Data b => b -> b) -> ThModFinalizers -> ThModFinalizers # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ThModFinalizers -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ThModFinalizers -> r # gmapQ :: (forall d. Data d => d -> u) -> ThModFinalizers -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ThModFinalizers -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ThModFinalizers -> m ThModFinalizers # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ThModFinalizers -> m ThModFinalizers # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ThModFinalizers -> m ThModFinalizers # | |
data DelayedSplice #
Instances
| Data DelayedSplice | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DelayedSplice -> c DelayedSplice # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DelayedSplice # toConstr :: DelayedSplice -> Constr # dataTypeOf :: DelayedSplice -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DelayedSplice) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DelayedSplice) # gmapT :: (forall b. Data b => b -> b) -> DelayedSplice -> DelayedSplice # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DelayedSplice -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DelayedSplice -> r # gmapQ :: (forall d. Data d => d -> u) -> DelayedSplice -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DelayedSplice -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DelayedSplice -> m DelayedSplice # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DelayedSplice -> m DelayedSplice # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DelayedSplice -> m DelayedSplice # | |
data HsSplicedThing id #
Haskell Spliced Thing
Values that can result from running a splice.
Constructors
| HsSplicedExpr (HsExpr id) | Haskell Spliced Expression |
| HsSplicedTy (HsType id) | Haskell Spliced Type |
| HsSplicedPat (Pat id) | Haskell Spliced Pattern |
Instances
| OutputableBndrId p => Outputable (HsSplicedThing (GhcPass p)) | |
Defined in GHC.Hs.Expr | |
type SplicePointName = Name #
data PendingRnSplice #
Pending Renamer Splice
Constructors
| PendingRnSplice UntypedSpliceFlavour SplicePointName (LHsExpr GhcRn) |
Instances
| Outputable PendingRnSplice | |
Defined in GHC.Hs.Expr | |
data UntypedSpliceFlavour #
Instances
| Data UntypedSpliceFlavour | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UntypedSpliceFlavour -> c UntypedSpliceFlavour # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UntypedSpliceFlavour # toConstr :: UntypedSpliceFlavour -> Constr # dataTypeOf :: UntypedSpliceFlavour -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UntypedSpliceFlavour) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UntypedSpliceFlavour) # gmapT :: (forall b. Data b => b -> b) -> UntypedSpliceFlavour -> UntypedSpliceFlavour # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UntypedSpliceFlavour -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UntypedSpliceFlavour -> r # gmapQ :: (forall d. Data d => d -> u) -> UntypedSpliceFlavour -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UntypedSpliceFlavour -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UntypedSpliceFlavour -> m UntypedSpliceFlavour # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UntypedSpliceFlavour -> m UntypedSpliceFlavour # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UntypedSpliceFlavour -> m UntypedSpliceFlavour # | |
data PendingTcSplice #
Pending Type-checker Splice
Constructors
| PendingTcSplice SplicePointName (LHsExpr GhcTc) |
Instances
| Outputable PendingTcSplice | |
Defined in GHC.Hs.Expr | |
Haskell Bracket
data ArithSeqInfo id #
Arithmetic Sequence Information
Constructors
| From (LHsExpr id) | |
| FromThen (LHsExpr id) (LHsExpr id) | |
| FromTo (LHsExpr id) (LHsExpr id) | |
| FromThenTo (LHsExpr id) (LHsExpr id) (LHsExpr id) |
Instances
| OutputableBndrId p => Outputable (ArithSeqInfo (GhcPass p)) | |
Defined in GHC.Hs.Expr | |
data HsMatchContext id #
Haskell Match Context
Context of a pattern match. This is more subtle than it would seem. See Note [Varieties of pattern matches].
Constructors
| FunRhs | A pattern matching on an argument of a function binding |
Fields
| |
| LambdaExpr | Patterns of a lambda |
| CaseAlt | Patterns and guards on a case alternative |
| IfAlt | Guards of a multi-way if alternative |
| ProcExpr | Patterns of a proc |
| PatBindRhs | A pattern binding eg [y] <- e = e |
| PatBindGuards | Guards of pattern bindings, e.g., (Just b) | Just _ <- x = e | otherwise = e' |
| RecUpd | Record update [used only in DsExpr to tell matchWrapper what sort of runtime error message to generate] |
| StmtCtxt (HsStmtContext id) | Pattern of a do-stmt, list comprehension, pattern guard, etc |
| ThPatSplice | A Template Haskell pattern splice |
| ThPatQuote | A Template Haskell pattern quotation [p| (a,b) |] |
| PatSyn | A pattern synonym declaration |
Instances
| Functor HsMatchContext | |
Defined in GHC.Hs.Expr Methods fmap :: (a -> b) -> HsMatchContext a -> HsMatchContext b # (<$) :: a -> HsMatchContext b -> HsMatchContext a # | |
| Data id => Data (HsMatchContext id) | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsMatchContext id -> c (HsMatchContext id) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsMatchContext id) # toConstr :: HsMatchContext id -> Constr # dataTypeOf :: HsMatchContext id -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsMatchContext id)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsMatchContext id)) # gmapT :: (forall b. Data b => b -> b) -> HsMatchContext id -> HsMatchContext id # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext id -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext id -> r # gmapQ :: (forall d. Data d => d -> u) -> HsMatchContext id -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsMatchContext id -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsMatchContext id -> m (HsMatchContext id) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext id -> m (HsMatchContext id) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext id -> m (HsMatchContext id) # | |
| OutputableBndr id => Outputable (HsMatchContext id) | |
Defined in GHC.Hs.Expr | |
data HsStmtContext id #
Haskell Statement Context. It expects to be parameterised with one of
RdrName, Name or Id
Constructors
| ListComp | |
| MonadComp | |
| DoExpr | do { ... } |
| MDoExpr | mdo { ... } ie recursive do-expression |
| ArrowExpr | do-notation in an arrow-command context |
| GhciStmtCtxt | A command-line Stmt in GHCi pat <- rhs |
| PatGuard (HsMatchContext id) | Pattern guard for specified thing |
| ParStmtCtxt (HsStmtContext id) | A branch of a parallel stmt |
| TransStmtCtxt (HsStmtContext id) | A branch of a transform stmt |
Instances
| Functor HsStmtContext | |
Defined in GHC.Hs.Expr Methods fmap :: (a -> b) -> HsStmtContext a -> HsStmtContext b # (<$) :: a -> HsStmtContext b -> HsStmtContext a # | |
| Data id => Data (HsStmtContext id) | |
Defined in GHC.Hs.Expr Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsStmtContext id -> c (HsStmtContext id) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsStmtContext id) # toConstr :: HsStmtContext id -> Constr # dataTypeOf :: HsStmtContext id -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsStmtContext id)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsStmtContext id)) # gmapT :: (forall b. Data b => b -> b) -> HsStmtContext id -> HsStmtContext id # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext id -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext id -> r # gmapQ :: (forall d. Data d => d -> u) -> HsStmtContext id -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsStmtContext id -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsStmtContext id -> m (HsStmtContext id) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext id -> m (HsStmtContext id) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext id -> m (HsStmtContext id) # | |
| (Outputable (GhcPass p), Outputable (NameOrRdrName (GhcPass p))) => Outputable (HsStmtContext (GhcPass p)) | |
Defined in GHC.Hs.Expr | |
roleAnnotDeclName :: forall (p :: Pass). RoleAnnotDecl (GhcPass p) -> IdP (GhcPass p) #
annProvenanceName_maybe :: AnnProvenance name -> Maybe name #
docDeclDoc :: DocDecl -> HsDocString #
pprFullRuleName :: Located (SourceText, RuleName) -> SDoc #
collectRuleBndrSigTys :: [RuleBndr pass] -> [LHsSigWcType pass] #
flattenRuleDecls :: [LRuleDecls pass] -> [LRuleDecl pass] #
mapDerivStrategy :: forall p (pass :: Pass). p ~ GhcPass pass => (XViaStrategy p -> XViaStrategy p) -> DerivStrategy p -> DerivStrategy p #
Map over the via type if dealing with ViaStrategy. Otherwise,
return the DerivStrategy unchanged.
foldDerivStrategy :: forall p (pass :: Pass) r. p ~ GhcPass pass => r -> (XViaStrategy p -> r) -> DerivStrategy p -> r #
Eliminate a DerivStrategy.
derivStrategyName :: DerivStrategy a -> SDoc #
A short description of a DerivStrategy'.
instDeclDataFamInsts :: forall (p :: Pass). [LInstDecl (GhcPass p)] -> [DataFamInstDecl (GhcPass p)] #
pprHsFamInstLHS :: forall (p :: Pass). OutputableBndrId p => IdP (GhcPass p) -> Maybe [LHsTyVarBndr (GhcPass p)] -> HsTyPats (GhcPass p) -> LexicalFixity -> LHsContext (GhcPass p) -> SDoc #
pprDataFamInstFlavour :: forall (p :: Pass). DataFamInstDecl (GhcPass p) -> SDoc #
pprTyFamInstDecl :: forall (p :: Pass). OutputableBndrId p => TopLevelFlag -> TyFamInstDecl (GhcPass p) -> SDoc #
hsConDeclTheta :: Maybe (LHsContext pass) -> [LHsType pass] #
hsConDeclArgTys :: HsConDeclDetails pass -> [LBangType pass] #
getConArgs :: ConDecl pass -> HsConDeclDetails pass #
newOrDataToFlavour :: NewOrData -> TyConFlavour #
Convert a NewOrData to a TyConFlavour
standaloneKindSigName :: forall (p :: Pass). StandaloneKindSig (GhcPass p) -> IdP (GhcPass p) #
resultVariableName :: forall (a :: Pass). FamilyResultSig (GhcPass a) -> Maybe (IdP (GhcPass a)) #
Maybe return name of the result type variable
famResultKindSignature :: forall (p :: Pass). FamilyResultSig (GhcPass p) -> Maybe (LHsKind (GhcPass p)) #
familyDeclName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> IdP (GhcPass p) #
familyDeclLName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> Located (IdP (GhcPass p)) #
tyClGroupKindSigs :: [TyClGroup pass] -> [LStandaloneKindSig pass] #
tyClGroupRoleDecls :: [TyClGroup pass] -> [LRoleAnnotDecl pass] #
tyClGroupInstDecls :: [TyClGroup pass] -> [LInstDecl pass] #
tyClGroupTyClDecls :: [TyClGroup pass] -> [LTyClDecl pass] #
hsDeclHasCusk :: TyClDecl GhcRn -> Bool #
Does this declaration have a complete, user-supplied kind signature? See Note [CUSKs: complete user-supplied kind signatures]
tyClDeclTyVars :: TyClDecl pass -> LHsQTyVars pass #
tyFamInstDeclLName :: forall (p :: Pass). TyFamInstDecl (GhcPass p) -> Located (IdP (GhcPass p)) #
tyFamInstDeclName :: forall (p :: Pass). TyFamInstDecl (GhcPass p) -> IdP (GhcPass p) #
isDataFamilyDecl :: TyClDecl pass -> Bool #
data family declaration
isClosedTypeFamilyInfo :: FamilyInfo pass -> Bool #
closed type family info
isOpenTypeFamilyInfo :: FamilyInfo pass -> Bool #
open type family info
isTypeFamilyDecl :: TyClDecl pass -> Bool #
type family declaration
isFamilyDecl :: TyClDecl pass -> Bool #
type/data family declaration
isClassDecl :: TyClDecl pass -> Bool #
type class
isDataDecl :: TyClDecl pass -> Bool #
True = argument is a data/newtype
declaration.
appendGroups :: forall (p :: Pass). HsGroup (GhcPass p) -> HsGroup (GhcPass p) -> HsGroup (GhcPass p) #
hsGroupInstDecls :: HsGroup id -> [LInstDecl id] #
emptyRnGroup :: forall (p :: Pass). HsGroup (GhcPass p) #
emptyRdrGroup :: forall (p :: Pass). HsGroup (GhcPass p) #
A Haskell Declaration
Constructors
| TyClD (XTyClD p) (TyClDecl p) | Type or Class Declaration |
| InstD (XInstD p) (InstDecl p) | Instance declaration |
| DerivD (XDerivD p) (DerivDecl p) | Deriving declaration |
| ValD (XValD p) (HsBind p) | Value declaration |
| SigD (XSigD p) (Sig p) | Signature declaration |
| KindSigD (XKindSigD p) (StandaloneKindSig p) | Standalone kind signature |
| DefD (XDefD p) (DefaultDecl p) | 'default' declaration |
| ForD (XForD p) (ForeignDecl p) | Foreign declaration |
| WarningD (XWarningD p) (WarnDecls p) | Warning declaration |
| AnnD (XAnnD p) (AnnDecl p) | Annotation declaration |
| RuleD (XRuleD p) (RuleDecls p) | Rule declaration |
| SpliceD (XSpliceD p) (SpliceDecl p) | Splice declaration (Includes quasi-quotes) |
| DocD (XDocD p) DocDecl | Documentation comment declaration |
| RoleAnnotD (XRoleAnnotD p) (RoleAnnotDecl p) | Role annotation declaration |
| XHsDecl (XXHsDecl p) |
Constructors
| HsGroup | |
Fields
| |
| XHsGroup (XXHsGroup p) | |
type LSpliceDecl pass = Located (SpliceDecl pass) #
Located Splice Declaration
data SpliceDecl p #
Splice Declaration
Constructors
| SpliceDecl (XSpliceDecl p) (Located (HsSplice p)) SpliceExplicitFlag | |
| XSpliceDecl (XXSpliceDecl p) |
Instances
| OutputableBndrId p => Outputable (SpliceDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
A type or class declaration.
Constructors
| FamDecl | type/data family T :: *->* |
Fields
| |
| SynDecl |
|
| DataDecl |
|
Fields
| |
| ClassDecl | |
Fields
| |
| XTyClDecl (XXTyClDecl pass) | |
data DataDeclRn #
Constructors
| DataDeclRn | |
Fields
| |
Instances
| Data DataDeclRn | |
Defined in GHC.Hs.Decls Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataDeclRn -> c DataDeclRn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataDeclRn # toConstr :: DataDeclRn -> Constr # dataTypeOf :: DataDeclRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataDeclRn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataDeclRn) # gmapT :: (forall b. Data b => b -> b) -> DataDeclRn -> DataDeclRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataDeclRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataDeclRn -> r # gmapQ :: (forall d. Data d => d -> u) -> DataDeclRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataDeclRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataDeclRn -> m DataDeclRn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDeclRn -> m DataDeclRn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDeclRn -> m DataDeclRn # | |
Type or Class Group
Constructors
| TyClGroup | |
Fields
| |
| XTyClGroup (XXTyClGroup pass) | |
type LFamilyResultSig pass = Located (FamilyResultSig pass) #
Located type Family Result Signature
data FamilyResultSig pass #
type Family Result Signature
Constructors
| NoSig (XNoSig pass) | |
| KindSig (XCKindSig pass) (LHsKind pass) | |
| TyVarSig (XTyVarSig pass) (LHsTyVarBndr pass) | |
| XFamilyResultSig (XXFamilyResultSig pass) |
type LFamilyDecl pass = Located (FamilyDecl pass) #
Located type Family Declaration
data FamilyDecl pass #
type Family Declaration
Constructors
| FamilyDecl | |
Fields
| |
| XFamilyDecl (XXFamilyDecl pass) | |
Instances
| OutputableBndrId p => Outputable (FamilyDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
type LInjectivityAnn pass = Located (InjectivityAnn pass) #
Located Injectivity Annotation
data InjectivityAnn pass #
If the user supplied an injectivity annotation it is represented using InjectivityAnn. At the moment this is a single injectivity condition - see Note [Injectivity annotation]. `Located name` stores the LHS of injectivity condition. `[Located name]` stores the RHS of injectivity condition. Example:
type family Foo a b c = r | r -> a c where ...
This will be represented as "InjectivityAnn r [a, c]"
Constructors
| InjectivityAnn (Located (IdP pass)) [Located (IdP pass)] |
data FamilyInfo pass #
Constructors
| DataFamily | |
| OpenTypeFamily | |
| ClosedTypeFamily (Maybe [LTyFamInstEqn pass]) |
|
Instances
| Outputable (FamilyInfo pass) | |
Defined in GHC.Hs.Decls | |
data HsDataDefn pass #
Haskell Data type Definition
Constructors
| HsDataDefn | Declares a data type or newtype, giving its constructors
|
Fields
| |
| XHsDataDefn (XXHsDataDefn pass) | |
Instances
| OutputableBndrId p => Outputable (HsDataDefn (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
type HsDeriving pass #
Arguments
| = Located [LHsDerivingClause pass] | The optional The list of |
Haskell Deriving clause
type LHsDerivingClause pass = Located (HsDerivingClause pass) #
data HsDerivingClause pass #
A single deriving clause of a data declaration.
Constructors
| HsDerivingClause | |
Fields
| |
| XHsDerivingClause (XXHsDerivingClause pass) | |
Instances
| OutputableBndrId p => Outputable (HsDerivingClause (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
type LStandaloneKindSig pass = Located (StandaloneKindSig pass) #
Located Standalone Kind Signature
data StandaloneKindSig pass #
Constructors
| StandaloneKindSig (XStandaloneKindSig pass) (Located (IdP pass)) (LHsSigType pass) | |
| XStandaloneKindSig (XXStandaloneKindSig pass) |
Instances
| OutputableBndrId p => Outputable (StandaloneKindSig (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Instances
| Eq NewOrData | |
| Data NewOrData | |
Defined in GHC.Hs.Decls Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewOrData -> c NewOrData # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewOrData # toConstr :: NewOrData -> Constr # dataTypeOf :: NewOrData -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NewOrData) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewOrData) # gmapT :: (forall b. Data b => b -> b) -> NewOrData -> NewOrData # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewOrData -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewOrData -> r # gmapQ :: (forall d. Data d => d -> u) -> NewOrData -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NewOrData -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewOrData -> m NewOrData # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewOrData -> m NewOrData # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewOrData -> m NewOrData # | |
| Outputable NewOrData | |
Arguments
| = Located (ConDecl pass) | May have |
Located data Constructor Declaration
data T b = forall a. Eq a => MkT a b
MkT :: forall b a. Eq a => MkT a b
data T b where
MkT1 :: Int -> T Int
data T = Int MkT Int
| MkT2
data T a where
Int MkT Int :: T Int
AnnKeywordIds :AnnOpen,AnnDotdot,AnnCLose,AnnEqual,AnnVbar,AnnDarrow,AnnDarrow,AnnForall,AnnDot
data Constructor Declaration
Constructors
| ConDeclGADT | |
Fields
| |
| ConDeclH98 | |
Fields
| |
| XConDecl (XXConDecl pass) | |
type HsConDeclDetails pass = HsConDetails (LBangType pass) (Located [LConDeclField pass]) #
Haskell data Constructor Declaration Details
type LTyFamInstEqn pass #
Arguments
| = Located (TyFamInstEqn pass) | May have |
Located Type Family Instance Equation
type HsTyPats pass = [LHsTypeArg pass] #
Haskell Type Patterns
type TyFamInstEqn pass = FamInstEqn pass (LHsType pass) #
Type Family Instance Equation
type TyFamDefltDecl = TyFamInstDecl #
Type family default declarations.
A convenient synonym for TyFamInstDecl.
See Note [Type family instance declarations in HsSyn].
type LTyFamDefltDecl pass = Located (TyFamDefltDecl pass) #
Located type family default declarations.
type LTyFamInstDecl pass = Located (TyFamInstDecl pass) #
Located Type Family Instance Declaration
newtype TyFamInstDecl pass #
Type Family Instance Declaration
Constructors
| TyFamInstDecl | |
Fields
| |
Instances
| OutputableBndrId p => Outputable (TyFamInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
type LDataFamInstDecl pass = Located (DataFamInstDecl pass) #
Located Data Family Instance Declaration
newtype DataFamInstDecl pass #
Data Family Instance Declaration
Constructors
| DataFamInstDecl | |
Fields
| |
Instances
| OutputableBndrId p => Outputable (DataFamInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
type LFamInstEqn pass rhs = Located (FamInstEqn pass rhs) #
Located Family Instance Equation
type FamInstEqn pass rhs #
Arguments
| = HsImplicitBndrs pass (FamEqn pass rhs) | Here, the |
Family Instance Equation
Family Equation
One equation in a type family instance declaration, data family instance declaration, or type family default. See Note [Type family instance declarations in HsSyn] See Note [Family instance declaration binders]
Constructors
| FamEqn | |
Fields
| |
| XFamEqn (XXFamEqn pass rhs) | |
type LClsInstDecl pass = Located (ClsInstDecl pass) #
Located Class Instance Declaration
data ClsInstDecl pass #
Class Instance Declaration
Constructors
| ClsInstDecl | |
Fields
| |
| XClsInstDecl (XXClsInstDecl pass) | |
Instances
| OutputableBndrId p => Outputable (ClsInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Instance Declaration
Constructors
| ClsInstD | |
Fields
| |
| DataFamInstD | |
Fields
| |
| TyFamInstD | |
Fields
| |
| XInstDecl (XXInstDecl pass) | |
type LDerivDecl pass = Located (DerivDecl pass) #
Located stand-alone 'deriving instance' declaration
Stand-alone 'deriving instance' declaration
Constructors
| DerivDecl | |
Fields
| |
| XDerivDecl (XXDerivDecl pass) | |
type LDerivStrategy pass = Located (DerivStrategy pass) #
data DerivStrategy pass #
Which technique the user explicitly requested when deriving an instance.
Constructors
| StockStrategy | GHC's "standard" strategy, which is to implement a
custom instance for the data type. This only works
for certain types that GHC knows about (e.g., |
| AnyclassStrategy | -XDeriveAnyClass |
| NewtypeStrategy | -XGeneralizedNewtypeDeriving |
| ViaStrategy (XViaStrategy pass) | -XDerivingVia |
Instances
| OutputableBndrId p => Outputable (DerivStrategy (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
type LDefaultDecl pass = Located (DefaultDecl pass) #
Located Default Declaration
data DefaultDecl pass #
Default Declaration
Constructors
| DefaultDecl (XCDefaultDecl pass) [LHsType pass] | |
| XDefaultDecl (XXDefaultDecl pass) |
Instances
| OutputableBndrId p => Outputable (DefaultDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
type LForeignDecl pass = Located (ForeignDecl pass) #
Located Foreign Declaration
data ForeignDecl pass #
Foreign Declaration
Constructors
| ForeignImport | |
Fields
| |
| ForeignExport | |
Fields
| |
| XForeignDecl (XXForeignDecl pass) | |
Instances
| OutputableBndrId p => Outputable (ForeignDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
data ForeignImport #
Constructors
| CImport (Located CCallConv) (Located Safety) (Maybe Header) CImportSpec (Located SourceText) |
Instances
| Data ForeignImport | |
Defined in GHC.Hs.Decls Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignImport -> c ForeignImport # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForeignImport # toConstr :: ForeignImport -> Constr # dataTypeOf :: ForeignImport -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForeignImport) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignImport) # gmapT :: (forall b. Data b => b -> b) -> ForeignImport -> ForeignImport # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignImport -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignImport -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignImport -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignImport -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignImport -> m ForeignImport # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignImport -> m ForeignImport # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignImport -> m ForeignImport # | |
| Outputable ForeignImport | |
Defined in GHC.Hs.Decls | |
data CImportSpec #
Constructors
| CLabel CLabelString | |
| CFunction CCallTarget | |
| CWrapper |
Instances
| Data CImportSpec | |
Defined in GHC.Hs.Decls Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CImportSpec -> c CImportSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CImportSpec # toConstr :: CImportSpec -> Constr # dataTypeOf :: CImportSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CImportSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CImportSpec) # gmapT :: (forall b. Data b => b -> b) -> CImportSpec -> CImportSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CImportSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CImportSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> CImportSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CImportSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CImportSpec -> m CImportSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CImportSpec -> m CImportSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CImportSpec -> m CImportSpec # | |
data ForeignExport #
Constructors
| CExport (Located CExportSpec) (Located SourceText) |
Instances
| Data ForeignExport | |
Defined in GHC.Hs.Decls Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignExport -> c ForeignExport # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForeignExport # toConstr :: ForeignExport -> Constr # dataTypeOf :: ForeignExport -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForeignExport) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignExport) # gmapT :: (forall b. Data b => b -> b) -> ForeignExport -> ForeignExport # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignExport -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignExport -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignExport -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignExport -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignExport -> m ForeignExport # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignExport -> m ForeignExport # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignExport -> m ForeignExport # | |
| Outputable ForeignExport | |
Defined in GHC.Hs.Decls | |
type LRuleDecls pass = Located (RuleDecls pass) #
Located Rule Declarations
Rule Declarations
Constructors
| HsRules | |
Fields
| |
| XRuleDecls (XXRuleDecls pass) | |
Rule Declaration
Constructors
| HsRule | |
Fields
| |
| XRuleDecl (XXRuleDecl pass) | |
Instances
| Data HsRuleRn | |
Defined in GHC.Hs.Decls Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRuleRn -> c HsRuleRn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsRuleRn # toConstr :: HsRuleRn -> Constr # dataTypeOf :: HsRuleRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsRuleRn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsRuleRn) # gmapT :: (forall b. Data b => b -> b) -> HsRuleRn -> HsRuleRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRuleRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRuleRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsRuleRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRuleRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRuleRn -> m HsRuleRn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRuleRn -> m HsRuleRn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRuleRn -> m HsRuleRn # | |
Rule Binder
Constructors
| RuleBndr (XCRuleBndr pass) (Located (IdP pass)) | |
| RuleBndrSig (XRuleBndrSig pass) (Located (IdP pass)) (LHsSigWcType pass) | |
| XRuleBndr (XXRuleBndr pass) |
Documentation comment Declaration
Constructors
| DocCommentNext HsDocString | |
| DocCommentPrev HsDocString | |
| DocCommentNamed String HsDocString | |
| DocGroup Int HsDocString |
Instances
| Data DocDecl | |
Defined in GHC.Hs.Decls Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DocDecl -> c DocDecl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DocDecl # toConstr :: DocDecl -> Constr # dataTypeOf :: DocDecl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DocDecl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DocDecl) # gmapT :: (forall b. Data b => b -> b) -> DocDecl -> DocDecl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DocDecl -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DocDecl -> r # gmapQ :: (forall d. Data d => d -> u) -> DocDecl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DocDecl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DocDecl -> m DocDecl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DocDecl -> m DocDecl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DocDecl -> m DocDecl # | |
| Outputable DocDecl | |
type LWarnDecls pass = Located (WarnDecls pass) #
Located Warning Declarations
Warning pragma Declarations
Constructors
| Warnings | |
Fields
| |
| XWarnDecls (XXWarnDecls pass) | |
Warning pragma Declaration
Constructors
| XWarnDecl (XXWarnDecl pass) |
Annotation Declaration
Constructors
| HsAnnotation (XHsAnnotation pass) SourceText (AnnProvenance (IdP pass)) (Located (HsExpr pass)) | |
| XAnnDecl (XXAnnDecl pass) |
data AnnProvenance name #
Annotation Provenance
Constructors
| ValueAnnProvenance (Located name) | |
| TypeAnnProvenance (Located name) | |
| ModuleAnnProvenance |
Instances
| Functor AnnProvenance | |
Defined in GHC.Hs.Decls Methods fmap :: (a -> b) -> AnnProvenance a -> AnnProvenance b # (<$) :: a -> AnnProvenance b -> AnnProvenance a # | |
| Foldable AnnProvenance | |
Defined in GHC.Hs.Decls Methods fold :: Monoid m => AnnProvenance m -> m # foldMap :: Monoid m => (a -> m) -> AnnProvenance a -> m # foldMap' :: Monoid m => (a -> m) -> AnnProvenance a -> m # foldr :: (a -> b -> b) -> b -> AnnProvenance a -> b # foldr' :: (a -> b -> b) -> b -> AnnProvenance a -> b # foldl :: (b -> a -> b) -> b -> AnnProvenance a -> b # foldl' :: (b -> a -> b) -> b -> AnnProvenance a -> b # foldr1 :: (a -> a -> a) -> AnnProvenance a -> a # foldl1 :: (a -> a -> a) -> AnnProvenance a -> a # toList :: AnnProvenance a -> [a] # null :: AnnProvenance a -> Bool # length :: AnnProvenance a -> Int # elem :: Eq a => a -> AnnProvenance a -> Bool # maximum :: Ord a => AnnProvenance a -> a # minimum :: Ord a => AnnProvenance a -> a # sum :: Num a => AnnProvenance a -> a # product :: Num a => AnnProvenance a -> a # | |
| Traversable AnnProvenance | |
Defined in GHC.Hs.Decls Methods traverse :: Applicative f => (a -> f b) -> AnnProvenance a -> f (AnnProvenance b) # sequenceA :: Applicative f => AnnProvenance (f a) -> f (AnnProvenance a) # mapM :: Monad m => (a -> m b) -> AnnProvenance a -> m (AnnProvenance b) # sequence :: Monad m => AnnProvenance (m a) -> m (AnnProvenance a) # | |
| Data pass => Data (AnnProvenance pass) | |
Defined in GHC.Hs.Decls Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnProvenance pass -> c (AnnProvenance pass) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnProvenance pass) # toConstr :: AnnProvenance pass -> Constr # dataTypeOf :: AnnProvenance pass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnProvenance pass)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnProvenance pass)) # gmapT :: (forall b. Data b => b -> b) -> AnnProvenance pass -> AnnProvenance pass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance pass -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance pass -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnProvenance pass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnProvenance pass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnProvenance pass -> m (AnnProvenance pass) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance pass -> m (AnnProvenance pass) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance pass -> m (AnnProvenance pass) # | |
type LRoleAnnotDecl pass = Located (RoleAnnotDecl pass) #
Located Role Annotation Declaration
data RoleAnnotDecl pass #
Role Annotation Declaration
Constructors
| RoleAnnotDecl (XCRoleAnnotDecl pass) (Located (IdP pass)) [Located (Maybe Role)] | |
| XRoleAnnotDecl (XXRoleAnnotDecl pass) |
Instances
| OutputableBndr (IdP (GhcPass p)) => Outputable (RoleAnnotDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
parenthesizePat :: forall (p :: Pass). PprPrec -> LPat (GhcPass p) -> LPat (GhcPass p) #
checks if parenthesizePat p pat is true, and
if so, surrounds patNeedsParens p patpat with a ParPat. Otherwise, it simply returns pat.
patNeedsParens :: PprPrec -> Pat p -> Bool #
returns patNeedsParens p patTrue if the pattern pat needs
parentheses under precedence p.
isIrrefutableHsPat :: forall (p :: Pass). OutputableBndrId p => LPat (GhcPass p) -> Bool #
mkCharLitPat :: forall (p :: Pass). SourceText -> Char -> OutPat (GhcPass p) #
mkPrefixConPat :: forall (p :: Pass). DataCon -> [OutPat (GhcPass p)] -> [Type] -> OutPat (GhcPass p) #
pprConArgs :: forall (p :: Pass). OutputableBndrId p => HsConPatDetails (GhcPass p) -> SDoc #
pprParendLPat :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LPat (GhcPass p) -> SDoc #
hsRecUpdFieldOcc :: HsRecField' (AmbiguousFieldOcc GhcTc) arg -> LFieldOcc GhcTc #
hsRecUpdFieldId :: HsRecField' (AmbiguousFieldOcc GhcTc) arg -> Located Id #
hsRecUpdFieldRdr :: forall (p :: Pass). HsRecUpdField (GhcPass p) -> Located RdrName #
hsRecFieldId :: HsRecField GhcTc arg -> Located Id #
hsRecFieldSel :: HsRecField pass arg -> Located (XCFieldOcc pass) #
hsRecFieldsArgs :: HsRecFields p arg -> [arg] #
hsRecFields :: HsRecFields p arg -> [XCFieldOcc p] #
hsConPatArgs :: HsConPatDetails p -> [LPat p] #
type HsConPatDetails p = HsConDetails (LPat p) (HsRecFields p (LPat p)) #
Haskell Constructor Pattern Details
data HsRecFields p arg #
Haskell Record Fields
HsRecFields is used only for patterns and expressions (not data type declarations)
Constructors
| HsRecFields | |
Fields
| |
Instances
| Functor (HsRecFields p) | |
Defined in GHC.Hs.Pat Methods fmap :: (a -> b) -> HsRecFields p a -> HsRecFields p b # (<$) :: a -> HsRecFields p b -> HsRecFields p a # | |
| Foldable (HsRecFields p) | |
Defined in GHC.Hs.Pat Methods fold :: Monoid m => HsRecFields p m -> m # foldMap :: Monoid m => (a -> m) -> HsRecFields p a -> m # foldMap' :: Monoid m => (a -> m) -> HsRecFields p a -> m # foldr :: (a -> b -> b) -> b -> HsRecFields p a -> b # foldr' :: (a -> b -> b) -> b -> HsRecFields p a -> b # foldl :: (b -> a -> b) -> b -> HsRecFields p a -> b # foldl' :: (b -> a -> b) -> b -> HsRecFields p a -> b # foldr1 :: (a -> a -> a) -> HsRecFields p a -> a # foldl1 :: (a -> a -> a) -> HsRecFields p a -> a # toList :: HsRecFields p a -> [a] # null :: HsRecFields p a -> Bool # length :: HsRecFields p a -> Int # elem :: Eq a => a -> HsRecFields p a -> Bool # maximum :: Ord a => HsRecFields p a -> a # minimum :: Ord a => HsRecFields p a -> a # sum :: Num a => HsRecFields p a -> a # product :: Num a => HsRecFields p a -> a # | |
| Traversable (HsRecFields p) | |
Defined in GHC.Hs.Pat Methods traverse :: Applicative f => (a -> f b) -> HsRecFields p a -> f (HsRecFields p b) # sequenceA :: Applicative f => HsRecFields p (f a) -> f (HsRecFields p a) # mapM :: Monad m => (a -> m b) -> HsRecFields p a -> m (HsRecFields p b) # sequence :: Monad m => HsRecFields p (m a) -> m (HsRecFields p a) # | |
| Outputable arg => Outputable (HsRecFields p arg) | |
Defined in GHC.Hs.Pat | |
type LHsRecField' p arg = Located (HsRecField' p arg) #
Located Haskell Record Field
type LHsRecField p arg = Located (HsRecField p arg) #
Located Haskell Record Field
type LHsRecUpdField p = Located (HsRecUpdField p) #
Located Haskell Record Update Field
type HsRecField p arg = HsRecField' (FieldOcc p) arg #
Haskell Record Field
type HsRecUpdField p = HsRecField' (AmbiguousFieldOcc p) (LHsExpr p) #
Haskell Record Update Field
data HsRecField' id arg #
Haskell Record Field
For details on above see note [Api annotations] in ApiAnnotation
Constructors
| HsRecField | |
Fields
| |
Instances
| Functor (HsRecField' id) | |
Defined in GHC.Hs.Pat Methods fmap :: (a -> b) -> HsRecField' id a -> HsRecField' id b # (<$) :: a -> HsRecField' id b -> HsRecField' id a # | |
| Foldable (HsRecField' id) | |
Defined in GHC.Hs.Pat Methods fold :: Monoid m => HsRecField' id m -> m # foldMap :: Monoid m => (a -> m) -> HsRecField' id a -> m # foldMap' :: Monoid m => (a -> m) -> HsRecField' id a -> m # foldr :: (a -> b -> b) -> b -> HsRecField' id a -> b # foldr' :: (a -> b -> b) -> b -> HsRecField' id a -> b # foldl :: (b -> a -> b) -> b -> HsRecField' id a -> b # foldl' :: (b -> a -> b) -> b -> HsRecField' id a -> b # foldr1 :: (a -> a -> a) -> HsRecField' id a -> a # foldl1 :: (a -> a -> a) -> HsRecField' id a -> a # toList :: HsRecField' id a -> [a] # null :: HsRecField' id a -> Bool # length :: HsRecField' id a -> Int # elem :: Eq a => a -> HsRecField' id a -> Bool # maximum :: Ord a => HsRecField' id a -> a # minimum :: Ord a => HsRecField' id a -> a # sum :: Num a => HsRecField' id a -> a # product :: Num a => HsRecField' id a -> a # | |
| Traversable (HsRecField' id) | |
Defined in GHC.Hs.Pat Methods traverse :: Applicative f => (a -> f b) -> HsRecField' id a -> f (HsRecField' id b) # sequenceA :: Applicative f => HsRecField' id (f a) -> f (HsRecField' id a) # mapM :: Monad m => (a -> m b) -> HsRecField' id a -> m (HsRecField' id b) # sequence :: Monad m => HsRecField' id (m a) -> m (HsRecField' id a) # | |
| (Data id, Data arg) => Data (HsRecField' id arg) | |
Defined in GHC.Hs.Pat Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecField' id arg -> c (HsRecField' id arg) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecField' id arg) # toConstr :: HsRecField' id arg -> Constr # dataTypeOf :: HsRecField' id arg -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecField' id arg)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecField' id arg)) # gmapT :: (forall b. Data b => b -> b) -> HsRecField' id arg -> HsRecField' id arg # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecField' id arg -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecField' id arg -> r # gmapQ :: (forall d. Data d => d -> u) -> HsRecField' id arg -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecField' id arg -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecField' id arg -> m (HsRecField' id arg) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecField' id arg -> m (HsRecField' id arg) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecField' id arg -> m (HsRecField' id arg) # | |
| (Outputable p, Outputable arg) => Outputable (HsRecField' p arg) | |
Defined in GHC.Hs.Pat | |
pprMinimalSig :: OutputableBndr name => LBooleanFormula (Located name) -> SDoc #
pprTcSpecPrags :: TcSpecPrags -> SDoc #
pprSpec :: OutputableBndr id => id -> SDoc -> InlinePragma -> SDoc #
pprVarSig :: OutputableBndr id => [id] -> SDoc -> SDoc #
pragSrcBrackets :: SourceText -> String -> SDoc -> SDoc #
Using SourceText in case the pragma was spelled differently or used mixed case
pragBrackets :: SDoc -> SDoc #
isCompleteMatchSig :: LSig name -> Bool #
isSCCFunSig :: LSig name -> Bool #
isMinimalLSig :: LSig name -> Bool #
isInlineLSig :: LSig name -> Bool #
isPragLSig :: LSig name -> Bool #
isSpecInstLSig :: LSig name -> Bool #
isSpecLSig :: LSig name -> Bool #
isTypeLSig :: LSig name -> Bool #
isFixityLSig :: LSig name -> Bool #
isDefaultMethod :: TcSpecPrags -> Bool #
hasSpecPrags :: TcSpecPrags -> Bool #
isEmptyIPBindsTc :: HsIPBinds GhcTc -> Bool #
ppr_monobind :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsBindLR (GhcPass idL) (GhcPass idR) -> SDoc #
plusHsValBinds :: forall (a :: Pass). HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) #
isEmptyLHsBinds :: LHsBindsLR idL idR -> Bool #
emptyLHsBinds :: LHsBindsLR idL idR #
emptyValBindsOut :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) #
emptyValBindsIn :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) #
isEmptyValBinds :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) -> Bool #
eqEmptyLocalBinds :: HsLocalBindsLR a b -> Bool #
isEmptyLocalBindsPR :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b) -> Bool #
isEmptyLocalBindsTc :: forall (a :: Pass). HsLocalBindsLR (GhcPass a) GhcTc -> Bool #
emptyLocalBinds :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b) #
pprDeclList :: [SDoc] -> SDoc #
pprLHsBindsForUser :: forall (idL :: Pass) (idR :: Pass) (id2 :: Pass). (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId id2) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> [LSig (GhcPass id2)] -> [SDoc] #
pprLHsBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> SDoc #
type HsLocalBinds id = HsLocalBindsLR id id #
Haskell Local Bindings
type LHsLocalBinds id = Located (HsLocalBinds id) #
Located Haskell local bindings
data HsLocalBindsLR idL idR #
Haskell Local Bindings with separate Left and Right identifier types
Bindings in a 'let' expression or a 'where' clause
Constructors
| HsValBinds (XHsValBinds idL idR) (HsValBindsLR idL idR) | Haskell Value Bindings |
| HsIPBinds (XHsIPBinds idL idR) (HsIPBinds idR) | Haskell Implicit Parameter Bindings |
| EmptyLocalBinds (XEmptyLocalBinds idL idR) | Empty Local Bindings |
| XHsLocalBindsLR (XXHsLocalBindsLR idL idR) |
Instances
| (OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsLocalBindsLR (GhcPass pl) (GhcPass pr)) | |
Defined in GHC.Hs.Binds | |
type LHsLocalBindsLR idL idR = Located (HsLocalBindsLR idL idR) #
type HsValBinds id = HsValBindsLR id id #
Haskell Value Bindings
data HsValBindsLR idL idR #
Haskell Value bindings with separate Left and Right identifier types (not implicit parameters) Used for both top level and nested bindings May contain pattern synonym bindings
Constructors
| ValBinds (XValBinds idL idR) (LHsBindsLR idL idR) [LSig idR] | Value Bindings In Before renaming RHS; idR is always RdrName Not dependency analysed Recursive by default |
| XValBindsLR (XXValBindsLR idL idR) | Value Bindings Out After renaming RHS; idR can be Name or Id Dependency analysed, later bindings in the list may depend on earlier ones. |
Instances
| (OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsValBindsLR (GhcPass pl) (GhcPass pr)) | |
Defined in GHC.Hs.Binds | |
type LHsBinds id = LHsBindsLR id id #
Located Haskell Bindings
type LHsBindsLR idL idR = Bag (LHsBindLR idL idR) #
Located Haskell Bindings with separate Left and Right identifier types
type LHsBindLR idL idR = Located (HsBindLR idL idR) #
Located Haskell Binding with separate Left and Right identifier types
Haskell Binding with separate Left and Right id's
Constructors
| FunBind | Function-like Binding FunBind is used for both functions Reason 1: Special case for type inference: see Reason 2: Instance decls can only have FunBinds, which is convenient. If you change this, you'll need to change e.g. rnMethodBinds But note that the form Strict bindings have their strictness recorded in the |
Fields
| |
| PatBind | Pattern Binding The pattern is never a simple variable; That case is done by FunBind. See Note [FunBind vs PatBind] for details about the relationship between FunBind and PatBind. |
| VarBind | Variable Binding Dictionary binding and suchlike. All VarBinds are introduced by the type checker |
| AbsBinds | Abstraction Bindings |
Fields
| |
| PatSynBind (XPatSynBind idL idR) (PatSynBind idL idR) |
|
| XHsBindsLR (XXHsBindsLR idL idR) | |
Instances
| (OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsBindLR (GhcPass pl) (GhcPass pr)) | |
data NPatBindTc #
Constructors
| NPatBindTc | |
Fields
| |
Instances
| Data NPatBindTc | |
Defined in GHC.Hs.Binds Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NPatBindTc -> c NPatBindTc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NPatBindTc # toConstr :: NPatBindTc -> Constr # dataTypeOf :: NPatBindTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NPatBindTc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NPatBindTc) # gmapT :: (forall b. Data b => b -> b) -> NPatBindTc -> NPatBindTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NPatBindTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NPatBindTc -> r # gmapQ :: (forall d. Data d => d -> u) -> NPatBindTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NPatBindTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NPatBindTc -> m NPatBindTc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NPatBindTc -> m NPatBindTc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NPatBindTc -> m NPatBindTc # | |
Abtraction Bindings Export
Constructors
| ABE | |
| XABExport (XXABExport p) | |
data PatSynBind idL idR #
AnnKeywordId:AnnPattern,AnnEqual,AnnLarrowAnnWhere,AnnOpen'{',AnnClose'}',
Pattern Synonym binding
Constructors
| PSB | |
| XPatSynBind (XXPatSynBind idL idR) | |
Instances
| (OutputableBndrId l, OutputableBndrId r, Outputable (XXPatSynBind (GhcPass l) (GhcPass r))) => Outputable (PatSynBind (GhcPass l) (GhcPass r)) | |
Defined in GHC.Hs.Binds | |
Haskell Implicit Parameter Bindings
Constructors
| IPBinds (XIPBinds id) [LIPBind id] | |
| XHsIPBinds (XXHsIPBinds id) |
type LIPBind id = Located (IPBind id) #
Located Implicit Parameter Binding
May have AnnKeywordId : AnnSemi when in a
list
Implicit parameter bindings.
These bindings start off as (Left "x") in the parser and stay that way until after type-checking when they are replaced with (Right d), where "d" is the name of the dictionary holding the evidence for the implicit parameter.
Signatures and pragmas
Constructors
| TypeSig (XTypeSig pass) [Located (IdP pass)] (LHsSigWcType pass) | An ordinary type signature f :: Num a => a -> a After renaming, this list of Names contains the named
wildcards brought into scope by this signature. For a signature
|
| PatSynSig (XPatSynSig pass) [Located (IdP pass)] (LHsSigType pass) | A pattern synonym type signature pattern Single :: () => (Show a) => a -> [a] |
| ClassOpSig (XClassOpSig pass) Bool [Located (IdP pass)] (LHsSigType pass) | A signature for a class method False: ordinary class-method signature True: generic-default class method signature e.g. class C a where op :: a -> a -- Ordinary default op :: Eq a => a -> a -- Generic default No wildcards allowed here |
| IdSig (XIdSig pass) Id | A type signature in generated code, notably the code generated for record selectors. We simply record the desired Id itself, replete with its name, type and IdDetails. Otherwise it's just like a type signature: there should be an accompanying binding |
| FixSig (XFixSig pass) (FixitySig pass) | An ordinary fixity declaration infixl 8 *** |
| InlineSig (XInlineSig pass) (Located (IdP pass)) InlinePragma | An inline pragma {#- INLINE f #-} |
| SpecSig (XSpecSig pass) (Located (IdP pass)) [LHsSigType pass] InlinePragma | A specialisation pragma {-# SPECIALISE f :: Int -> Int #-} |
| SpecInstSig (XSpecInstSig pass) SourceText (LHsSigType pass) | A specialisation pragma for instance declarations only {-# SPECIALISE instance Eq [Int] #-}(Class tys); should be a specialisation of the current instance declaration |
| MinimalSig (XMinimalSig pass) SourceText (LBooleanFormula (Located (IdP pass))) | A minimal complete definition pragma {-# MINIMAL a | (b, c | (d | e)) #-} |
| SCCFunSig (XSCCFunSig pass) SourceText (Located (IdP pass)) (Maybe (Located StringLiteral)) | A "set cost centre" pragma for declarations {-# SCC funName #-}or {-# SCC funName "cost_centre_name" #-} |
| CompleteMatchSig (XCompleteMatchSig pass) SourceText (Located [Located (IdP pass)]) (Maybe (Located (IdP pass))) | A complete match pragma {-# COMPLETE C, D [:: T] #-}Used to inform the pattern match checker about additional complete matchings which, for example, arise from pattern synonym definitions. |
| XSig (XXSig pass) |
type LFixitySig pass = Located (FixitySig pass) #
Located Fixity Signature
Fixity Signature
Constructors
| FixitySig (XFixitySig pass) [Located (IdP pass)] Fixity | |
| XFixitySig (XXFixitySig pass) |
data TcSpecPrags #
Type checker Specialisation Pragmas
TcSpecPrags conveys SPECIALISE pragmas from the type checker to the desugarer
Constructors
| IsDefaultMethod | Super-specialised: a default method should be macro-expanded at every call site |
| SpecPrags [LTcSpecPrag] |
Instances
| Data TcSpecPrags | |
Defined in GHC.Hs.Binds Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcSpecPrags -> c TcSpecPrags # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcSpecPrags # toConstr :: TcSpecPrags -> Constr # dataTypeOf :: TcSpecPrags -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcSpecPrags) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcSpecPrags) # gmapT :: (forall b. Data b => b -> b) -> TcSpecPrags -> TcSpecPrags # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrags -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrags -> r # gmapQ :: (forall d. Data d => d -> u) -> TcSpecPrags -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TcSpecPrags -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags # | |
type LTcSpecPrag = Located TcSpecPrag #
Located Type checker Specification Pragmas
data TcSpecPrag #
Type checker Specification Pragma
Constructors
| SpecPrag Id HsWrapper InlinePragma | The Id to be specialised, a wrapper that specialises the polymorphic function, and inlining spec for the specialised function |
Instances
| Data TcSpecPrag | |
Defined in GHC.Hs.Binds Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcSpecPrag -> c TcSpecPrag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcSpecPrag # toConstr :: TcSpecPrag -> Constr # dataTypeOf :: TcSpecPrag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcSpecPrag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcSpecPrag) # gmapT :: (forall b. Data b => b -> b) -> TcSpecPrag -> TcSpecPrag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrag -> r # gmapQ :: (forall d. Data d => d -> u) -> TcSpecPrag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TcSpecPrag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag # | |
| Outputable TcSpecPrag | |
Defined in GHC.Hs.Binds | |
type HsPatSynDetails arg = HsConDetails arg [RecordPatSynField arg] #
Haskell Pattern Synonym Details
data RecordPatSynField a #
Record Pattern Synonym Field
Constructors
| RecordPatSynField | |
Fields
| |
Instances
data HsPatSynDir id #
Haskell Pattern Synonym Direction
Constructors
| Unidirectional | |
| ImplicitBidirectional | |
| ExplicitBidirectional (MatchGroup id (LHsExpr id)) |
instanceBindFun :: TyCoVar -> BindFlag #
lookupInstEnv :: Bool -> InstEnvs -> Class -> [Type] -> ClsInstLookupResult #
See Note [Rules for instance lookup] ^ See Note [Safe Haskell Overlapping Instances] in TcSimplify ^ See Note [Safe Haskell Overlapping Instances Implementation] in TcSimplify
lookupUniqueInstEnv :: InstEnvs -> Class -> [Type] -> Either MsgDoc (ClsInst, [Type]) #
Look up an instance in the given instance environment. The given class application must match exactly one instance and the match may not contain any flexi type variables. If the lookup is unsuccessful, yield 'Left errorMessage'.
identicalClsInstHead :: ClsInst -> ClsInst -> Bool #
True when when the instance heads are the same e.g. both are Eq [(a,b)] Used for overriding in GHCi Obviously should be insenstive to alpha-renaming
deleteDFunFromInstEnv :: InstEnv -> DFunId -> InstEnv #
deleteFromInstEnv :: InstEnv -> ClsInst -> InstEnv #
extendInstEnv :: InstEnv -> ClsInst -> InstEnv #
extendInstEnvList :: InstEnv -> [ClsInst] -> InstEnv #
memberInstEnv :: InstEnv -> ClsInst -> Bool #
Checks for an exact match of ClsInst in the instance environment. We use this when we do signature checking in TcRnDriver
classInstances :: InstEnvs -> Class -> [ClsInst] #
instIsVisible :: VisibleOrphanModules -> ClsInst -> Bool #
Test if an instance is visible, by checking that its origin module
is in VisibleOrphanModules.
See Note [Instance lookup and orphan instances]
instEnvClasses :: InstEnv -> [Class] #
instEnvElts :: InstEnv -> [ClsInst] #
emptyInstEnv :: InstEnv #
mkLocalInstance :: DFunId -> OverlapFlag -> [TyVar] -> Class -> [Type] -> ClsInst #
orphNamesOfClsInst :: ClsInst -> NameSet #
Collects the names of concrete types and type constructors that make up the head of a class instance. For instance, given `class Foo a b`:
`instance Foo (Either (Maybe Int) a) Bool` would yield [Either, Maybe, Int, Bool]
Used in the implementation of ":info" in GHCi.
The tcSplitSigmaTy is because of
instance Foo a => Baz T where ...
The decl is an orphan if Baz and T are both not locally defined,
even if Foo *is* locally defined
pprInstances :: [ClsInst] -> SDoc #
pprInstanceHdr :: ClsInst -> SDoc #
pprInstance :: ClsInst -> SDoc #
instanceRoughTcs :: ClsInst -> [Maybe Name] #
instanceDFunId :: ClsInst -> DFunId #
isIncoherent :: ClsInst -> Bool #
isOverlapping :: ClsInst -> Bool #
isOverlappable :: ClsInst -> Bool #
fuzzyClsInstCmp :: ClsInst -> ClsInst -> Ordering #
A fuzzy comparison function for class instances, intended for sorting instances before displaying them to the user.
A type-class instance. Note that there is some tricky laziness at work here. See Note [ClsInst laziness and the rough-match fields] for more details.
Constructors
| ClsInst | |
Fields
| |
Instances
| Data ClsInst | |
Defined in InstEnv Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInst -> c ClsInst # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClsInst # toConstr :: ClsInst -> Constr # dataTypeOf :: ClsInst -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClsInst) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClsInst) # gmapT :: (forall b. Data b => b -> b) -> ClsInst -> ClsInst # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r # gmapQ :: (forall d. Data d => d -> u) -> ClsInst -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInst -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # | |
| NamedThing ClsInst | |
| Outputable ClsInst | |
InstEnvs represents the combination of the global type class instance
environment, the local type class instance environment, and the set of
transitively reachable orphan modules (according to what modules have been
directly imported) used to test orphan instance visibility.
Constructors
| InstEnvs | |
Fields | |
type VisibleOrphanModules = ModuleSet #
Set of visible orphan modules, according to what modules have been directly imported. This is based off of the dep_orphs field, which records transitively reachable orphan modules (modules that define orphan instances).
type DFunInstType = Maybe Type #
type InstMatch = (ClsInst, [DFunInstType]) #
type ClsInstLookupResult = ([InstMatch], [ClsInst], [InstMatch]) #
Instances
| NamedThing FamInst | |
Defined in FamInstEnv | |
| Outputable FamInst | |
Information we can use to dynamically link modules into the compiler
Constructors
| LM | |
Fields
| |
Objects which have yet to be linked by the compiler
Constructors
| DotO FilePath | An object file (.o) |
| DotA FilePath | Static archive file (.a) |
| DotDLL FilePath | Dynamically linked library file (.so, .dll, .dylib) |
| BCOs CompiledByteCode [SptEntry] | A byte-code object, lives only in memory. Also carries some static pointer table entries which should be loaded along with the BCOs. See Note [Grant plan for static forms] in StaticPtrTable. |
An entry to be inserted into a module's static pointer table. See Note [Grand plan for static forms] in StaticPtrTable.
Constructors
| SptEntry Id Fingerprint |
Construct an empty ModBreaks
data CompiledByteCode #
Instances
| Outputable CompiledByteCode | |
Defined in ByteCodeTypes | |
type BreakIndex = Int #
Breakpoint index
All the information about the breakpoints for a module
Constructors
| ModBreaks | |
Fields
| |
parenthesizeHsContext :: forall (p :: Pass). PprPrec -> LHsContext (GhcPass p) -> LHsContext (GhcPass p) #
checks if parenthesizeHsContext p ctxtctxt is a single constraint
c such that is true, and if so, surrounds hsTypeNeedsParens p cc
with an HsParTy to form a parenthesized ctxt. Otherwise, it simply
returns ctxt unchanged.
parenthesizeHsType :: forall (p :: Pass). PprPrec -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
checks if parenthesizeHsType p ty is
true, and if so, surrounds hsTypeNeedsParens p tyty with an HsParTy. Otherwise, it simply
returns ty.
hsTypeNeedsParens :: PprPrec -> HsType pass -> Bool #
returns hsTypeNeedsParens p tTrue if the type t needs parentheses
under precedence p.
pprConDeclFields :: forall (p :: Pass). OutputableBndrId p => [LConDeclField (GhcPass p)] -> SDoc #
pprLHsContext :: forall (p :: Pass). OutputableBndrId p => LHsContext (GhcPass p) -> SDoc #
pprHsExplicitForAll :: forall (p :: Pass). OutputableBndrId p => ForallVisFlag -> Maybe [LHsTyVarBndr (GhcPass p)] -> SDoc #
Version of pprHsForAll or pprHsForAllExtra that will always print
forall. when passed Just []. Prints nothing if passed Nothing
pprHsForAllExtra :: forall (p :: Pass). OutputableBndrId p => Maybe SrcSpan -> ForallVisFlag -> [LHsTyVarBndr (GhcPass p)] -> LHsContext (GhcPass p) -> SDoc #
Version of pprHsForAll that can also print an extra-constraints
wildcard, e.g. _ => a -> Bool or (Show a, _) => a -> String. This
underscore will be printed when the 'Maybe SrcSpan' argument is a Just
containing the location of the extra-constraints wildcard. A special
function for this is needed, as the extra-constraints wildcard is removed
from the actual context and type, and stored in a separate field, thus just
printing the type will not print the extra-constraints wildcard.
pprHsForAll :: forall (p :: Pass). OutputableBndrId p => ForallVisFlag -> [LHsTyVarBndr (GhcPass p)] -> LHsContext (GhcPass p) -> SDoc #
Prints a forall; When passed an empty list, prints forall ./forall ->
only when -dppr-debug is enabled.
pprAnonWildCard :: SDoc #
rdrNameAmbiguousFieldOcc :: forall (p :: Pass). AmbiguousFieldOcc (GhcPass p) -> RdrName #
getLHsInstDeclClass_maybe :: forall (p :: Pass). LHsSigType (GhcPass p) -> Maybe (Located (IdP (GhcPass p))) #
getLHsInstDeclHead :: forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p) #
splitLHsInstDeclTy :: LHsSigType GhcRn -> ([Name], LHsContext GhcRn, LHsType GhcRn) #
Decompose a type class instance type (of the form
forall tvs. context => instance_head) into its constituent parts.
Note that this function looks through parentheses, so it will work on types
such as (forall tvs. ...). The downside to this is that it is not
generally possible to take the returned types and reconstruct the original
type (parentheses and all) from them.
splitLHsQualTy :: LHsType pass -> (LHsContext pass, LHsType pass) #
Decompose a type of the form context => body into its constituent parts.
Note that this function looks through parentheses, so it will work on types
such as (context => ...). The downside to this is that it is not
generally possible to take the returned types and reconstruct the original
type (parentheses and all) from them.
splitLHsForAllTyInvis :: LHsType pass -> ([LHsTyVarBndr pass], LHsType pass) #
Decompose a type of the form forall tvs. body into its constituent
parts. Note that only invisible foralls
(i.e., forall a., with a dot) are split apart; visible foralls
(i.e., forall a ->, with an arrow) are left untouched.
This function is used to split apart certain types, such as instance
declaration types, which disallow visible foralls. For instance, if GHC
split apart the forall in instance forall a -> Show (Blah a), then that
declaration would mistakenly be accepted!
Note that this function looks through parentheses, so it will work on types
such as (forall a. ...). The downside to this is that it is not
generally possible to take the returned types and reconstruct the original
type (parentheses and all) from them.
splitLHsSigmaTyInvis :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, LHsType pass) #
Decompose a sigma type (of the form forall tvs. context => body)
into its constituent parts. Note that only invisible foralls
(i.e., forall a., with a dot) are split apart; visible foralls
(i.e., forall a ->, with an arrow) are left untouched.
This function is used to split apart certain types, such as instance
declaration types, which disallow visible foralls. For instance, if GHC
split apart the forall in instance forall a -> Show (Blah a), then that
declaration would mistakenly be accepted!
Note that this function looks through parentheses, so it will work on types
such as (forall a. ...). The downside to this is that it is not
generally possible to take the returned types and reconstruct the original
type (parentheses and all) from them.
splitLHsPatSynTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, [LHsTyVarBndr pass], LHsContext pass, LHsType pass) #
Decompose a pattern synonym type signature into its constituent parts.
Note that this function looks through parentheses, so it will work on types
such as (forall a. ...). The downside to this is that it is not
generally possible to take the returned types and reconstruct the original
type (parentheses and all) from them.
numVisibleArgs :: [HsArg tm ty] -> Arity #
hsTyGetAppHead_maybe :: forall (p :: Pass). LHsType (GhcPass p) -> Maybe (Located (IdP (GhcPass p))) #
mkHsAppKindTy :: forall (p :: Pass). XAppKindTy (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
mkHsAppTys :: forall (p :: Pass). LHsType (GhcPass p) -> [LHsType (GhcPass p)] -> LHsType (GhcPass p) #
mkHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
mkHsOpTy :: forall (p :: Pass). LHsType (GhcPass p) -> Located (IdP (GhcPass p)) -> LHsType (GhcPass p) -> HsType (GhcPass p) #
isLHsForAllTy :: LHsType p -> Bool #
ignoreParens :: LHsType pass -> LHsType pass #
hsTyKindSig :: LHsType pass -> Maybe (LHsKind pass) #
Get the kind signature of a type, ignoring parentheses:
hsTyKindSig `Maybe ` = Nothing hsTyKindSig `Maybe :: Type -> Type ` = Just `Type -> Type` hsTyKindSig `Maybe :: ((Type -> Type))` = Just `Type -> Type`
This is used to extract the result kind of type synonyms with a CUSK:
type S = (F :: res_kind) ^^^^^^^^
hsLTyVarBndrsToTypes :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [LHsType (GhcPass p)] #
Convert a LHsTyVarBndrs to a list of types. Works on *type* variable only, no kind vars.
hsLTyVarBndrToType :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> LHsType (GhcPass p) #
Convert a LHsTyVarBndr to an equivalent LHsType.
hsLTyVarLocNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [Located (IdP (GhcPass p))] #
hsLTyVarLocName :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> Located (IdP (GhcPass p)) #
hsAllLTyVarNames :: LHsQTyVars GhcRn -> [Name] #
hsExplicitLTyVarNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [IdP (GhcPass p)] #
hsLTyVarNames :: forall (p :: Pass). [LHsTyVarBndr (GhcPass p)] -> [IdP (GhcPass p)] #
hsLTyVarName :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> IdP (GhcPass p) #
hsTyVarName :: forall (p :: Pass). HsTyVarBndr (GhcPass p) -> IdP (GhcPass p) #
hsScopedTvs :: LHsSigType GhcRn -> [Name] #
hsWcScopedTvs :: LHsSigWcType GhcRn -> [Name] #
hsConDetailsArgs :: HsConDetails (LHsType a) (Located [LConDeclField a]) -> [LHsType a] #
hsTvbAllKinded :: LHsQTyVars pass -> Bool #
Do all type variables in this LHsQTyVars come with kind annotations?
isHsKindedTyVar :: HsTyVarBndr pass -> Bool #
Does this HsTyVarBndr come with an explicit kind annotation?
hsIPNameFS :: HsIPName -> FastString #
mkEmptyWildCardBndrs :: thing -> HsWildCardBndrs GhcRn thing #
mkEmptyImplicitBndrs :: thing -> HsImplicitBndrs GhcRn thing #
mkHsWildCardBndrs :: thing -> HsWildCardBndrs GhcPs thing #
mkHsImplicitBndrs :: thing -> HsImplicitBndrs GhcPs thing #
dropWildCards :: LHsSigWcType pass -> LHsSigType pass #
hsSigWcType :: LHsSigWcType pass -> LHsType pass #
hsImplicitBody :: forall (p :: Pass) thing. HsImplicitBndrs (GhcPass p) thing -> thing #
isEmptyLHsQTvs :: LHsQTyVars GhcRn -> Bool #
hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr pass] #
mkHsQTvs :: [LHsTyVarBndr GhcPs] -> LHsQTyVars GhcPs #
noLHsContext :: LHsContext pass #
getBangStrictness :: LHsType a -> HsSrcBang #
getBangType :: LHsType a -> LHsType a #
type BangType pass = HsType pass #
Bang Type
In the parser, strictness and packedness annotations bind more tightly
than docstrings. This means that when consuming a BangType (and looking
for HsBangTy) we must be ready to peer behind a potential layer of
HsDocTy. See #15206 for motivation and getBangType for an example.
type LHsContext pass #
Arguments
| = Located (HsContext pass) |
|
Located Haskell Context
Arguments
| = Located (HsType pass) | May have |
Located Haskell Type
type LHsTyVarBndr pass = Located (HsTyVarBndr pass) #
Located Haskell Type Variable Binder
data LHsQTyVars pass #
Located Haskell Quantified Type Variables
Constructors
| HsQTvs | |
Fields
| |
| XLHsQTyVars (XXLHsQTyVars pass) | |
Instances
| OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) | |
Defined in GHC.Hs.Types | |
data HsImplicitBndrs pass thing #
Haskell Implicit Binders
Constructors
| HsIB | |
| XHsImplicitBndrs (XXHsImplicitBndrs pass thing) | |
Instances
| Outputable thing => Outputable (HsImplicitBndrs (GhcPass p) thing) | |
Defined in GHC.Hs.Types | |
data HsWildCardBndrs pass thing #
Haskell Wildcard Binders
Constructors
| HsWC | |
| XHsWildCardBndrs (XXHsWildCardBndrs pass thing) | |
Instances
| Outputable thing => Outputable (HsWildCardBndrs (GhcPass p) thing) | |
Defined in GHC.Hs.Types | |
type LHsSigType pass = HsImplicitBndrs pass (LHsType pass) #
Located Haskell Signature Type
type LHsWcType pass = HsWildCardBndrs pass (LHsType pass) #
Located Haskell Wildcard Type
type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass) #
Located Haskell Signature Wildcard Type
These names are used early on to store the names of implicit parameters. They completely disappear after type-checking.
Constructors
| HsIPName FastString |
Instances
| Eq HsIPName | |
| Data HsIPName | |
Defined in GHC.Hs.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPName -> c HsIPName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsIPName # toConstr :: HsIPName -> Constr # dataTypeOf :: HsIPName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsIPName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsIPName) # gmapT :: (forall b. Data b => b -> b) -> HsIPName -> HsIPName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPName -> r # gmapQ :: (forall d. Data d => d -> u) -> HsIPName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName # | |
| Outputable HsIPName | |
| OutputableBndr HsIPName | |
Defined in GHC.Hs.Types Methods pprBndr :: BindingSite -> HsIPName -> SDoc # pprPrefixOcc :: HsIPName -> SDoc # pprInfixOcc :: HsIPName -> SDoc # bndrIsJoin_maybe :: HsIPName -> Maybe Int # | |
data HsTyVarBndr pass #
Haskell Type Variable Binder
Constructors
| UserTyVar (XUserTyVar pass) (Located (IdP pass)) | |
| KindedTyVar (XKindedTyVar pass) (Located (IdP pass)) (LHsKind pass) | |
| XTyVarBndr (XXTyVarBndr pass) |
Instances
| NamedThing (HsTyVarBndr GhcRn) | |
Defined in GHC.Hs.Types | |
| OutputableBndrId p => Outputable (HsTyVarBndr (GhcPass p)) | |
Defined in GHC.Hs.Types | |
Haskell Type
Constructors
data NewHsTypeX #
Instances
| Data NewHsTypeX |
|
Defined in GHC.Hs.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewHsTypeX -> c NewHsTypeX # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewHsTypeX # toConstr :: NewHsTypeX -> Constr # dataTypeOf :: NewHsTypeX -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NewHsTypeX) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewHsTypeX) # gmapT :: (forall b. Data b => b -> b) -> NewHsTypeX -> NewHsTypeX # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewHsTypeX -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewHsTypeX -> r # gmapQ :: (forall d. Data d => d -> u) -> NewHsTypeX -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NewHsTypeX -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewHsTypeX -> m NewHsTypeX # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewHsTypeX -> m NewHsTypeX # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewHsTypeX -> m NewHsTypeX # | |
| Outputable NewHsTypeX | |
Defined in GHC.Hs.Types | |
Haskell Type Literal
Constructors
| HsNumTy SourceText Integer | |
| HsStrTy SourceText FastString |
Instances
| Data HsTyLit | |
Defined in GHC.Hs.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyLit -> c HsTyLit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsTyLit # toConstr :: HsTyLit -> Constr # dataTypeOf :: HsTyLit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsTyLit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsTyLit) # gmapT :: (forall b. Data b => b -> b) -> HsTyLit -> HsTyLit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyLit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyLit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit # | |
| Outputable HsTyLit | |
data HsTupleSort #
Haskell Tuple Sort
Instances
| Data HsTupleSort | |
Defined in GHC.Hs.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupleSort -> c HsTupleSort # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsTupleSort # toConstr :: HsTupleSort -> Constr # dataTypeOf :: HsTupleSort -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsTupleSort) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsTupleSort) # gmapT :: (forall b. Data b => b -> b) -> HsTupleSort -> HsTupleSort # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTupleSort -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupleSort -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort # | |
type LConDeclField pass #
Arguments
| = Located (ConDeclField pass) | May have |
Located Constructor Declaration Field
data ConDeclField pass #
Constructor Declaration Field
Constructors
| ConDeclField | |
Fields
| |
| XConDeclField (XXConDeclField pass) | |
Instances
| OutputableBndrId p => Outputable (ConDeclField (GhcPass p)) | |
Defined in GHC.Hs.Types | |
data HsConDetails arg rec #
Haskell Constructor Details
Instances
| (Data arg, Data rec) => Data (HsConDetails arg rec) | |
Defined in GHC.Hs.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConDetails arg rec -> c (HsConDetails arg rec) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDetails arg rec) # toConstr :: HsConDetails arg rec -> Constr # dataTypeOf :: HsConDetails arg rec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDetails arg rec)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDetails arg rec)) # gmapT :: (forall b. Data b => b -> b) -> HsConDetails arg rec -> HsConDetails arg rec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails arg rec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails arg rec -> r # gmapQ :: (forall d. Data d => d -> u) -> HsConDetails arg rec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDetails arg rec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDetails arg rec -> m (HsConDetails arg rec) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails arg rec -> m (HsConDetails arg rec) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails arg rec -> m (HsConDetails arg rec) # | |
| (Outputable arg, Outputable rec) => Outputable (HsConDetails arg rec) | |
Defined in GHC.Hs.Types | |
Instances
| (Outputable tm, Outputable ty) => Outputable (HsArg tm ty) | |
type LHsTypeArg p = HsArg (LHsType p) (LHsKind p) #
Field Occurrence
Represents an *occurrence* of an unambiguous field. We store
both the RdrName the user originally wrote, and after the
renamer, the selector function.
Constructors
| FieldOcc | |
Fields
| |
| XFieldOcc (XXFieldOcc pass) | |
Instances
| Eq (XCFieldOcc (GhcPass p)) => Eq (FieldOcc (GhcPass p)) | |
| Ord (XCFieldOcc (GhcPass p)) => Ord (FieldOcc (GhcPass p)) | |
Defined in GHC.Hs.Types Methods compare :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Ordering # (<) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool # (<=) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool # (>) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool # (>=) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool # max :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) # min :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) # | |
| Outputable (FieldOcc pass) | |
data AmbiguousFieldOcc pass #
Ambiguous Field Occurrence
Represents an *occurrence* of a field that is potentially
ambiguous after the renamer, with the ambiguity resolved by the
typechecker. We always store the RdrName that the user
originally wrote, and store the selector function after the renamer
(for unambiguous occurrences) or the typechecker (for ambiguous
occurrences).
See Note [HsRecField and HsRecUpdField] in GHC.Hs.Pat and Note [Disambiguating record fields] in TcExpr. See Note [Located RdrNames] in GHC.Hs.Expr
Constructors
| Unambiguous (XUnambiguous pass) (Located RdrName) | |
| Ambiguous (XAmbiguous pass) (Located RdrName) | |
| XAmbiguousFieldOcc (XXAmbiguousFieldOcc pass) |
Instances
| Outputable (AmbiguousFieldOcc (GhcPass p)) | |
Defined in GHC.Hs.Types | |
| OutputableBndr (AmbiguousFieldOcc (GhcPass p)) | |
Defined in GHC.Hs.Types Methods pprBndr :: BindingSite -> AmbiguousFieldOcc (GhcPass p) -> SDoc # pprPrefixOcc :: AmbiguousFieldOcc (GhcPass p) -> SDoc # pprInfixOcc :: AmbiguousFieldOcc (GhcPass p) -> SDoc # bndrIsJoin_maybe :: AmbiguousFieldOcc (GhcPass p) -> Maybe Int # | |
data ExecOptions #
Constructors
| ExecOptions | |
Fields
| |
data SingleStep #
Constructors
| RunToCompletion | |
| SingleStep | |
| RunAndLogSteps |
data ExecResult #
Constructors
| ExecComplete | |
Fields | |
| ExecBreak | |
Fields
| |
Constructors
| Resume | |
Fields
| |
mkTupleTy1 :: Boxity -> [Type] -> Type #
Make a tuple type. The list of types should not include any RuntimeRep specifications. Boxed 1-tuples are *not* flattened. See Note [One-tuples] and Note [Don't flatten tuples from HsSyn] in MkCore
mkTupleTy :: Boxity -> [Type] -> Type #
Make a tuple type. The list of types should not include any RuntimeRep specifications. Boxed 1-tuples are flattened. See Note [One-tuples]
justDataCon :: DataCon #
maybeTyCon :: TyCon #
consDataCon :: DataCon #
nilDataCon :: DataCon #
ordGTDataConId :: Id #
ordEQDataConId :: Id #
ordLTDataConId :: Id #
ordGTDataCon :: DataCon #
ordEQDataCon :: DataCon #
ordLTDataCon :: DataCon #
orderingTyCon :: TyCon #
trueDataConId :: Id #
falseDataConId :: Id #
trueDataCon :: DataCon #
falseDataCon :: DataCon #
doubleTyCon :: TyCon #
floatDataCon :: DataCon #
floatTyCon :: TyCon #
word8DataCon :: DataCon #
word8TyCon :: TyCon #
wordDataCon :: DataCon #
intDataCon :: DataCon #
charDataCon :: DataCon #
boxingDataCon_maybe :: TyCon -> Maybe DataCon #
liftedRepTy :: Type #
coercibleClass :: Class #
heqDataCon :: DataCon #
unboxedSumKind :: [Type] -> Kind #
Specialization of unboxedTupleSumKind for sums
sumDataCon :: ConTag -> Arity -> DataCon #
Data constructor for i-th alternative of a n-ary unboxed sum.
unitDataConId :: Id #
unitDataCon :: DataCon #
unitTyConKey :: Unique #
tupleDataConName :: Boxity -> Arity -> Name #
tupleDataCon :: Boxity -> Arity -> DataCon #
promotedTupleDataCon :: Boxity -> Arity -> TyCon #
tupleTyCon :: Boxity -> Arity -> TyCon #
cTupleDataConNames :: [Name] #
cTupleDataConName :: Arity -> Name #
cTupleTyConNameArity_maybe :: Name -> Maybe Arity #
If the given name is that of a constraint tuple, return its arity. Note that this is inefficient.
isCTupleTyConName :: Name -> Bool #
cTupleTyConNames :: [Name] #
cTupleTyConName :: Arity -> Name #
mkTupleStr :: Boxity -> Arity -> String #
isBuiltInOcc_maybe :: OccName -> Maybe Name #
Built-in syntax isn't "in scope" so these OccNames map to wired-in Names with BuiltInSyntax. However, this should only be necessary while resolving names produced by Template Haskell splices since we take care to encode built-in syntax names specially in interface files. See Note [Symbol table representation of names].
Moreover, there is no need to include names of things that the user can't write (e.g. type representation bindings like $tc(,,,)).
typeToTypeKind :: Kind #
typeNatKindCon :: TyCon #
intTyCon_RDR :: RdrName #
makeRecoveryTyCon :: TyCon -> TyCon #
Make a fake, recovery TyCon from an existing one.
Used when recovering from errors in type declarations
doubleTyConName :: Name #
floatTyConName :: Name #
word8TyConName :: Name #
wordTyConName :: Name #
justDataConName :: Name #
maybeTyConName :: Name #
consDataConName :: Name #
nilDataConName :: Name #
listTyConName :: Name #
boolTyConName :: Name #
intTyConName :: Name #
charTyConName :: Name #
heqTyConName :: Name #
eqTyCon_RDR :: RdrName #
eqTyConName :: Name #
mkWiredInIdName :: Module -> FastString -> Unique -> Id -> Name #
mkWiredInTyConName :: BuiltInSyntax -> Module -> FastString -> Unique -> TyCon -> Name #
wiredInTyCons :: [TyCon] #
isNeverLevPolyId :: Id -> Bool #
zapStableUnfolding :: Id -> Id #
zapIdTailCallInfo :: Id -> Id #
zapIdUsedOnceInfo :: Id -> Id #
zapIdUsageEnvInfo :: Id -> Id #
zapIdUsageInfo :: Id -> Id #
zapIdDemandInfo :: Id -> Id #
zapFragileIdInfo :: Id -> Id #
zapLamIdInfo :: Id -> Id #
updOneShotInfo :: Id -> OneShotInfo -> Id #
setIdOneShotInfo :: Id -> OneShotInfo -> Id infixl 1 #
clearOneShotLambda :: Id -> Id #
setOneShotLambda :: Id -> Id #
isProbablyOneShotLambda :: Id -> Bool #
isStateHackType :: Type -> Bool #
typeOneShot :: Type -> OneShotInfo #
stateHackOneShot :: OneShotInfo #
Should we apply the state hack to values of this Type?
isOneShotBndr :: Var -> Bool #
Returns whether the lambda associated with the Id is certainly applied at most once
This one is the "business end", called externally.
It works on type variables as well as Ids, returning True
Its main purpose is to encapsulate the Horrible State Hack
See Note [The state-transformer hack] in CoreArity
idStateHackOneShotInfo :: Id -> OneShotInfo #
Like idOneShotInfo, but taking the Horrible State Hack in to account
See Note [The state-transformer hack] in CoreArity
idOneShotInfo :: Id -> OneShotInfo #
isConLikeId :: Id -> Bool #
idRuleMatchInfo :: Id -> RuleMatchInfo #
setInlineActivation :: Id -> Activation -> Id infixl 1 #
idInlineActivation :: Id -> Activation #
modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> Id #
setInlinePragma :: Id -> InlinePragma -> Id infixl 1 #
idInlinePragma :: Id -> InlinePragma #
zapIdOccInfo :: Id -> Id #
setIdOccInfo :: Id -> OccInfo -> Id infixl 1 #
setIdCafInfo :: Id -> CafInfo -> Id #
setIdSpecialisation :: Id -> RuleInfo -> Id infixl 1 #
idHasRules :: Id -> Bool #
idCoreRules :: Id -> [CoreRule] #
idSpecialisation :: Id -> RuleInfo #
setCaseBndrEvald :: StrictnessMark -> Id -> Id #
setIdDemandInfo :: Id -> Demand -> Id infixl 1 #
idDemandInfo :: Id -> Demand #
setIdUnfolding :: Id -> Unfolding -> Id infixl 1 #
realIdUnfolding :: Id -> Unfolding #
idUnfolding :: Id -> Unfolding #
isStrictId :: Id -> Bool #
This predicate says whether the Id has a strict demand placed on it or
has a type such that it can always be evaluated strictly (i.e an
unlifted type, as of GHC 7.6). We need to
check separately whether the Id has a so-called "strict type" because if
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.
zapIdStrictness :: Id -> Id #
setIdStrictness :: Id -> StrictSig -> Id infixl 1 #
idStrictness :: Id -> StrictSig #
Accesses the Id's strictnessInfo.
isBottomingId :: Var -> Bool #
Returns true if an application to n args would diverge
idFunRepArity :: Id -> RepArity #
setIdCallArity :: Id -> Arity -> Id infixl 1 #
idCallArity :: Id -> Arity #
setIdArity :: Id -> Arity -> Id infixl 1 #
idJoinArity :: JoinId -> JoinArity #
isDeadBinder :: Id -> Bool #
isImplicitId :: Id -> Bool #
isImplicitId tells whether an Ids 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.
hasNoBinding :: Id -> Bool #
Returns True of an Id which may not have a
binding, even though it is defined in this module.
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
isJoinId_maybe :: Var -> Maybe JoinArity #
isDataConId_maybe :: Id -> Maybe DataCon #
isDataConWrapId_maybe :: Id -> Maybe DataCon #
isDataConWrapId :: Id -> Bool #
isDataConWorkId_maybe :: Id -> Maybe DataCon #
isDataConWorkId :: Id -> Bool #
isFCallId_maybe :: Id -> Maybe ForeignCall #
isPrimOpId_maybe :: Id -> Maybe PrimOp #
isPrimOpId :: Id -> Bool #
isClassOpId_maybe :: Id -> Maybe Class #
isNaughtyRecordSelector :: Id -> Bool #
isPatSynRecordSelector :: Id -> Bool #
isDataConRecordSelector :: Id -> Bool #
isRecordSelector :: Id -> Bool #
recordSelectorTyCon :: Id -> RecSelParent #
mkTemplateLocalsNum :: Int -> [Type] -> [Id] #
Create a template local for a series of type, but start from a specified template local
mkTemplateLocals :: [Type] -> [Id] #
Create a template local for a series of types
mkTemplateLocal :: Int -> Type -> Id #
Create a template local: a family of system local Ids in bijection with Ints, typically used in unfoldings
mkWorkerId :: Unique -> Id -> Type -> Id #
Workers get local names. CoreTidy will externalise these if necessary
mkUserLocalOrCoVar :: OccName -> Unique -> Type -> SrcSpan -> Id #
Like mkUserLocal, but checks if we have a coercion type
mkSysLocalOrCoVarM :: MonadUnique m => FastString -> Type -> m Id #
mkSysLocalM :: MonadUnique m => FastString -> Type -> m Id #
mkSysLocalOrCoVar :: FastString -> Unique -> Type -> Id #
Like mkSysLocal, but checks to see if we have a covar type
mkSysLocal :: FastString -> Unique -> Type -> Id #
mkExportedVanillaId :: Name -> Type -> 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]
mkLocalIdOrCoVarWithInfo :: Name -> Type -> IdInfo -> Id #
Make a local id, with the IdDetails set to CoVarId if the type indicates so.
mkLocalIdOrCoVar :: Name -> Type -> Id #
Like mkLocalId, but checks the type to see if it should make a covar
mkLocalCoVar :: Name -> Type -> CoVar #
Make a local CoVar
modifyIdInfo :: HasDebugCallStack => (IdInfo -> IdInfo) -> Id -> Id #
localiseId :: Id -> Id #
setIdUnique :: Id -> Unique -> Id #
collectNAnnBndrs :: Int -> AnnExpr bndr annot -> ([bndr], AnnExpr bndr annot) #
As collectNBinders but for AnnExpr rather than Expr
collectAnnBndrs :: AnnExpr bndr annot -> ([bndr], AnnExpr bndr annot) #
As collectBinders but for AnnExpr rather than Expr
deAnnotate' :: AnnExpr' bndr annot -> Expr bndr #
deAnnotate :: AnnExpr bndr annot -> Expr bndr #
collectAnnArgsTicks :: (Tickish Var -> Bool) -> AnnExpr b a -> (AnnExpr b a, [AnnExpr b a], [Tickish Var]) #
collectAnnArgs :: AnnExpr b a -> (AnnExpr b a, [AnnExpr b a]) #
Takes a nested application expression and returns the function being applied and the arguments to which it is applied
valArgCount :: [Arg b] -> Int #
The number of argument expressions that are values rather than types at their top level
valBndrCount :: [CoreBndr] -> Int #
The number of binders that bind values rather than types
Returns True iff the expression is a Coercion
expression at its top level
Returns True for value arguments, false for type args
NB: coercions are value arguments (zero width, to be sure,
like State#, but still value args).
isRuntimeArg :: CoreExpr -> Bool #
Will this argument expression exist at runtime?
isRuntimeVar :: Var -> Bool #
Will this variable exist at runtime?
collectArgsTicks :: (Tickish Id -> Bool) -> Expr b -> (Expr b, [Arg b], [Tickish Id]) #
Like collectArgs, but also collects looks through floatable
ticks if it means that we can find more arguments.
stripNArgs :: Word -> Expr a -> Maybe (Expr a) #
Attempt to remove the last N arguments of a function call. Strip off any ticks or coercions encountered along the way and any at the end.
collectArgs :: Expr b -> (Expr b, [Arg b]) #
Takes a nested application expression and returns the function being applied and the arguments to which it is applied
collectNBinders :: Int -> Expr b -> ([b], Expr b) #
Strip off exactly N leading lambdas (type or value). Good for use with join points.
collectTyBinders :: CoreExpr -> ([TyVar], CoreExpr) #
collectBinders :: Expr b -> ([b], Expr b) #
We often want to strip off leading lambdas before getting down to
business. Variants are collectTyBinders, collectValBinders,
and collectTyAndValBinders
flattenBinds :: [Bind b] -> [(b, Expr b)] #
Collapse all the bindings in the supplied groups into a single
list of lhs/rhs pairs suitable for binding in a Rec binding group
rhssOfAlts :: [Alt b] -> [Expr b] #
rhssOfBind :: Bind b -> [Expr b] #
bindersOfBinds :: [Bind b] -> [b] #
bindersOf applied to a list of binding groups
exprToType :: CoreExpr -> Type #
applyTypeToArg :: Type -> CoreExpr -> Type #
Determines the type resulting from applying an expression with given type to a given argument expression
varsToCoreExprs :: [CoreBndr] -> [Expr b] #
mkCoBind :: CoVar -> Coercion -> CoreBind #
Create a binding group where a type variable is bound to a type. Per CoreSyn,
this can only be used to bind something in a non-recursive let expression
mkTyBind :: TyVar -> Type -> CoreBind #
Create a binding group where a type variable is bound to a type. Per CoreSyn,
this can only be used to bind something in a non-recursive let expression
mkLetRec :: [(b, Expr b)] -> Expr b -> Expr b #
mkLetRec binds body wraps body in a let rec with the given set of
binds if binds is non-empty.
mkLetNonRec :: b -> Expr b -> Expr b -> Expr b #
mkLetNonRec bndr rhs body wraps body in a let binding bndr.
mkLets :: [Bind b] -> Expr b -> Expr b #
Bind all supplied binding groups over an expression in a nested let expression. Assumes
that the rhs satisfies the let/app invariant. Prefer to use mkCoreLets if
possible, which does guarantee the invariant
mkLams :: [b] -> Expr b -> Expr b #
Bind all supplied binders over an expression in a nested lambda expression. Prefer to
use mkCoreLams if possible
mkDoubleLitDouble :: Double -> Expr b #
Create a machine double precision literal expression of type Double# from a Double.
If you want an expression of type Double use mkDoubleExpr
mkDoubleLit :: Rational -> Expr b #
Create a machine double precision literal expression of type Double# from a Rational.
If you want an expression of type Double use mkDoubleExpr
mkFloatLitFloat :: Float -> Expr b #
Create a machine single precision literal expression of type Float# from a Float.
If you want an expression of type Float use mkFloatExpr
mkFloatLit :: Rational -> Expr b #
Create a machine single precision literal expression of type Float# from a Rational.
If you want an expression of type Float use mkFloatExpr
mkStringLit :: String -> Expr b #
Create a machine string literal expression of type Addr#.
If you want an expression of type String use mkStringExpr
Create a machine character literal expression of type Char#.
If you want an expression of type Char use mkCharExpr
mkInt64LitInt64 :: Int64 -> Expr b #
mkWord64LitWord64 :: Word64 -> Expr b #
mkWordLitWord :: DynFlags -> Word -> Expr b #
Create a machine word literal expression of type Word# from a Word.
If you want an expression of type Word use mkWordExpr
mkWordLit :: DynFlags -> Integer -> Expr b #
Create a machine word literal expression of type Word# from an Integer.
If you want an expression of type Word use mkWordExpr
mkIntLitInt :: DynFlags -> Int -> Expr b #
Create a machine integer literal expression of type Int# from an Int.
If you want an expression of type Int use mkIntExpr
mkIntLit :: DynFlags -> Integer -> Expr b #
Create a machine integer literal expression of type Int# from an Integer.
If you want an expression of type Int use mkIntExpr
mkTyApps :: Expr b -> [Type] -> Expr b infixl 4 #
Apply a list of type argument expressions to a function expression in a nested fashion
mkConApp :: DataCon -> [Arg b] -> Expr b #
Apply a list of argument expressions to a data constructor in a nested fashion. Prefer to
use mkCoreConApps if possible
mkVarApps :: Expr b -> [Var] -> Expr b infixl 4 #
Apply a list of type or value variables to a function expression in a nested fashion
mkCoApps :: Expr b -> [Coercion] -> Expr b infixl 4 #
Apply a list of coercion argument expressions to a function expression in a nested fashion
mkApps :: Expr b -> [Arg b] -> Expr b infixl 4 #
Apply a list of argument expressions to a function expression in a nested fashion. Prefer to
use mkCoreApps if possible
deTagExpr :: TaggedExpr t -> CoreExpr #
cmpAltCon :: AltCon -> AltCon -> Ordering #
Compares AltCons within a single list of alternatives
DEFAULT comes out smallest, so that sorting by AltCon puts
alternatives in the order required: see Note [Case expression invariants]
isFragileUnfolding :: Unfolding -> Bool #
isBootUnfolding :: Unfolding -> Bool #
hasSomeUnfolding :: Unfolding -> Bool #
Only returns False if there is no unfolding information available at all
isStableUnfolding :: Unfolding -> Bool #
isCompulsoryUnfolding :: Unfolding -> Bool #
isExpandableUnfolding :: Unfolding -> Bool #
isCheapUnfolding :: Unfolding -> Bool #
Is the thing we will unfold into certainly cheap?
isConLikeUnfolding :: Unfolding -> Bool #
True if the unfolding is a constructor application, the application
of a CONLIKE function or OtherCon
isEvaldUnfolding :: Unfolding -> Bool #
Determines if it possibly the case that the unfolding will
yield a value. Unlike isValueUnfolding it returns True
for OtherCon
isValueUnfolding :: Unfolding -> Bool #
Determines if it is certainly the case that the unfolding will
yield a value (something in HNF): returns False if unsure
otherCons :: Unfolding -> [AltCon] #
The constructors that the unfolding could never be:
returns [] if no information is available
maybeUnfoldingTemplate :: Unfolding -> Maybe CoreExpr #
Retrieves the template of an unfolding if possible maybeUnfoldingTemplate is used mainly wnen specialising, and we do want to specialise DFuns, so it's important to return a template for DFunUnfoldings
unfoldingTemplate :: Unfolding -> CoreExpr #
Retrieves the template of an unfolding: panics if none is known
isStableSource :: UnfoldingSource -> Bool #
mkOtherCon :: [AltCon] -> Unfolding #
There is no known Unfolding, because this came from an
hi-boot file.
This unfolding marks the associated thing as being evaluated
There is no known Unfolding
boringCxtNotOk :: Bool #
boringCxtOk :: Bool #
unSaturatedOk :: Bool #
needSaturated :: Bool #
setRuleIdName :: Name -> CoreRule -> CoreRule #
isLocalRule :: CoreRule -> Bool #
ruleActivation :: CoreRule -> Activation #
ruleModule :: CoreRule -> Maybe Module #
ruleArity :: CoreRule -> Int #
The number of arguments the ru_fn must be applied
to before the rule can match on it
isAutoRule :: CoreRule -> Bool #
isBuiltinRule :: CoreRule -> Bool #
emptyRuleEnv :: RuleEnv #
chooseOrphanAnchor :: NameSet -> IsOrphan #
tickishContains :: Eq b => Tickish b -> Tickish b -> Bool #
Returns whether one tick "contains" the other one, therefore making the second tick redundant.
tickishPlace :: Tickish id -> TickishPlacement #
Placement behaviour we want for the ticks
tickishIsCode :: Tickish id -> Bool #
Return True if this source annotation compiles to some backend
code. Without this flag, the tickish is seen as a simple annotation
that does not have any associated evaluation code.
What this means that we are allowed to disregard the tick if doing so means that we can skip generating any code in the first place. A typical example is top-level bindings:
foo = tick... y -> ... ==> foo = y -> tick... ...
Here there is just no operational difference between the first and the second version. Therefore code generation should simply translate the code as if it found the latter.
tickishCanSplit :: Tickish id -> Bool #
Returns True for a tick that is both counting and scoping and
can be split into its (tick, scope) parts using mkNoScope and
mkNoTick respectively.
tickishFloatable :: Tickish id -> Bool #
Returns True for ticks that can be floated upwards easily even
where it might change execution counts, such as:
Just (tick... foo) ==> tick... (Just foo)
This is a combination of tickishSoftScope and
tickishCounts. Note that in principle splittable ticks can become
floatable using mkNoTick -- even though there's currently no
tickish for which that is the case.
tickishScopesLike :: Tickish id -> TickishScoping -> Bool #
Returns whether the tick scoping rule is at least as permissive as the given scoping rule.
tickishScoped :: Tickish id -> TickishScoping #
Returns the intended scoping rule for a Tickish
tickishCounts :: Tickish id -> Bool #
A "counting tick" (where tickishCounts is True) is one that counts evaluations in some way. We cannot discard a counting tick, and the compiler should preserve the number of counting ticks as far as possible.
However, we still allow the simplifier to increase or decrease sharing, so in practice the actual number of ticks may vary, except that we never change the value from zero to non-zero or vice versa.
This is the data type that represents GHCs core intermediate language. Currently GHC uses System FC https://www.microsoft.com/en-us/research/publication/system-f-with-type-equality-coercions/ for this purpose, which is closely related to the simpler and better known System F http://en.wikipedia.org/wiki/System_F.
We get from Haskell source to this Core language in a number of stages:
- The source code is parsed into an abstract syntax tree, which is represented
by the data type
HsExprwith the names beingRdrNames - This syntax tree is renamed, which attaches a
Uniqueto everyRdrName(yielding aName) to disambiguate identifiers which are lexically identical. For example, this program:
f x = let f x = x + 1
in f (x - 2)
Would be renamed by having Uniques attached so it looked something like this:
f_1 x_2 = let f_3 x_4 = x_4 + 1
in f_3 (x_2 - 2)
But see Note [Shadowing] below.
- The resulting syntax tree undergoes type checking (which also deals with instantiating
type class arguments) to yield a
HsExprtype that hasIdas it's names. - Finally the syntax tree is desugared from the expressive
HsExprtype into thisExprtype, which has far fewer constructors and hence is easier to perform optimization, analysis and code generation on.
The type parameter b is for the type of binders in the expression tree.
The language consists of the following elements:
- Variables See Note [Variable occurrences in Core]
- Primitive literals
- Applications: note that the argument may be a
Type. See Note [CoreSyn let/app invariant] See Note [Levity polymorphism invariants] - Lambda abstraction See Note [Levity polymorphism invariants]
- Recursive and non recursive
lets. Operationally this corresponds to allocating a thunk for the things bound and then executing the sub-expression.
See Note [CoreSyn letrec invariant] See Note [CoreSyn let/app invariant] See Note [Levity polymorphism invariants] See Note [CoreSyn type and coercion invariant]
- Case expression. Operationally this corresponds to evaluating the scrutinee (expression examined) to weak head normal form and then examining at most one level of resulting constructor (i.e. you cannot do nested pattern matching directly with this).
The binder gets bound to the value of the scrutinee,
and the Type must be that of all the case alternatives
IMPORTANT: see Note [Case expression invariants]
- Cast an expression to a particular type.
This is used to implement
newtypes (anewtypeconstructor or destructor just becomes aCastin Core) and GADTs. - Notes. These allow general information to be added to expressions in the syntax tree
- A type: this should only show up at the top level of an Arg
- A coercion
Constructors
| Var Id | |
| Lit Literal | |
| App (Expr b) (Arg b) infixl 4 | |
| Lam b (Expr b) | |
| Let (Bind b) (Expr b) | |
| Case (Expr b) b Type [Alt b] | |
| Cast (Expr b) Coercion | |
| Tick (Tickish Id) (Expr b) | |
| Type Type | |
| Coercion Coercion |
Instances
| Show CoreExpr Source # | |
| Subable CoreExpr Source # | |
| Eq (DeBruijn CoreExpr) | |
| Eq (DeBruijn CoreAlt) | |
| Data b => Data (Expr b) | |
Defined in CoreSyn Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Expr b -> c (Expr b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Expr b) # toConstr :: Expr b -> Constr # dataTypeOf :: Expr b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Expr b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Expr b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Expr b -> Expr b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expr b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expr b -> r # gmapQ :: (forall d. Data d => d -> u) -> Expr b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Expr b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expr b -> m (Expr b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr b -> m (Expr b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr b -> m (Expr b) # | |
| PPrint (Expr Var) Source # | |
Defined in Language.Haskell.Liquid.Types.PrettyPrint | |
| CBVisitable (Expr Var) Source # | |
| CBVisitable (Alt Var) Source # | |
| Subable (Alt Var) Source # | |
| Show (Axiom Var Type CoreExpr) Source # | |
type Alt b = (AltCon, [b], Expr b) #
A case split alternative. Consists of the constructor leading to the alternative,
the variables bound from the constructor, and the expression to be executed given that binding.
The default alternative is (DEFAULT, [], rhs)
A case alternative constructor (i.e. pattern match)
Constructors
| DataAlt DataCon | |
| LitAlt Literal | A literal: |
| DEFAULT | Trivial alternative: |
Instances
| Eq AltCon | |
| Data AltCon | |
Defined in CoreSyn Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AltCon -> c AltCon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AltCon # toConstr :: AltCon -> Constr # dataTypeOf :: AltCon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AltCon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AltCon) # gmapT :: (forall b. Data b => b -> b) -> AltCon -> AltCon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AltCon -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AltCon -> r # gmapQ :: (forall d. Data d => d -> u) -> AltCon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AltCon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AltCon -> m AltCon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AltCon -> m AltCon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AltCon -> m AltCon # | |
| Ord AltCon | |
| Outputable AltCon | |
| PPrint AltCon Source # | |
Defined in Language.Haskell.Liquid.Synthesize.Misc | |
| CBVisitable AltCon Source # | |
| Eq (DeBruijn CoreAlt) | |
| CBVisitable (Alt Var) Source # | |
| Subable (Alt Var) Source # | |
Binding, used for top level bindings in a module and local bindings in a let.
Instances
| CBVisitable CoreBind Source # | |
| Data b => Data (Bind b) | |
Defined in CoreSyn Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Bind b -> c (Bind b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Bind b) # toConstr :: Bind b -> Constr # dataTypeOf :: Bind b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Bind b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Bind b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Bind b -> Bind b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bind b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bind b -> r # gmapQ :: (forall d. Data d => d -> u) -> Bind b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bind b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bind b -> m (Bind b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bind b -> m (Bind b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bind b -> m (Bind b) # | |
| PPrint (Bind Var) Source # | |
Defined in Language.Haskell.Liquid.Types.PrettyPrint | |
| CBVisitable [CoreBind] Source # | |
| Subable (Bind Var) Source # | |
type InCoercion = Coercion #
type OutCoercion = Coercion #
type MOutCoercion = MCoercion #
Allows attaching extra information to points in expressions
Constructors
| ProfNote | An |
Fields
| |
| HpcTick | A "tick" used by HPC to track the execution of each subexpression in the original source code. |
Fields
| |
| Breakpoint | A breakpoint for the GHCi debugger. This behaves like an HPC tick, but has a list of free variables which will be available for inspection in GHCi when the program stops at the breakpoint. NB. we must take account of these Ids when (a) counting free variables, and (b) substituting (don't substitute for them) |
Fields
| |
| SourceNote | A source note. Source notes are pure annotations: Their presence should neither influence compilation nor execution. The semantics are given by causality: The presence of a source note means that a local change in the referenced source code span will possibly provoke the generated code to change. On the flip-side, the functionality of annotated code *must* be invariant against changes to all source code *except* the spans referenced in the source notes (see "Causality of optimized Haskell" paper for details). Therefore extending the scope of any given source note is always valid. Note that it is still undesirable though, as this reduces their usefulness for debugging and profiling. Therefore we will generally try only to make use of this property where it is necessary to enable optimizations. |
Fields
| |
Instances
| Eq id => Eq (Tickish id) | |
| Data id => Data (Tickish id) | |
Defined in CoreSyn Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tickish id -> c (Tickish id) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tickish id) # toConstr :: Tickish id -> Constr # dataTypeOf :: Tickish id -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tickish id)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tickish id)) # gmapT :: (forall b. Data b => b -> b) -> Tickish id -> Tickish id # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tickish id -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tickish id -> r # gmapQ :: (forall d. Data d => d -> u) -> Tickish id -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tickish id -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tickish id -> m (Tickish id) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tickish id -> m (Tickish id) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tickish id -> m (Tickish id) # | |
| Ord id => Ord (Tickish id) | |
data TickishScoping #
Specifies the scoping behaviour of ticks. This governs the behaviour of ticks that care about the covered code and the cost associated with it. Important for ticks relating to profiling.
Constructors
| NoScope | No scoping: The tick does not care about what code it covers. Transformations can freely move code inside as well as outside without any additional annotation obligations |
| SoftScope | Soft scoping: We want all code that is covered to stay covered. Note that this scope type does not forbid transformations from happening, as long as all results of the transformations are still covered by this tick or a copy of it. For example let x = tick... (let y = foo in bar) in baz ===> let x = tick... bar; y = tick... foo in baz Is a valid transformation as far as "bar" and "foo" is concerned, because both still are scoped over by the tick. Note though that one might object to the "let" not being covered by the tick any more. However, we are generally lax with this - constant costs don't matter too much, and given that the "let" was effectively merged we can view it as having lost its identity anyway. Also note that this scoping behaviour allows floating a tick "upwards" in pretty much any situation. For example: case foo of x -> tick... bar ==> tick... case foo of x -> bar While this is always leagl, we want to make a best effort to only make us of this where it exposes transformation opportunities. |
| CostCentreScope | Cost centre scoping: We don't want any costs to move to other cost-centre stacks. This means we not only want no code or cost to get moved out of their cost centres, but we also object to code getting associated with new cost-centre ticks - or changing the order in which they get applied. A rule of thumb is that we don't want any code to gain new annotations. However, there are notable exceptions, for example: let f = y -> foo in tick... ... (f x) ... ==> tick... ... foo[x/y] ... In-lining lambdas like this is always legal, because inlining a function does not change the cost-centre stack when the function is called. |
Instances
| Eq TickishScoping | |
Defined in CoreSyn Methods (==) :: TickishScoping -> TickishScoping -> Bool # (/=) :: TickishScoping -> TickishScoping -> Bool # | |
data TickishPlacement #
Governs the kind of expression that the tick gets placed on when
annotating for example using mkTick. If we find that we want to
put a tickish on an expression ruled out here, we try to float it
inwards until we find a suitable expression.
Constructors
| PlaceRuntime | Place ticks exactly on run-time expressions. We can still move the tick through pure compile-time constructs such as other ticks, casts or type lambdas. This is the most restrictive placement rule for ticks, as all tickishs have in common that they want to track runtime processes. The only legal placement rule for counting ticks. |
| PlaceNonLam | As |
| PlaceCostCentre | In addition to floating through lambdas, cost-centre style tickishs can also be moved from constructors, non-function variables and literals. For example: let x = scc... C (scc... y) (scc... 3) in ... Neither the constructor application, the variable or the literal are likely to have any cost worth mentioning. And even if y names a thunk, the call would not care about the evaluation context. Therefore removing all annotations in the above example is safe. |
Instances
| Eq TickishPlacement | |
Defined in CoreSyn Methods (==) :: TickishPlacement -> TickishPlacement -> Bool # (/=) :: TickishPlacement -> TickishPlacement -> Bool # | |
Is this instance an orphan? If it is not an orphan, contains an OccName
witnessing the instance's non-orphanhood.
See Note [Orphans]
Instances
| Data IsOrphan | |
Defined in CoreSyn Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IsOrphan -> c IsOrphan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IsOrphan # toConstr :: IsOrphan -> Constr # dataTypeOf :: IsOrphan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IsOrphan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsOrphan) # gmapT :: (forall b. Data b => b -> b) -> IsOrphan -> IsOrphan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IsOrphan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IsOrphan -> r # gmapQ :: (forall d. Data d => d -> u) -> IsOrphan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IsOrphan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IsOrphan -> m IsOrphan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IsOrphan -> m IsOrphan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IsOrphan -> m IsOrphan # | |
| Binary IsOrphan | |
A full rule environment which we can apply rules from. Like a RuleBase,
but it also includes the set of visible orphans we use to filter out orphan
rules which are not visible (even though we can see them...)
Constructors
| RuleEnv | |
Fields | |
A CoreRule is:
- "Local" if the function it is a rule for is defined in the same module as the rule itself.
- "Orphan" if nothing on the LHS is defined in the same module as the rule itself
Constructors
| Rule | |
Fields
| |
| BuiltinRule | Built-in rules are used for constant folding and suchlike. They have no free variables. A built-in rule is always visible (there is no such thing as an orphan built-in rule.) |
Fields | |
type InScopeEnv = (InScopeSet, IdUnfoldingFun) #
type IdUnfoldingFun = Id -> Unfolding #
Records the unfolding of an identifier, which is approximately the form the identifier would have if we substituted its definition in for the identifier. This type should be treated as abstract everywhere except in CoreUnfold
Constructors
| NoUnfolding | We have no information about the unfolding. |
| BootUnfolding | We have no information about the unfolding, because
this |
| OtherCon [AltCon] | It ain't one of these constructors.
data C = C !(Int -> Int)
case x of { C f -> ... }Here, |
| DFunUnfolding | |
| CoreUnfolding | An unfolding with redundant cached information. Parameters: uf_tmpl: Template used to perform unfolding; NB: Occurrence info is guaranteed correct: see Note [OccInfo in unfoldings and rules] uf_is_top: Is this a top level binding? uf_is_value: uf_is_work_free: Does this waste only a little work if we expand it inside an inlining?
Basically this is a cached version of uf_guidance: Tells us about the size of the unfolding template |
Fields
| |
data UnfoldingSource #
Constructors
| InlineRhs | |
| InlineStable | |
| InlineCompulsory |
data UnfoldingGuidance #
UnfoldingGuidance says when unfolding should take place
Constructors
| UnfWhen | |
Fields
| |
| UnfIfGoodArgs | |
| UnfNever | |
Instances
| Eq UnfoldingGuidance | |
Defined in CoreSyn Methods (==) :: UnfoldingGuidance -> UnfoldingGuidance -> Bool # (/=) :: UnfoldingGuidance -> UnfoldingGuidance -> Bool # | |
type CoreProgram = [CoreBind] #
The common case for the type of binders and variables when we are manipulating the Core language within GHC
data TaggedBndr t #
Binders are tagged with a t
Instances
| Outputable b => Outputable (TaggedBndr b) | |
Defined in CoreSyn | |
type TaggedBind t = Bind (TaggedBndr t) #
type TaggedExpr t = Expr (TaggedBndr t) #
type TaggedArg t = Arg (TaggedBndr t) #
type TaggedAlt t = Alt (TaggedBndr t) #
type AnnAlt bndr annot = (AltCon, [bndr], AnnExpr bndr annot) #
A clone of the Alt type but allowing annotation at every tree node
A clone of the Bind type but allowing annotation at every tree node
conLikeIsInfix :: ConLike -> Bool #
conLikesWithFields :: [ConLike] -> [FieldLabelString] -> [ConLike] #
The ConLikes that have *all* the given fields
conLikeFieldType :: ConLike -> FieldLabelString -> Type #
Extract the type for any given labelled field of the ConLike
conLikeFullSig :: ConLike -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, ThetaType, [Type], Type) #
The "full signature" of the ConLike returns, in order:
1) The universally quantified type variables
2) The existentially quantified type/coercion variables
3) The equality specification
4) The provided theta (the constraints provided by a match)
5) The required theta (the constraints required for a match)
6) The original argument types (i.e. before any change of the representation of the type)
7) The original result type
conLikeResTy :: ConLike -> [Type] -> Type #
Returns the type of the whole pattern
conLikeImplBangs :: ConLike -> [HsImplBang] #
Returns the strictness information for each constructor
conLikeWrapId_maybe :: ConLike -> Maybe Id #
Returns the Id of the wrapper. This is also known as the builder in
some contexts. The value is Nothing only in the case of unidirectional
pattern synonyms.
conLikeStupidTheta :: ConLike -> ThetaType #
conLikeExTyCoVars :: ConLike -> [TyCoVar] #
Existentially quantified type/coercion variables
conLikeInstOrigArgTys :: ConLike -> [Type] -> [Type] #
Returns just the instantiated value argument types of a ConLike,
(excluding dictionary args)
conLikeFieldLabels :: ConLike -> [FieldLabel] #
Names of fields used for selectors
conLikeArity :: ConLike -> Arity #
Number of arguments
Extract the type constructor, type argument, data constructor and it's representation argument types from a type if it is a product type.
Precisely, we return Just for any type that is all of:
- Concrete (i.e. constructors visible)
- Single-constructor
- Not existentially quantified
Whether the type is a data type or a newtype
promoteDataCon :: DataCon -> TyCon #
dataConUserTyVarsArePermuted :: DataCon -> Bool #
Were the type variables of the data con written in a different order than the regular order (universal tyvars followed by existential tyvars)?
This is not a cheap test, so we minimize its use in GHC as much as possible.
Currently, its only call site in the GHC codebase is in mkDataConRep in
MkId, and so dataConUserTyVarsArePermuted is only called at most once
during a data constructor's lifetime.
dataConCannotMatch :: [Type] -> DataCon -> Bool #
classDataCon :: Class -> DataCon #
specialPromotedDc :: DataCon -> Bool #
Should this DataCon be allowed in a type even without -XDataKinds? Currently, only Lifted & Unlifted
isVanillaDataCon :: DataCon -> Bool #
Vanilla DataCons are those that are nice boring Haskell 98 constructors
isUnboxedTupleCon :: DataCon -> Bool #
isTupleDataCon :: DataCon -> Bool #
dataConIdentity :: DataCon -> ByteString #
The string package:module.name identifying a constructor, which is attached
to its info table and used by the GHCi debugger and the heap profiler
dataConRepArgTys :: DataCon -> [Type] #
Returns the arg types of the worker, including *all* non-dependent evidence, after any flattening has been done and without substituting for any type variables
dataConOrigArgTys :: DataCon -> [Type] #
Returns the argument types of the wrapper, excluding all dictionary arguments and without substituting for any type variables
Arguments
| :: DataCon | A datacon with no existentials or equality constraints However, it can have a dcTheta (notably it can be a class dictionary, with superclasses) |
| -> [Type] | Instantiated at these types |
| -> [Type] |
Finds the instantiated types of the arguments required to construct a
DataCon representation
NB: these INCLUDE any dictionary args
but EXCLUDE the data-declaration context, which is discarded
It's all post-flattening etc; this is a representation type
dataConUserType :: DataCon -> Type #
The user-declared type of the data constructor in the nice-to-read form:
T :: forall a b. a -> b -> T [a]
rather than:
T :: forall a c. forall b. (c~[a]) => a -> b -> T c
The type variables are quantified in the order that the user wrote them.
See Note [DataCon user type variable binders].
NB: If the constructor is part of a data instance, the result type mentions the family tycon, not the internal one.
dataConOrigResTy :: DataCon -> Type #
dataConInstSig :: DataCon -> [Type] -> ([TyCoVar], ThetaType, [Type]) #
Instantiate the universal tyvars of a data con, returning ( instantiated existentials , instantiated constraints including dependent GADT equalities which are *also* listed in the instantiated existentials , instantiated args)
dataConSig :: DataCon -> ([TyCoVar], ThetaType, [Type], Type) #
The "signature" of the DataCon returns, in order:
1) The result of dataConUnivAndExTyCoVars,
2) All the ThetaTypes relating to the DataCon (coercion, dictionary,
implicit parameter - whatever), including dependent GADT equalities.
Dependent GADT equalities are *also* listed in return value (1), so be
careful!
3) The type arguments to the constructor
4) The original result type of the DataCon
dataConBoxer :: DataCon -> Maybe DataConBoxer #
dataConImplBangs :: DataCon -> [HsImplBang] #
dataConRepStrictness :: DataCon -> [StrictnessMark] #
Give the demands on the arguments of a Core constructor application (Con dc args)
isNullaryRepDataCon :: DataCon -> Bool #
Return whether there are any argument types for this DataCons runtime representation type
See Note [DataCon arities]
isNullarySrcDataCon :: DataCon -> Bool #
Return whether there are any argument types for this DataCons original source type
See Note [DataCon arities]
dataConRepArity :: DataCon -> Arity #
Gives the number of actual fields in the representation of the data constructor. This may be more than appear in the source code; the extra ones are the existentially quantified dictionaries
dataConSrcBangs :: DataCon -> [HsSrcBang] #
Strictness/unpack annotations, from user; or, for imported
DataCons, from the interface file
The list is in one-to-one correspondence with the arity of the DataCon
dataConFieldType_maybe :: DataCon -> FieldLabelString -> Maybe (FieldLabel, Type) #
dataConFieldType :: DataCon -> FieldLabelString -> Type #
Extract the type for any given labelled field of the DataCon
dataConImplicitTyThings :: DataCon -> [TyThing] #
Find all the Ids implicitly brought into scope by the data constructor. Currently,
the union of the dataConWorkId and the dataConWrapId
dataConWrapId :: DataCon -> Id #
Returns an Id which looks like the Haskell-source constructor by using
the wrapper if it exists (see dataConWrapId_maybe) and failing over to
the worker (see dataConWorkId)
dataConWrapId_maybe :: DataCon -> Maybe Id #
Get the Id of the DataCon wrapper: a function that wraps the "actual"
constructor so it has the type visible in the source program: c.f.
dataConWorkId.
Returns Nothing if there is no wrapper, which occurs for an algebraic data
constructor and also for a newtype (whose constructor is inlined
compulsorily)
dataConWorkId :: DataCon -> Id #
dataConTheta :: DataCon -> ThetaType #
The *full* constraints on the constructor type, including dependent GADT equalities.
dataConEqSpec :: DataCon -> [EqSpec] #
Equalities derived from the result type of the data constructor, as written by the programmer in any GADT declaration. This includes *all* GADT-like equalities, including those written in by hand by the programmer.
dataConUnivAndExTyCoVars :: DataCon -> [TyCoVar] #
Both the universal and existential type/coercion variables of the constructor
dataConUnivTyVars :: DataCon -> [TyVar] #
The universally-quantified type variables of the constructor
dataConIsInfix :: DataCon -> Bool #
Should the DataCon be presented infix?
dataConRepType :: DataCon -> Type #
The representation type of the data constructor, i.e. the sort type that will represent values of this type at runtime
dataConOrigTyCon :: DataCon -> TyCon #
The original type constructor used in the definition of this data constructor. In case of a data family instance, that will be the family type constructor.
dataConTagZ :: DataCon -> ConTagZ #
dataConTag :: DataCon -> ConTag #
The tag used for ordering DataCons
Arguments
| :: Name | |
| -> Bool | Is the constructor declared infix? |
| -> TyConRepName | TyConRepName for the promoted TyCon |
| -> [HsSrcBang] | Strictness/unpack annotations, from user |
| -> [FieldLabel] | Field labels for the constructor, if it is a record, otherwise empty |
| -> [TyVar] | Universals. |
| -> [TyCoVar] | Existentials. |
| -> [TyVarBinder] | User-written |
| -> [EqSpec] | GADT equalities |
| -> KnotTied ThetaType | Theta-type occurring before the arguments proper |
| -> [KnotTied Type] | Original argument types |
| -> KnotTied Type | Original result type |
| -> RuntimeRepInfo | See comments on |
| -> KnotTied TyCon | Representation type constructor |
| -> ConTag | Constructor tag |
| -> ThetaType | The "stupid theta", context of the data
declaration e.g. |
| -> Id | Worker Id |
| -> DataConRep | Representation |
| -> DataCon |
Build a new data constructor
isMarkedStrict :: StrictnessMark -> Bool #
isSrcUnpacked :: SrcUnpackedness -> Bool #
isSrcStrict :: SrcStrictness -> Bool #
isBanged :: HsImplBang -> Bool #
eqHsBang :: HsImplBang -> HsImplBang -> Bool #
Compare strictness annotations
substEqSpec :: TCvSubst -> EqSpec -> EqSpec #
Substitute in an EqSpec. Precondition: if the LHS of the EqSpec
is mapped in the substitution, it is mapped to a type variable, not
a full type.
eqSpecPreds :: [EqSpec] -> ThetaType #
eqSpecPair :: EqSpec -> (TyVar, Type) #
eqSpecType :: EqSpec -> Type #
eqSpecTyVar :: EqSpec -> TyVar #
Haskell Source Bang
Bangs on data constructor arguments as the user wrote them in the source code.
(HsSrcBang _ SrcUnpack SrcLazy) and
(HsSrcBang _ SrcUnpack NoSrcStrict) (without StrictData) makes no sense, we
emit a warning (in checkValidDataCon) and treat it like
(HsSrcBang _ NoSrcUnpack SrcLazy)
Constructors
| HsSrcBang SourceText SrcUnpackedness SrcStrictness |
Instances
| Data HsSrcBang | |
Defined in DataCon Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSrcBang -> c HsSrcBang # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsSrcBang # toConstr :: HsSrcBang -> Constr # dataTypeOf :: HsSrcBang -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsSrcBang) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSrcBang) # gmapT :: (forall b. Data b => b -> b) -> HsSrcBang -> HsSrcBang # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSrcBang -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSrcBang -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang # | |
| Outputable HsSrcBang | |
data HsImplBang #
Haskell Implementation Bang
Bangs of data constructor arguments as generated by the compiler after consulting HsSrcBang, flags, etc.
Constructors
| HsLazy | Lazy field, or one with an unlifted type |
| HsStrict | Strict but not unpacked field |
| HsUnpack (Maybe Coercion) | Strict and unpacked field co :: arg-ty ~ product-ty HsBang |
Instances
| Data HsImplBang | |
Defined in DataCon Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplBang -> c HsImplBang # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsImplBang # toConstr :: HsImplBang -> Constr # dataTypeOf :: HsImplBang -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsImplBang) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsImplBang) # gmapT :: (forall b. Data b => b -> b) -> HsImplBang -> HsImplBang # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r # gmapQ :: (forall d. Data d => d -> u) -> HsImplBang -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplBang -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang # | |
| Outputable HsImplBang | |
Defined in DataCon | |
data SrcStrictness #
Source Strictness
What strictness annotation the user wrote
Constructors
| SrcLazy | Lazy, ie '~' |
| SrcStrict | Strict, ie |
| NoSrcStrict | no strictness annotation |
Instances
| Eq SrcStrictness | |
Defined in DataCon Methods (==) :: SrcStrictness -> SrcStrictness -> Bool # (/=) :: SrcStrictness -> SrcStrictness -> Bool # | |
| Data SrcStrictness | |
Defined in DataCon Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcStrictness -> c SrcStrictness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcStrictness # toConstr :: SrcStrictness -> Constr # dataTypeOf :: SrcStrictness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcStrictness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcStrictness) # gmapT :: (forall b. Data b => b -> b) -> SrcStrictness -> SrcStrictness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcStrictness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcStrictness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness # | |
| Binary SrcStrictness | |
Defined in DataCon Methods put_ :: BinHandle -> SrcStrictness -> IO () # put :: BinHandle -> SrcStrictness -> IO (Bin SrcStrictness) # get :: BinHandle -> IO SrcStrictness # | |
| Outputable SrcStrictness | |
Defined in DataCon | |
data SrcUnpackedness #
Source Unpackedness
What unpackedness the user requested
Constructors
| SrcUnpack | |
| SrcNoUnpack | |
| NoSrcUnpack | no unpack pragma |
Instances
| Eq SrcUnpackedness | |
Defined in DataCon Methods (==) :: SrcUnpackedness -> SrcUnpackedness -> Bool # (/=) :: SrcUnpackedness -> SrcUnpackedness -> Bool # | |
| Data SrcUnpackedness | |
Defined in DataCon Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcUnpackedness -> c SrcUnpackedness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcUnpackedness # toConstr :: SrcUnpackedness -> Constr # dataTypeOf :: SrcUnpackedness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcUnpackedness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcUnpackedness) # gmapT :: (forall b. Data b => b -> b) -> SrcUnpackedness -> SrcUnpackedness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcUnpackedness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcUnpackedness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness # | |
| Binary SrcUnpackedness | |
Defined in DataCon Methods put_ :: BinHandle -> SrcUnpackedness -> IO () # put :: BinHandle -> SrcUnpackedness -> IO (Bin SrcUnpackedness) # get :: BinHandle -> IO SrcUnpackedness # | |
| Outputable SrcUnpackedness | |
Defined in DataCon | |
data StrictnessMark #
Constructors
| MarkedStrict | |
| NotMarkedStrict |
Instances
| Outputable StrictnessMark | |
Defined in DataCon | |
isEqPrimPred :: PredType -> Bool #
isClassPred :: PredType -> Bool #
isEvVarType :: Type -> Bool #
roughMatchTcs :: [Type] -> [Maybe Name] #
hsOverLitNeedsParens :: PprPrec -> HsOverLit x -> Bool #
returns hsOverLitNeedsParens p olTrue if an overloaded literal
ol needs to be parenthesized under precedence p.
hsLitNeedsParens :: PprPrec -> HsLit x -> Bool #
returns hsLitNeedsParens p lTrue if a literal l needs
to be parenthesized under precedence p.
pmPprHsLit :: forall (x :: Pass). HsLit (GhcPass x) -> SDoc #
pmPprHsLit pretty prints literals and is used when pretty printing pattern match warnings. All are printed the same (i.e., without hashes if they are primitive and not wrapped in constructors if they are boxed). This happens mainly for too reasons: * We do not want to expose their internal representation * The warnings become too messy
pp_st_suffix :: SourceText -> SDoc -> SDoc -> SDoc #
convertLit :: ConvertIdX a b => HsLit a -> HsLit b #
Convert a literal from one index type to another, updating the annotations
according to the relevant Convertable instance
overLitType :: HsOverLit GhcTc -> Type #
Haskell Literal
Constructors
| HsChar (XHsChar x) Char | Character |
| HsCharPrim (XHsCharPrim x) Char | Unboxed character |
| HsString (XHsString x) FastString | String |
| HsStringPrim (XHsStringPrim x) ByteString | Packed bytes |
| HsInt (XHsInt x) IntegralLit | Genuinely an Int; arises from
|
| HsIntPrim (XHsIntPrim x) Integer | literal |
| HsWordPrim (XHsWordPrim x) Integer | literal |
| HsInt64Prim (XHsInt64Prim x) Integer | literal |
| HsWord64Prim (XHsWord64Prim x) Integer | literal |
| HsInteger (XHsInteger x) Integer Type | Genuinely an integer; arises only from TRANSLATION (overloaded literals are done with HsOverLit) |
| HsRat (XHsRat x) FractionalLit Type | Genuinely a rational; arises only from TRANSLATION (overloaded literals are done with HsOverLit) |
| HsFloatPrim (XHsFloatPrim x) FractionalLit | Unboxed Float |
| HsDoublePrim (XHsDoublePrim x) FractionalLit | Unboxed Double |
| XLit (XXLit x) |
Haskell Overloaded Literal
Constructors
| OverLit | |
Fields
| |
| XOverLit (XXOverLit p) | |
Instances
| Eq (XXOverLit p) => Eq (HsOverLit p) | |
| Ord (XXOverLit p) => Ord (HsOverLit p) | |
Defined in GHC.Hs.Lit | |
| OutputableBndrId p => Outputable (HsOverLit (GhcPass p)) | |
Constructors
| OverLitTc | |
Fields
| |
Instances
| Data OverLitTc | |
Defined in GHC.Hs.Lit Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverLitTc -> c OverLitTc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverLitTc # toConstr :: OverLitTc -> Constr # dataTypeOf :: OverLitTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverLitTc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverLitTc) # gmapT :: (forall b. Data b => b -> b) -> OverLitTc -> OverLitTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverLitTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverLitTc -> r # gmapQ :: (forall d. Data d => d -> u) -> OverLitTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverLitTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverLitTc -> m OverLitTc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitTc -> m OverLitTc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitTc -> m OverLitTc # | |
data OverLitVal #
Overloaded Literal Value
Constructors
| HsIntegral !IntegralLit | Integer-looking literals; |
| HsFractional !FractionalLit | Frac-looking literals |
| HsIsString !SourceText !FastString | String-looking literals |
Instances
| Eq OverLitVal | |
Defined in GHC.Hs.Lit | |
| Data OverLitVal | |
Defined in GHC.Hs.Lit Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverLitVal -> c OverLitVal # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverLitVal # toConstr :: OverLitVal -> Constr # dataTypeOf :: OverLitVal -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverLitVal) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverLitVal) # gmapT :: (forall b. Data b => b -> b) -> OverLitVal -> OverLitVal # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverLitVal -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverLitVal -> r # gmapQ :: (forall d. Data d => d -> u) -> OverLitVal -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverLitVal -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverLitVal -> m OverLitVal # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitVal -> m OverLitVal # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitVal -> m OverLitVal # | |
| Ord OverLitVal | |
Defined in GHC.Hs.Lit Methods compare :: OverLitVal -> OverLitVal -> Ordering # (<) :: OverLitVal -> OverLitVal -> Bool # (<=) :: OverLitVal -> OverLitVal -> Bool # (>) :: OverLitVal -> OverLitVal -> Bool # (>=) :: OverLitVal -> OverLitVal -> Bool # max :: OverLitVal -> OverLitVal -> OverLitVal # min :: OverLitVal -> OverLitVal -> OverLitVal # | |
| Outputable OverLitVal | |
Defined in GHC.Hs.Lit | |
absentLiteralOf :: TyCon -> Maybe Literal #
literalType :: Literal -> Type #
Find the Haskell Type the literal occupies
litIsLifted :: Literal -> Bool #
litFitsInChar :: Literal -> Bool #
litIsDupable :: DynFlags -> Literal -> Bool #
True if code space does not go bad if we duplicate this literal
litIsTrivial :: Literal -> Bool #
True if there is absolutely no penalty to duplicating the literal. False principally of strings.
"Why?", you say? I'm glad you asked. Well, for one duplicating strings would blow up code sizes. Not only this, it's also unsafe.
Consider a program that wants to traverse a string. One way it might do this is to first compute the Addr# pointing to the end of the string, and then, starting from the beginning, bump a pointer using eqAddr# to determine the end. For instance,
-- Given pointers to the start and end of a string, count how many zeros -- the string contains. countZeros :: Addr -> -> Int countZeros start end = go start 0 where go off n | off `addrEq#` end = n | otherwise = go (off `plusAddr#` 1) n' where n' | isTrue off 0 0#) = n + 1 | otherwise = n
Consider what happens if we considered strings to be trivial (and therefore
duplicable) and emitted a call like countZeros "hello"
. The beginning and end pointers do not belong to the same
string, meaning that an iteration like the above would blow up terribly.
This is what happened in #12757.plusAddr# 5)
Ultimately the solution here is to make primitive strings a bit more structured, ensuring that the compiler can't inline in ways that will break user code. One approach to this is described in #8472.
rubbishLit :: Literal #
A nonsense literal of type forall (a :: .TYPE UnliftedRep). a
nullAddrLit :: Literal #
double2FloatLit :: Literal -> Literal #
float2DoubleLit :: Literal -> Literal #
int2DoubleLit :: Literal -> Literal #
double2IntLit :: Literal -> Literal #
int2FloatLit :: Literal -> Literal #
float2IntLit :: Literal -> Literal #
int2CharLit :: Literal -> Literal #
char2IntLit :: Literal -> Literal #
narrow32WordLit :: Literal -> Literal #
narrow16WordLit :: Literal -> Literal #
narrow8WordLit :: Literal -> Literal #
narrow32IntLit :: Literal -> Literal #
narrow16IntLit :: Literal -> Literal #
narrow8IntLit :: Literal -> Literal #
narrowLit :: Integral a => Proxy a -> Literal -> Literal #
Narrow a literal number (unchecked result range)
int2WordLit :: DynFlags -> Literal -> Literal #
word2IntLit :: DynFlags -> Literal -> Literal #
isLitValue :: Literal -> Bool #
isLitValue_maybe :: Literal -> Maybe Integer #
inCharRange :: Char -> Bool #
inWordRange :: DynFlags -> Integer -> Bool #
inIntRange :: DynFlags -> Integer -> Bool #
mkLitNatural :: Integer -> Type -> Literal #
mkLitInteger :: Integer -> Type -> Literal #
mkLitString :: String -> Literal #
Creates a Literal of type Addr#, which is appropriate for passing to
e.g. some of the "error" functions in GHC.Err such as GHC.Err.runtimeError
mkLitDouble :: Rational -> Literal #
Creates a Literal of type Double#
mkLitFloat :: Rational -> Literal #
Creates a Literal of type Float#
mkLitWord64Wrap :: DynFlags -> Integer -> Literal #
Creates a Literal of type Word64#.
If the argument is out of the range, it is wrapped.
mkLitWord64 :: Integer -> Literal #
Creates a Literal of type Word64#
mkLitInt64Wrap :: DynFlags -> Integer -> Literal #
Creates a Literal of type Int64#.
If the argument is out of the range, it is wrapped.
mkLitInt64 :: Integer -> Literal #
Creates a Literal of type Int64#
mkLitWordWrap :: DynFlags -> Integer -> Literal #
Creates a Literal of type Word#.
If the argument is out of the (target-dependent) range, it is wrapped.
See Note [WordInt underflowoverflow]
mkLitIntWrap :: DynFlags -> Integer -> Literal #
Creates a Literal of type Int#.
If the argument is out of the (target-dependent) range, it is wrapped.
See Note [WordInt underflowoverflow]
mkLitNumber :: DynFlags -> LitNumType -> Integer -> Type -> Literal #
Create a numeric Literal of the given type
litNumCheckRange :: DynFlags -> LitNumType -> Integer -> Bool #
Check that a given number is in the range of a numeric literal
mkLitNumberWrap :: DynFlags -> LitNumType -> Integer -> Type -> Literal #
Create a numeric Literal of the given type
litNumIsSigned :: LitNumType -> Bool #
Indicate if a numeric literal type supports negative numbers
So-called Literals are one of:
- An unboxed numeric literal or floating-point literal which is presumed
to be surrounded by appropriate constructors (
Int#, etc.), so that the overall thing makes sense.
We maintain the invariant that the Integer in the LitNumber
constructor is actually in the (possibly target-dependent) range.
The mkLit{Int,Word}*Wrap smart constructors ensure this by applying
the target machine's wrapping semantics. Use these in situations
where you know the wrapping semantics are correct.
- The literal derived from the label mentioned in a "foreign label"
declaration (
LitLabel) - A
LitRubbishto be used in place of values ofUnliftedRep(i.e. 'MutVar#') when the the value is never used. - A character
- A string
- The NULL pointer
Constructors
| LitChar Char |
|
| LitNumber !LitNumType !Integer Type | Any numeric literal that can be internally represented with an Integer. See Note [Types of LitNumbers] below for the Type field. |
| LitString ByteString | A string-literal: stored and emitted
UTF-8 encoded, we'll arrange to decode it
at runtime. Also emitted with a |
| LitNullAddr | The |
| LitRubbish | A nonsense value, used when an unlifted
binding is absent and has type
|
| LitFloat Rational |
|
| LitDouble Rational |
|
| LitLabel FastString (Maybe Int) FunctionOrData | A label literal. Parameters: 1) The name of the symbol mentioned in the declaration 2) The size (in bytes) of the arguments
the label expects. Only applicable with
3) Flag indicating whether the symbol references a function or a data |
Instances
| Eq Literal | |
| Data Literal | |
Defined in Literal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Literal -> c Literal # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Literal # toConstr :: Literal -> Constr # dataTypeOf :: Literal -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Literal) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal) # gmapT :: (forall b. Data b => b -> b) -> Literal -> Literal # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r # gmapQ :: (forall d. Data d => d -> u) -> Literal -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Literal -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Literal -> m Literal # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal # | |
| Ord Literal | Needed for the |
| Binary Literal | |
| Outputable Literal | |
data LitNumType #
Numeric literal type
Constructors
| LitNumInteger |
|
| LitNumNatural |
|
| LitNumInt |
|
| LitNumInt64 |
|
| LitNumWord |
|
| LitNumWord64 |
|
Instances
Arguments
| :: 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.)
classifiesTypeWithValues :: Kind -> Bool #
Does this classify a type allowed to have values? Responds True to things like *, #, TYPE Lifted, TYPE v, Constraint.
True of any sub-kind of OpenTypeKind
isKindLevPoly :: Kind -> Bool #
Tests whether the given kind (which should look like TYPE x)
is something other than a constructor tree (that is, constructors at every node).
E.g. True of TYPE k, TYPE (F Int)
False of TYPE 'LiftedRep
isConstraintKindCon :: TyCon -> Bool #
splitVisVarsOfTypes :: [Type] -> Pair TyCoVarSet #
splitVisVarsOfType :: Type -> Pair TyCoVarSet #
Retrieve the free variables in this type, splitting them based on whether they are used visibly or invisibly. Invisible ones come first.
synTyConResKind :: TyCon -> Kind #
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.
resultIsLevPoly :: Type -> Bool #
Looking past all pi-types, is the end result potentially levity polymorphic? Example: True for (forall r (a :: TYPE r). String -> a) Example: False for (forall r1 r2 (a :: TYPE r1) (b :: TYPE r2). a -> b -> Type)
isTypeLevPoly :: Type -> Bool #
Returns True if a type is levity polymorphic. Should be the same as (isKindLevPoly . typeKind) but much faster. Precondition: The type has kind (TYPE blah)
tcReturnsConstraintKind :: Kind -> Bool #
tcIsRuntimeTypeKind :: Kind -> Bool #
Is this kind equivalent to TYPE r (for some unknown r)?
This considers Constraint to be distinct from *.
tcIsLiftedTypeKind :: Kind -> Bool #
Is this kind equivalent to *?
This considers Constraint to be distinct from *. For a version that
treats them as the same type, see isLiftedTypeKind.
tcIsConstraintKind :: Kind -> Bool #
tcTypeKind :: HasDebugCallStack => Type -> Kind #
nonDetCmpTc :: TyCon -> TyCon -> Ordering #
nonDetCmpTypes :: [Type] -> [Type] -> Ordering #
nonDetCmpType :: Type -> Type -> Ordering #
eqTypes :: [Type] -> [Type] -> Bool #
Type equality on lists of types, looking through type synonyms but not newtypes.
eqTypeX :: RnEnv2 -> Type -> Type -> Bool #
Compare types with respect to a (presumably) non-empty RnEnv2.
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 CoreSyn.) 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]
isPrimitiveType :: Type -> Bool #
Returns true of types that are opaque to Haskell.
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 levity-polymorphic types.
isDataFamilyAppType :: Type -> Bool #
Check whether a type is a data family type
See Type for what an algebraic type is. Should only be applied to types, as opposed to e.g. partially saturated type constructors
isUnboxedSumType :: Type -> Bool #
isUnboxedTupleType :: Type -> Bool #
getRuntimeRep :: HasDebugCallStack => Type -> Type #
Extract the RuntimeRep classifier of a type. For instance,
getRuntimeRep_maybe Int = LiftedRep. Panics if this is not possible.
getRuntimeRep_maybe :: HasDebugCallStack => Type -> Maybe Type #
Extract the RuntimeRep classifier of a type. For instance,
getRuntimeRep_maybe Int = LiftedRep. Returns Nothing if this is not
possible.
dropRuntimeRepArgs :: [Type] -> [Type] #
Drops prefix of RuntimeRep constructors in TyConApps. Useful for e.g.
dropping 'LiftedRep arguments of unboxed tuple TyCon applications:
isRuntimeRepKindedTy :: Type -> Bool #
Is this a type of kind RuntimeRep? (e.g. LiftedRep)
mightBeUnliftedType :: Type -> Bool #
isUnliftedType :: HasDebugCallStack => Type -> Bool #
See Type for what an unlifted type is.
Panics on levity polymorphic types; See mightBeUnliftedType for
a more approximate predicate that behaves better in the presence of
levity polymorphism.
isLiftedType_maybe :: HasDebugCallStack => Type -> Maybe Bool #
Returns Just True if this type is surely lifted, Just False if it is surely unlifted, Nothing if we can't be sure (i.e., it is levity polymorphic), and panics if the kind does not have the shape TYPE r.
isCoVarType :: Type -> Bool #
isFamFreeTy :: Type -> Bool #
coAxNthLHS :: forall (br :: BranchFlag). CoAxiom br -> Int -> Type #
Get the type on the LHS of a coercion induced by a type/data family instance.
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)
closeOverKindsDSet :: DTyVarSet -> DTyVarSet #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministic set.
closeOverKindsList :: [TyVar] -> [TyVar] #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministically ordered list.
closeOverKindsFV :: [TyVar] -> FV #
Given a list of tyvars returns a deterministic FV computation that returns the given tyvars with the kind variables free in the kinds of the given tyvars.
closeOverKinds :: TyVarSet -> TyVarSet #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a non-deterministic set.
binderRelevantType_maybe :: TyCoBinder -> Maybe Type #
Extract a relevant type, if there is one.
tyBinderType :: TyBinder -> Type #
tyCoBinderType :: TyCoBinder -> Type #
isAnonTyCoBinder :: TyCoBinder -> Bool #
Does this binder bind a variable that is not erased? Returns
True for anonymous binders.
mkAnonBinder :: AnonArgFlag -> Type -> TyCoBinder #
Make an anonymous binder
appTyArgFlags :: Type -> [Type] -> [ArgFlag] #
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 appTyArgFlags comes in handy,
since f Type Bool would be represented in Core using AppTys.
(See also #15792).
tyConArgFlags :: TyCon -> [Type] -> [ArgFlag] #
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 tyConArgFlags 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.
partitionInvisibles :: [(a, ArgFlag)] -> ([a], [a]) #
Given a list of things paired with their visibilities, partition the things into (invisible things, visible things).
filterOutInferredTypes :: TyCon -> [Type] -> [Type] #
filterOutInvisibleTypes :: TyCon -> [Type] -> [Type] #
splitPiTysInvisibleN :: Int -> Type -> ([TyCoBinder], Type) #
splitPiTysInvisible :: Type -> ([TyCoBinder], Type) #
invisibleTyBndrCount :: Type -> Int #
splitForAllVarBndrs :: Type -> ([TyCoVarBinder], Type) #
Like splitPiTys but split off only named binders
and returns TyCoVarBinders rather than TyCoBinders
splitPiTys :: Type -> ([TyCoBinder], Type) #
Split off all TyCoBinders to a type, splitting both proper foralls and functions
splitPiTy :: Type -> (TyCoBinder, Type) #
Takes a forall type apart, or panics
splitPiTy_maybe :: Type -> Maybe (TyCoBinder, Type) #
Attempts to take a forall type apart; works with proper foralls and functions
splitForAllTy_co_maybe :: Type -> Maybe (TyCoVar, Type) #
Like splitForAllTy_maybe, but only returns Just if it is a covar binder.
splitForAllTy_ty_maybe :: Type -> Maybe (TyCoVar, Type) #
Like splitForAllTy_maybe, but only returns Just if it is a tyvar binder.
splitForAllTy_maybe :: Type -> Maybe (TyCoVar, Type) #
Attempts to take a forall type apart, but only if it's a proper forall, with a named binder
dropForAlls :: Type -> Type #
Drops all ForAllTys
splitForAllTy :: Type -> (TyCoVar, Type) #
Take a forall type apart, or panics if that is not possible.
isForAllTy_co :: Type -> Bool #
Like isForAllTy, but returns True only if it is a covar binder
isForAllTy_ty :: Type -> Bool #
Like isForAllTy, but returns True only if it is a tyvar binder
isForAllTy :: Type -> Bool #
Checks whether this is a proper forall (with a named binder)
splitForAllTysSameVis :: ArgFlag -> Type -> ([TyCoVar], Type) #
Like splitForAllTys, but only splits a ForAllTy if
is sameVis argf supplied_argfTrue, where argf is the visibility
of the ForAllTy's binder and supplied_argf is the visibility provided
as an argument to this function.
splitForAllTys :: 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.
Arguments
| :: [TyVar] | binders |
| -> TyCoVarSet | free variables of result |
| -> [TyConBinder] |
Given a list of type-level vars and the free vars of a result kind, makes TyCoBinders, 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.
mkLamType :: Var -> Type -> Type #
Makes a (->) type or an implicit forall type, depending
on whether it is given a type variable or a term variable.
This is used, for example, when producing the type of a lambda.
Always uses Inferred binders.
mkVisForAllTys :: [TyVar] -> Type -> Type #
Like mkForAllTys, but assumes all variables are dependent and visible
mkSpecForAllTys :: [TyVar] -> Type -> Type #
Like mkForAllTys, but assumes all variables are dependent and
Specified, a common case
mkSpecForAllTy :: TyVar -> Type -> Type #
Like mkForAllTy, but assumes the variable is dependent and Specified,
a common case
mkInvForAllTys :: [TyVar] -> Type -> Type #
Like mkTyCoInvForAllTys, but tvs should be a list of tyvar
mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type #
Like mkForAllTys, but assumes all variables are dependent and
Inferred, a common case
mkInvForAllTy :: TyVar -> Type -> Type #
Like mkTyCoInvForAllTy, but tv should be a tyvar
stripCoercionTy :: Type -> Coercion #
isCoercionTy_maybe :: Type -> Maybe Coercion #
mkCoercionTy :: Coercion -> Type #
discardCast :: Type -> Type #
Drop the cast on a type, if any. If there is no cast, just return the original type. This is rarely what you want. The CastTy data constructor (in TyCoRep) has the invariant that another CastTy is not inside. See the data constructor for a full description of this invariant. Since CastTy cannot be nested, the result of discardCast cannot be a CastTy.
tyConBindersTyCoBinders :: [TyConBinder] -> [TyCoBinder] #
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.
splitListTyConApp_maybe :: Type -> Maybe Type #
Attempts to tease a list type apart and gives the type of the elements if successful (looks through type synonyms)
repSplitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #
Like splitTyConApp_maybe, but doesn't look through synonyms. This
assumes the synonyms have already been dealt with.
Moreover, for a FunTy, it only succeeds if the argument types have enough info to extract the runtime-rep arguments that the funTyCon requires. This will usually be true; but may be temporarily false during canonicalization: see Note [FunTy and decomposing tycon applications] in TcCanonical
tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type]) #
Split a type constructor application into its type constructor and
applied types. Note that this may fail 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). Consequently, you may need to zonk your
type before using this function.
If you only need the TyCon, consider using tcTyConAppTyCon_maybe.
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
tyConAppArgN :: Int -> Type -> Type #
tyConAppArgs :: Type -> [Type] #
tyConAppArgs_maybe :: Type -> Maybe [Type] #
The same as snd . splitTyConApp
tyConAppTyCon :: Type -> TyCon #
tyConAppTyCon_maybe :: Type -> Maybe TyCon #
The same as fst . splitTyConApp
tyConAppTyConPicky_maybe :: Type -> Maybe TyCon #
Retrieve the tycon heading this type, if there is one. Does not look through synonyms.
mkTyConApp :: TyCon -> [Type] -> Type #
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 undefineds 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
funResultTy :: Type -> Type #
Extract the function result type and panic if that is not possible
splitFunTys :: Type -> ([Type], Type) #
splitFunTy_maybe :: Type -> Maybe (Type, Type) #
Attempts to extract the argument and result types from a type
splitFunTy :: Type -> (Type, Type) #
Attempts to extract the argument and result types from a type, and
panics if that is not possible. See also splitFunTy_maybe
pprUserTypeErrorTy :: Type -> SDoc #
Render a type corresponding to a user type error into a SDoc.
userTypeError_maybe :: Type -> Maybe Type #
Is this type a custom user error? If so, give us the kind and the error message.
isStrLitTy :: Type -> Maybe FastString #
Is this a symbol literal. We also look through type synonyms.
mkStrLitTy :: FastString -> Type #
isNumLitTy :: Type -> Maybe Integer #
Is this a numeric literal. We also look through type synonyms.
mkNumLitTy :: Integer -> Type #
repSplitAppTys :: HasDebugCallStack => Type -> (Type, [Type]) #
Like splitAppTys, but doesn't look through type synonyms
splitAppTys :: 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.
splitAppTy :: Type -> (Type, Type) #
Attempts to take a type application apart, as in splitAppTy_maybe,
and panics if this is not possible
tcRepSplitAppTy_maybe :: Type -> Maybe (Type, Type) #
Does the AppTy split as in tcSplitAppTy_maybe, but assumes that
any coreView stuff is already done. Refuses to look through (c => t)
repSplitAppTy_maybe :: HasDebugCallStack => Type -> Maybe (Type, Type) #
Does the AppTy split as in splitAppTy_maybe, but assumes that
any Core view stuff is already done
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!
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
getTyVar :: String -> 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
mapCoercion :: Monad m => TyCoMapper env m -> env -> Coercion -> m Coercion #
isRuntimeRepVar :: TyVar -> Bool #
Is a tyvar of type RuntimeRep?
isUnliftedRuntimeRep :: Type -> Bool #
isUnliftedTypeKind :: Kind -> Bool #
Returns True if the kind classifies unlifted types and False otherwise. Note that this returns False for levity-polymorphic kinds, which may be specialized to a kind that classifies unlifted types.
isLiftedRuntimeRep :: Type -> Bool #
kindRep_maybe :: HasDebugCallStack => Kind -> Maybe Type #
Given a kind (TYPE rr), extract its RuntimeRep classifier rr.
For example, kindRep_maybe * = Just LiftedRep
Returns Nothing if the kind is not of form (TYPE rr)
Treats * and Constraint as the same
kindRep :: HasDebugCallStack => Kind -> Type #
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
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
data TyCoMapper env (m :: Type -> Type) #
This describes how a "map" operation over a type/coercion should behave
Constructors
| TyCoMapper | |
Fields
| |
cloneTyVarBndrs :: TCvSubst -> [TyVar] -> UniqSupply -> (TCvSubst, [TyVar]) #
substVarBndrs :: HasCallStack => TCvSubst -> [TyCoVar] -> (TCvSubst, [TyCoVar]) #
substVarBndr :: HasCallStack => TCvSubst -> TyCoVar -> (TCvSubst, TyCoVar) #
substTyVarBndrs :: HasCallStack => TCvSubst -> [TyVar] -> (TCvSubst, [TyVar]) #
substTyVarBndr :: HasCallStack => TCvSubst -> TyVar -> (TCvSubst, TyVar) #
substCoUnchecked :: TCvSubst -> 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.
substTyVars :: TCvSubst -> [TyVar] -> [Type] #
substTyVar :: TCvSubst -> TyVar -> Type #
substThetaUnchecked :: TCvSubst -> 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.
substTheta :: HasCallStack => TCvSubst -> ThetaType -> ThetaType #
Substitute within a ThetaType
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substTysUnchecked :: TCvSubst -> [Type] -> [Type] #
Substitute within several Types 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.
substTys :: HasCallStack => TCvSubst -> [Type] -> [Type] #
Substitute within several Types
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substTyUnchecked :: TCvSubst -> 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.
substTy :: HasCallStack => TCvSubst -> Type -> Type #
Substitute within a Type
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substTyAddInScope :: TCvSubst -> 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].
substTysWith :: [TyVar] -> [Type] -> [Type] -> [Type] #
Type substitution, see zipTvSubst
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.
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.
substTyWith :: HasCallStack => [TyVar] -> [Type] -> Type -> Type #
Type substitution, see zipTvSubst
zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv #
zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv #
mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst #
Generates the in-scope set for the TCvSubst from the types in the
incoming environment. No CoVars, please!
zipTCvSubst :: HasDebugCallStack => [TyCoVar] -> [Type] -> TCvSubst #
zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> TCvSubst #
Generates the in-scope set for the TCvSubst from the types in the incoming
environment. No CoVars, please!
unionTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst #
extendTvSubstBinderAndInScope :: TCvSubst -> TyCoBinder -> Type -> TCvSubst #
extendTCvInScopeSet :: TCvSubst -> VarSet -> TCvSubst #
extendTCvInScopeList :: TCvSubst -> [Var] -> TCvSubst #
extendTCvInScope :: TCvSubst -> Var -> TCvSubst #
zapTCvSubst :: TCvSubst -> TCvSubst #
setTvSubstEnv :: TCvSubst -> TvSubstEnv -> TCvSubst #
notElemTCvSubst :: Var -> TCvSubst -> Bool #
getTCvSubstRangeFVs :: TCvSubst -> VarSet #
Returns the free variables of the types in the range of a substitution as a non-deterministic set.
getTCvInScope :: TCvSubst -> InScopeSet #
getTvSubstEnv :: TCvSubst -> TvSubstEnv #
mkTCvSubst :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> TCvSubst #
isEmptyTCvSubst :: TCvSubst -> Bool #
mkEmptyTCvSubst :: InScopeSet -> TCvSubst #
composeTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst #
Composes two substitutions, applying the second one provided first, like in function composition.
composeTCvSubstEnv :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv) #
(compose env1 env2)(x) is env1(env2(x)); i.e. apply env2 then env1.
It assumes that both are idempotent.
Typically, env1 is the refinement to a base substitution env2
Type & coercion substitution
The following invariants must hold of a TCvSubst:
- The in-scope set is needed only to guide the generation of fresh uniques
- In particular, the kind of the type variables in the in-scope set is not relevant
- The substitution is only applied ONCE! This is because in general such application will not reach a fixed point.
Constructors
| TCvSubst InScopeSet TvSubstEnv CvSubstEnv |
pprTypeApp :: TyCon -> [Type] -> SDoc #
pprForAll :: [TyCoVarBinder] -> SDoc #
pprThetaArrowTy :: ThetaType -> SDoc #
pprParendType :: Type -> SDoc #
tidyTopType :: Type -> Type #
Calls tidyType on a top-level type (i.e. with an empty tidying environment)
tidyOpenTypes :: TidyEnv -> [Type] -> (TidyEnv, [Type]) #
Grabs the free type variables, tidies them
and then uses tidyType to work over the type itself
tidyTyCoVarOcc :: TidyEnv -> TyCoVar -> TyCoVar #
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
tidyFreeTyCoVars :: TidyEnv -> [TyCoVar] -> TidyEnv #
Add the free TyVars to the env in tidy form,
so that we can tidy the type they are free in
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.
tyCoVarsOfTypesWellScoped :: [Type] -> [TyVar] #
Get the free vars of types in scoped order
tyCoVarsOfTypeWellScoped :: Type -> [TyVar] #
Get the free vars of a type in scoped order
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 RnTypes
noFreeVarsOfType :: Type -> Bool #
Returns True if this type has no free variables. Should be the same as isEmptyVarSet . tyCoVarsOfType, but faster in the non-forall case.
coVarsOfTypes :: [Type] -> TyCoVarSet #
coVarsOfType :: Type -> CoVarSet #
tyCoFVsVarBndr :: Var -> FV -> FV #
tyCoFVsVarBndrs :: [Var] -> FV -> FV #
tyCoFVsBndr :: TyCoVarBinder -> FV -> 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 FV.
Eta-expanded because that makes it run faster (apparently) See Note [FV eta expansion] in FV for explanation.
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 FV.
tyCoVarsOfTypes :: [Type] -> TyCoVarSet #
tyCoVarsOfType :: Type -> TyCoVarSet #
doubleX8PrimTy :: Type #
floatX16PrimTy :: Type #
doubleX4PrimTy :: Type #
floatX8PrimTy :: Type #
doubleX2PrimTy :: Type #
floatX4PrimTy :: Type #
word64X8PrimTy :: Type #
word32X16PrimTy :: Type #
word16X32PrimTy :: Type #
word8X64PrimTy :: Type #
word64X4PrimTy :: Type #
word32X8PrimTy :: Type #
word16X16PrimTy :: Type #
word8X32PrimTy :: Type #
word64X2PrimTy :: Type #
word32X4PrimTy :: Type #
word16X8PrimTy :: Type #
word8X16PrimTy :: Type #
int64X8PrimTy :: Type #
int32X16PrimTy :: Type #
int16X32PrimTy :: Type #
int8X64PrimTy :: Type #
int64X4PrimTy :: Type #
int32X8PrimTy :: Type #
int16X16PrimTy :: Type #
int8X32PrimTy :: Type #
int64X2PrimTy :: Type #
int32X4PrimTy :: Type #
int16X8PrimTy :: Type #
int8X16PrimTy :: Type #
threadIdPrimTy :: Type #
mkWeakPrimTy :: Type -> Type #
weakPrimTyCon :: TyCon #
bcoPrimTyCon :: TyCon #
compactPrimTy :: Type #
mkStableNamePrimTy :: Type -> Type #
mkStablePtrPrimTy :: Type -> Type #
mkTVarPrimTy :: Type -> Type -> Type #
tVarPrimTyCon :: TyCon #
mkMVarPrimTy :: Type -> Type -> Type #
mVarPrimTyCon :: TyCon #
mkMutVarPrimTy :: Type -> Type -> Type #
mkSmallMutableArrayPrimTy :: Type -> Type -> Type #
mkMutableArrayArrayPrimTy :: Type -> Type #
mkMutableByteArrayPrimTy :: Type -> Type #
mkMutableArrayPrimTy :: Type -> Type -> Type #
mkSmallArrayPrimTy :: Type -> Type #
byteArrayPrimTy :: Type #
mkArrayPrimTy :: Type -> Type #
arrayPrimTyCon :: TyCon #
equalityTyCon :: Role -> TyCon #
Given a Role, what TyCon is the type of equality predicates at that role?
eqPrimTyCon :: TyCon #
proxyPrimTyCon :: TyCon #
mkProxyPrimTy :: Type -> Type -> Type #
voidPrimTyCon :: TyCon #
voidPrimTy :: Type #
realWorldTy :: Type #
realWorldTyCon :: TyCon #
statePrimTyCon :: TyCon #
mkStatePrimTy :: Type -> Type #
doublePrimTy :: Type #
floatPrimTyCon :: TyCon #
floatPrimTy :: Type #
addrPrimTyCon :: TyCon #
addrPrimTy :: Type #
word64PrimTy :: Type #
word32PrimTy :: Type #
word16PrimTy :: Type #
word8PrimTyCon :: TyCon #
word8PrimTy :: Type #
wordPrimTyCon :: TyCon #
wordPrimTy :: Type #
int64PrimTyCon :: TyCon #
int64PrimTy :: Type #
int32PrimTyCon :: TyCon #
int32PrimTy :: Type #
int16PrimTyCon :: TyCon #
int16PrimTy :: Type #
int8PrimTyCon :: TyCon #
int8PrimTy :: Type #
intPrimTyCon :: TyCon #
charPrimTyCon :: TyCon #
charPrimTy :: Type #
primRepToRuntimeRep :: PrimRep -> Type #
mkPrimTyConName :: FastString -> Unique -> TyCon -> Name #
tYPETyConName :: Name #
The (->) type constructor.
(->) :: forall (rep1 :: RuntimeRep) (rep2 :: RuntimeRep).
TYPE rep1 -> TYPE rep2 -> *
funTyConName :: Name #
openBetaTy :: Type #
openAlphaTy :: Type #
openBetaTyVar :: TyVar #
openAlphaTyVar :: TyVar #
runtimeRep2Ty :: Type #
runtimeRep1Ty :: Type #
alphaTysUnliftedRep :: [Type] #
alphaTyVarsUnliftedRep :: [TyVar] #
deltaTyVar :: TyVar #
gammaTyVar :: TyVar #
alphaTyVar :: TyVar #
alphaTyVars :: [TyVar] #
mkTemplateAnonTyConBinders :: [Kind] -> [TyConBinder] #
mkTemplateKindTyConBinders :: [Kind] -> [TyConBinder] #
mkTemplateTyConBinders :: [Kind] -> ([Kind] -> [Kind]) -> [TyConBinder] #
mkTemplateTyVars :: [Kind] -> [TyVar] #
mkTemplateTyVarsFrom :: Int -> [Kind] -> [TyVar] #
mkTemplateKindVars :: [Kind] -> [TyVar] #
exposedPrimTyCons :: [TyCon] #
unexposedPrimTyCons :: [TyCon] #
primTyCons :: [TyCon] #
provSize :: UnivCoProvenance -> Int #
coercionSize :: Coercion -> Int #
setCoHoleCoVar :: CoercionHole -> CoVar -> CoercionHole #
coHoleCoVar :: CoercionHole -> CoVar #
Create the plain type constructor type which has been applied to no type arguments at all.
mkPiTys :: [TyCoBinder] -> Type -> Type #
mkPiTy :: TyCoBinder -> Type -> Type #
mkForAllTys :: [TyCoVarBinder] -> Type -> Type #
Wraps foralls over the type using the provided TyCoVars from left to right
mkInvisFunTys :: [Type] -> Type -> Type #
Make nested arrow types
mkVisFunTys :: [Type] -> Type -> Type #
Make nested arrow types
mkInvisFunTy :: Type -> Type -> Type infixr 3 #
mkVisFunTy :: Type -> Type -> Type infixr 3 #
mkTyCoVarTys :: [TyCoVar] -> [Type] #
mkTyCoVarTy :: TyCoVar -> Type #
mkTyVarTys :: [TyVar] -> [Type] #
isTyBinder :: TyCoBinder -> Bool #
If its a named binder, is the binder a tyvar? Returns True for nondependent binder. This check that we're really returning a *Ty*Binder (as opposed to a coercion binder). That way, if/when we allow coercion quantification in more places, we'll know we missed updating some function.
isNamedBinder :: TyCoBinder -> Bool #
isVisibleBinder :: TyCoBinder -> Bool #
Does this binder bind a visible argument?
isInvisibleBinder :: TyCoBinder -> Bool #
Does this binder bind an invisible argument?
delBinderVar :: VarSet -> TyCoVarBinder -> VarSet #
Remove the binder's variable from the set, if the binder has a variable.
tyThingCategory :: TyThing -> String #
pprTyThingCategory :: TyThing -> SDoc #
pprShortTyThing :: TyThing -> SDoc #
type KindOrType = Type #
The key representation of types within the compiler
A type labeled KnotTied might have knot-tied tycons in it. See
Note [Type checking recursive type and class declarations] in
TcTyClsDecls
type TyBinder = TyCoBinder #
TyBinder is like TyCoBinder, but there can only be TyVarBinder
in the Named field.
type KindCoercion = CoercionN #
type MCoercionR = MCoercion #
data CoercionHole #
A coercion to be filled in by the type-checker. See Note [Coercion holes]
Instances
| Data CoercionHole | |
Defined in TyCoRep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CoercionHole -> c CoercionHole # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CoercionHole # toConstr :: CoercionHole -> Constr # dataTypeOf :: CoercionHole -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CoercionHole) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoercionHole) # gmapT :: (forall b. Data b => b -> b) -> CoercionHole -> CoercionHole # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CoercionHole -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CoercionHole -> r # gmapQ :: (forall d. Data d => d -> u) -> CoercionHole -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CoercionHole -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole # | |
| Outputable CoercionHole | |
Defined in TyCoRep | |
isCoercionTy :: Type -> Bool #
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 TyCoRep
piResultTy :: HasDebugCallStack => Type -> Type -> Type #
eqType :: Type -> Type -> Bool #
Type equality on source types. Does not look through newtypes or
PredTypes, but it does look through type synonyms.
This first checks that the kinds of the types are equal and then
checks whether the types are equal, ignoring casts and coercions.
(The kind check is a recursive call, but since all kinds have type
Type, there is no need to check the types of kinds.)
See also Note [Non-trivial definitional equality] in TyCoRep.
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 considers Constraint to be a synonym of TYPE LiftedRep.
By being non-recursive and inlined, this case analysis gets efficiently joined onto the case analysis that the caller is already doing
tcView :: Type -> Maybe Type #
Gives the typechecker view of a type. This unwraps synonyms but
leaves Constraint alone. c.f. coreView, which turns Constraint into
TYPE LiftedRep. Returns Nothing if no unwrapping happens.
See also Note [coreView vs tcView]
isRuntimeRepTy :: Type -> Bool #
Is this the type RuntimeRep?
isLiftedTypeKind :: Kind -> Bool #
This version considers Constraint to be the same as *. Returns True if the argument is equivalent to Type/Constraint and False otherwise. See Note [Kind Constraint and kind Type]
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
tyConSkolem :: TyCon -> Bool #
Returns whether or not this TyCon is definite, or a hole
that may be filled in at some later point. See Note [Skolem abstract data]
checkRecTc :: RecTcChecker -> TyCon -> Maybe RecTcChecker #
setRecTcMaxBound :: Int -> RecTcChecker -> RecTcChecker #
Change the upper bound for the number of times a RecTcChecker is allowed
to encounter each TyCon.
The default upper bound (100) for the number of times a RecTcChecker is
allowed to encounter each TyCon.
Initialise a RecTcChecker with defaultRecTcMaxBound.
pprPromotionQuote :: TyCon -> SDoc #
tcFlavourIsOpen :: TyConFlavour -> Bool #
Is this flavour of TyCon an open type family or a data family?
tyConFlavour :: TyCon -> TyConFlavour #
mkTyConTagMap :: TyCon -> NameEnv ConTag #
tyConRuntimeRepInfo :: TyCon -> RuntimeRepInfo #
Extract any RuntimeRepInfo from this TyCon
tyConFamInst_maybe :: TyCon -> Maybe (TyCon, [Type]) #
If this TyCon is that of a data family instance, return the family in question
and the instance types. Otherwise, return Nothing
tyConFamInstSig_maybe :: TyCon -> Maybe (TyCon, [Type], CoAxiom Unbranched) #
isFamInstTyCon :: TyCon -> Bool #
Is this TyCon that for a data family instance?
tyConClass_maybe :: TyCon -> Maybe Class #
If this TyCon is that for a class instance, return the class it is for.
Otherwise returns Nothing
isClassTyCon :: TyCon -> Bool #
Is this TyCon that for a class instance?
famTyConFlav_maybe :: TyCon -> Maybe FamTyConFlav #
Extract the flavour of a type family (with all the extra information that it carries)
synTyConRhs_maybe :: TyCon -> Maybe Type #
Extract the information pertaining to the right hand side of a type synonym
(type) declaration.
synTyConDefn_maybe :: TyCon -> Maybe ([TyVar], Type) #
Extract the TyVars bound by a vanilla type synonym
and the corresponding (unsubstituted) right hand side.
tyConStupidTheta :: TyCon -> [PredType] #
Find the "stupid theta" of the TyCon. A "stupid theta" is the context
to the left of an algebraic type declaration, e.g. Eq a in the declaration
data Eq a => T a ...
newTyConDataCon_maybe :: TyCon -> Maybe DataCon #
newTyConCo :: TyCon -> CoAxiom Unbranched #
newTyConCo_maybe :: TyCon -> Maybe (CoAxiom Unbranched) #
newTyConEtadRhs :: TyCon -> ([TyVar], Type) #
newTyConEtadArity :: TyCon -> Int #
The number of type parameters that need to be passed to a newtype to resolve it. May be less than in the definition if it can be eta-contracted.
newTyConRhs :: TyCon -> ([TyVar], Type) #
tyConRoles :: TyCon -> [Role] #
Get the list of roles for the type parameters of a TyCon
tyConFamilyResVar_maybe :: TyCon -> Maybe Name #
Extract type variable naming the result of injective type family
algTyConRhs :: TyCon -> AlgTyConRhs #
Extract an AlgTyConRhs with information about data constructors from an
algebraic or tuple TyCon. Panics for any other sort of TyCon
tyConFamilySize :: TyCon -> Int #
tyConSingleDataCon :: TyCon -> DataCon #
tyConSingleDataCon_maybe :: TyCon -> Maybe DataCon #
If the given TyCon has a single data constructor, i.e. it is a data
type with one alternative, a tuple type or a newtype then that constructor
is returned. If the TyCon has more than one constructor, or represents a
primitive or function type constructor then Nothing is returned. In any
other case, the function panics
tyConDataCons_maybe :: TyCon -> Maybe [DataCon] #
tyConDataCons :: TyCon -> [DataCon] #
As tyConDataCons_maybe, but returns the empty list of constructors if no
constructors could be found
isTyConWithSrcDataCons :: TyCon -> Bool #
Check if the tycon actually refers to a proper `data` or `newtype` with user defined constructors rather than one from a class or other construction.
Arguments
| :: TyCon | |
| -> [tyco] | Arguments to |
| -> Maybe ([(TyVar, tyco)], Type, [tyco]) | Returns a |
Expand a type synonym application, if any
isTcLevPoly :: TyCon -> Bool #
Could this TyCon ever be levity-polymorphic when fully applied? True is safe. False means we're sure. Does only a quick check based on the TyCon's category. Precondition: The fully-applied TyCon has kind (TYPE blah)
setTcTyConKind :: TyCon -> Kind -> TyCon #
tyConCType_maybe :: TyCon -> Maybe CType #
isImplicitTyCon :: TyCon -> Bool #
Identifies implicit tycons that, in particular, do not go into interface files (because they are implicitly reconstructed when the interface is read).
Note that:
- Associated families are implicit, as they are re-constructed from the class declaration in which they reside, and
- Family instances are not implicit as they represent the instance body
(similar to a
dfundoes that for a class instance). - Tuples are implicit iff they have a wired-in name (namely: boxed and unboxed tuples are wired-in and implicit, but constraint tuples are not)
isLiftedTypeKindTyConName :: Name -> Bool #
isKindTyCon :: TyCon -> Bool #
Is this tycon really meant for use at the kind level? That is, should it be permitted without -XDataKinds?
isPromotedDataCon_maybe :: TyCon -> Maybe DataCon #
Retrieves the promoted DataCon if this is a PromotedDataCon;
isPromotedDataCon :: TyCon -> Bool #
Is this a PromotedDataCon?
isPromotedTupleTyCon :: TyCon -> Bool #
Is this the TyCon for a promoted tuple?
isUnboxedSumTyCon :: TyCon -> Bool #
Is this the TyCon for an unboxed sum?
isBoxedTupleTyCon :: TyCon -> Bool #
Is this the TyCon for a boxed tuple?
tyConTuple_maybe :: TyCon -> Maybe TupleSort #
tyConFlavourAssoc_maybe :: TyConFlavour -> Maybe TyCon #
Get the enclosing class TyCon (if there is one) for the given TyConFlavour
tyConAssoc_maybe :: TyCon -> Maybe TyCon #
Get the enclosing class TyCon (if there is one) for the given TyCon.
isTyConAssoc :: TyCon -> Bool #
Is this TyCon for an associated type?
tyConInjectivityInfo :: TyCon -> Injectivity #
returns tyConInjectivityInfo tc is Injective istc is an
injective tycon (where is states for which tyConBinders tc is
injective), or NotInjective otherwise.
isClosedSynFamilyTyConWithAxiom_maybe :: TyCon -> Maybe (CoAxiom Branched) #
Is this a non-empty closed type family? Returns Nothing for
abstract or empty closed families.
isOpenTypeFamilyTyCon :: TyCon -> Bool #
Is this an open type family TyCon?
isDataFamilyTyCon :: TyCon -> Bool #
Is this a synonym TyCon that can have may have further instances appear?
isTypeFamilyTyCon :: TyCon -> Bool #
Is this a synonym TyCon that can have may have further instances appear?
isOpenFamilyTyCon :: TyCon -> Bool #
Is this a TyCon, synonym or otherwise, that defines a family with
instances?
isFamilyTyCon :: TyCon -> Bool #
Is this a TyCon, synonym or otherwise, that defines a family?
isEnumerationTyCon :: TyCon -> Bool #
Is this an algebraic TyCon which is just an enumeration of values?
isGadtSyntaxTyCon :: TyCon -> Bool #
Is this an algebraic TyCon declared with the GADT syntax?
mustBeSaturated :: TyCon -> Bool #
True iff we can decompose (T a b c) into ((T a b) c) I.e. is it injective and generative w.r.t nominal equality? That is, if (T a b) ~N d e f, is it always the case that (T ~N d), (a ~N e) and (b ~N f)? Specifically NOT true of synonyms (open and otherwise)
It'd be unusual to call mustBeSaturated on a regular H98 type synonym, because you should probably have expanded it first But regardless, it's not decomposable
isFamFreeTyCon :: TyCon -> Bool #
isTauTyCon :: TyCon -> Bool #
isTypeSynonymTyCon :: TyCon -> Bool #
Is this a TyCon representing a regular H98 type synonym (type)?
isDataSumTyCon_maybe :: TyCon -> Maybe [DataCon] #
isProductTyCon :: TyCon -> Bool #
unwrapNewTyConEtad_maybe :: TyCon -> Maybe ([TyVar], Type, CoAxiom Unbranched) #
unwrapNewTyCon_maybe :: TyCon -> Maybe ([TyVar], Type, CoAxiom Unbranched) #
isNewTyCon :: TyCon -> Bool #
Is this TyCon that for a newtype
isGenInjAlgRhs :: AlgTyConRhs -> Bool #
Is this an AlgTyConRhs of a TyCon that is generative and injective
with respect to representational equality?
isGenerativeTyCon :: TyCon -> Role -> Bool #
isGenerativeTyCon is true of TyCons for which this property holds
(where X is the role passed in):
If (T tys ~X t), then (t's head ~X T).
See also Note [Decomposing equality] in TcCanonical
isInjectiveTyCon :: TyCon -> Role -> Bool #
isInjectiveTyCon is true of TyCons for which this property holds
(where X is the role passed in):
If (T a1 b1 c1) ~X (T a2 b2 c2), then (a1 ~X1 a2), (b1 ~X2 b2), and (c1 ~X3 c2)
(where X1, X2, and X3, are the roles given by tyConRolesX tc X)
See also Note [Decomposing equality] in TcCanonical
isDataTyCon :: TyCon -> Bool #
Returns True for data types that are definitely represented by
heap-allocated constructors. These are scrutinised by Core-level
case expressions, and they get info tables allocated for them.
Generally, the function will be true for all data types and false
for newtypes, unboxed tuples, unboxed sums and type family
TyCons. But it is not guaranteed to return True in all cases
that it could.
NB: for a data type family, only the instance TyCons
get an info table. The family declaration TyCon does not
isVanillaAlgTyCon :: TyCon -> Bool #
Returns True for vanilla AlgTyCons -- that is, those created
with a data or newtype declaration.
isAlgTyCon :: TyCon -> Bool #
Returns True if the supplied TyCon resulted from either a
data or newtype declaration
isUnliftedTyCon :: TyCon -> Bool #
isPrimTyCon :: TyCon -> Bool #
Does this TyCon represent something that cannot be defined in Haskell?
isAbstractTyCon :: TyCon -> Bool #
Test if the TyCon is algebraic but abstract (invisible data constructors)
mkPromotedDataCon :: DataCon -> Name -> TyConRepName -> [TyConTyCoBinder] -> Kind -> [Role] -> RuntimeRepInfo -> TyCon #
Create a promoted data constructor TyCon
Somewhat dodgily, we give it the same Name
as the data constructor itself; when we pretty-print
the TyCon we add a quote; see the Outputable TyCon instance
Arguments
| :: Name | |
| -> [TyConBinder] | |
| -> Kind | result kind |
| -> Maybe Name | |
| -> FamTyConFlav | |
| -> Maybe Class | |
| -> Injectivity | |
| -> TyCon |
Create a type family TyCon
Create a type synonym TyCon
Arguments
| :: Name | |
| -> [TyConBinder] | |
| -> Kind | result kind |
| -> [Role] | |
| -> TyCon |
Create a lifted primitive TyCon such as RealWorld
Kind constructors
Arguments
| :: Name | |
| -> [TyConBinder] | |
| -> Kind | result kind, never levity-polymorphic |
| -> [Role] | |
| -> TyCon |
Create an unlifted primitive TyCon, such as Int#.
noTcTyConScopedTyVars :: [(Name, TcTyVar)] #
No scoped type variables (to be used with mkTcTyCon).
Arguments
| :: Name | |
| -> [TyConBinder] | |
| -> Kind | result kind only |
| -> [(Name, TcTyVar)] | Scoped type variables; see Note [How TcTyCons work] in TcTyClsDecls |
| -> Bool | Is this TcTyCon generalised already? |
| -> TyConFlavour | What sort of |
| -> TyCon |
Makes a tycon suitable for use during type-checking. It stores a variety of details about the definition of the TyCon, but no right-hand side. It lives only during the type-checking of a mutually-recursive group of tycons; it is then zonked to a proper TyCon in zonkTcTyCon. See also Note [Kind checking recursive type and class declarations] in TcTyClsDecls.
Arguments
| :: Name | |
| -> [TyConBinder] | |
| -> Kind | Kind of the resulting |
| -> Arity | Arity of the sum |
| -> [TyVar] |
|
| -> [DataCon] | |
| -> AlgTyConFlav | |
| -> TyCon |
Arguments
| :: Name | |
| -> [TyConBinder] | |
| -> Kind | Result kind of the |
| -> Arity | Arity of the tuple |
| -> DataCon | |
| -> TupleSort | Whether the tuple is boxed or unboxed |
| -> AlgTyConFlav | |
| -> TyCon |
mkClassTyCon :: Name -> [TyConBinder] -> [Role] -> AlgTyConRhs -> Class -> Name -> TyCon #
Simpler specialization of mkAlgTyCon for classes
Arguments
| :: Name | |
| -> [TyConBinder] | Binders of the |
| -> Kind | Result kind |
| -> [Role] | The roles for each TyVar |
| -> Maybe CType | The C type this type corresponds to when using the CAPI FFI |
| -> [PredType] | Stupid theta: see |
| -> AlgTyConRhs | Information about data constructors |
| -> AlgTyConFlav | What flavour is it? (e.g. vanilla, type family) |
| -> Bool | Was the |
| -> TyCon |
This is the making of an algebraic TyCon. Notably, you have to
pass in the generic (in the -XGenerics sense) information about the
type constructor - you can get hold of it easily (see Generics
module)
mkFunTyCon :: Name -> [TyConBinder] -> Name -> TyCon #
lookupTyConFieldLabel :: FieldLabelString -> TyCon -> Maybe FieldLabel #
Look up a field label belonging to this TyCon
tyConFieldLabels :: TyCon -> [FieldLabel] #
The labels for the fields of this particular TyCon
primRepIsFloat :: PrimRep -> Maybe Bool #
Return if Rep stands for floating type, returns Nothing for vector types.
primElemRepSizeB :: PrimElemRep -> Int #
primRepSizeB :: DynFlags -> PrimRep -> Int #
The size of a PrimRep in bytes.
This applies also when used in a constructor, where we allow packing the
fields. For instance, in data Foo = Foo Float the two fields will
take only 8 bytes, which for 64-bit arch will be equal to 1 word.
See also mkVirtHeapOffsetsWithPadding for details of how data fields are
layed out.
isGcPtrRep :: PrimRep -> Bool #
tyConRepModOcc :: Module -> OccName -> (Module, OccName) #
The name (and defining module) for the Typeable representation (TyCon) of a type constructor.
See Note [Grand plan for Typeable] in TcTypeable in TcTypeable.
mkPrelTyConRepName :: Name -> TyConRepName #
Make a Name for the Typeable representation of the given wired-in type
isNoParent :: AlgTyConFlav -> Bool #
visibleDataCons :: AlgTyConRhs -> [DataCon] #
Both type classes as well as family instances imply implicit type constructors. These implicit type constructors refer to their parent structure (ie, the class or family from which they derive) using a type of the following form.
Extract those DataCons that we are able to learn about. Note
that visibility in this sense does not correspond to visibility in
the context of any particular user program!
mkDataTyConRhs :: [DataCon] -> AlgTyConRhs #
tyConVisibleTyVars :: TyCon -> [TyVar] #
tyConTyVarBinders :: [TyConBinder] -> [TyVarBinder] #
mkTyConKind :: [TyConBinder] -> Kind -> Kind #
isInvisibleTyConBinder :: VarBndr tv TyConBndrVis -> Bool #
isVisibleTyConBinder :: VarBndr tv TyConBndrVis -> Bool #
isNamedTyConBinder :: TyConBinder -> Bool #
mkRequiredTyConBinder :: TyCoVarSet -> TyVar -> TyConBinder #
Make a Required TyConBinder. It chooses between NamedTCB and AnonTCB based on whether the tv is mentioned in the dependent set
mkNamedTyConBinders :: ArgFlag -> [TyVar] -> [TyConBinder] #
mkNamedTyConBinder :: ArgFlag -> TyVar -> TyConBinder #
mkAnonTyConBinders :: AnonArgFlag -> [TyVar] -> [TyConBinder] #
mkAnonTyConBinder :: AnonArgFlag -> TyVar -> TyConBinder #
type TyConBinder = VarBndr TyVar TyConBndrVis #
type TyConTyCoBinder = VarBndr TyCoVar TyConBndrVis #
data TyConBndrVis #
Constructors
| NamedTCB ArgFlag | |
| AnonTCB AnonArgFlag |
Instances
| Binary TyConBndrVis | |
Defined in TyCon Methods put_ :: BinHandle -> TyConBndrVis -> IO () # put :: BinHandle -> TyConBndrVis -> IO (Bin TyConBndrVis) # get :: BinHandle -> IO TyConBndrVis # | |
| Outputable TyConBndrVis | |
Defined in TyCon | |
| OutputableBndr tv => Outputable (VarBndr tv TyConBndrVis) | |
data AlgTyConRhs #
Represents right-hand-sides of TyCons for algebraic types
Constructors
| AbstractTyCon | Says that we know nothing about this data type, except that it's represented by a pointer. Used when we export a data type abstractly into an .hi file. |
| DataTyCon | Information about those |
Fields
| |
| TupleTyCon | |
| SumTyCon | An unboxed sum type. |
Fields
| |
| NewTyCon | Information about those |
Fields
| |
data RuntimeRepInfo #
Some promoted datacons signify extra info relevant to GHC. For example,
the IntRep constructor of RuntimeRep corresponds to the IntRep
constructor of PrimRep. This data structure allows us to store this
information right in the TyCon. The other approach would be to look
up things like RuntimeRep's PrimRep by known-key every time.
See also Note [Getting from RuntimeRep to PrimRep] in RepType
Constructors
| NoRRI | an ordinary promoted data con |
| RuntimeRep ([Type] -> [PrimRep]) | A constructor of |
| VecCount Int | A constructor of |
| VecElem PrimElemRep | A constructor of |
data AlgTyConFlav #
Constructors
| VanillaAlgTyCon TyConRepName | An ordinary type constructor has no parent. |
| UnboxedAlgTyCon (Maybe TyConRepName) | An unboxed type constructor. The TyConRepName is a Maybe since we currently don't allow unboxed sums to be Typeable since there are too many of them. See #13276. |
| ClassTyCon Class TyConRepName | Type constructors representing a class dictionary. See Note [ATyCon for classes] in TyCoRep |
| DataFamInstTyCon (CoAxiom Unbranched) TyCon [Type] | Type constructors representing an *instance* of a *data* family. Parameters: 1) The type family in question 2) Instance types; free variables are the 3) A |
Instances
| Outputable AlgTyConFlav | |
Defined in TyCon | |
data Injectivity #
Constructors
| NotInjective | |
| Injective [Bool] |
Instances
| Eq Injectivity | |
Defined in TyCon | |
| Binary Injectivity | |
Defined in TyCon Methods put_ :: BinHandle -> Injectivity -> IO () # put :: BinHandle -> Injectivity -> IO (Bin Injectivity) # get :: BinHandle -> IO Injectivity # | |
data FamTyConFlav #
Information pertaining to the expansion of a type synonym (type)
Constructors
| DataFamilyTyCon TyConRepName | Represents an open type family without a fixed right hand side. Additional instances can appear at any time. These are introduced by either a top level declaration: data family T a :: * Or an associated data type declaration, within a class declaration: class C a b where data T b :: * |
| OpenSynFamilyTyCon | An open type synonym family e.g. |
| ClosedSynFamilyTyCon (Maybe (CoAxiom Branched)) | A closed type synonym family e.g.
|
| AbstractClosedSynFamilyTyCon | A closed type synonym family declared in an hs-boot file with type family F a where .. |
| BuiltInSynFamTyCon BuiltInSynFamily | Built-in type family used by the TypeNats solver |
Instances
| Outputable FamTyConFlav | |
Defined in TyCon | |
type TyConRepName = Name #
A PrimRep is an abstraction of a type. It contains information that
the code generator needs in order to pass arguments, return results,
and store values of this type. See also Note [RuntimeRep and PrimRep] in RepType
and Note [VoidRep] in RepType.
Constructors
| VoidRep | |
| LiftedRep | |
| UnliftedRep | Unlifted pointer |
| Int8Rep | Signed, 8-bit value |
| Int16Rep | Signed, 16-bit value |
| Int32Rep | Signed, 32-bit value |
| Int64Rep | Signed, 64 bit value (with 32-bit words only) |
| IntRep | Signed, word-sized value |
| Word8Rep | Unsigned, 8 bit value |
| Word16Rep | Unsigned, 16 bit value |
| Word32Rep | Unsigned, 32 bit value |
| Word64Rep | Unsigned, 64 bit value (with 32-bit words only) |
| WordRep | Unsigned, word-sized value |
| AddrRep | A pointer, but not to a Haskell value (use '(Un)liftedRep') |
| FloatRep | |
| DoubleRep | |
| VecRep Int PrimElemRep | A vector |
data PrimElemRep #
Constructors
| Int8ElemRep | |
| Int16ElemRep | |
| Int32ElemRep | |
| Int64ElemRep | |
| Word8ElemRep | |
| Word16ElemRep | |
| Word32ElemRep | |
| Word64ElemRep | |
| FloatElemRep | |
| DoubleElemRep |
Instances
| Eq PrimElemRep | |
Defined in TyCon | |
| Show PrimElemRep | |
Defined in TyCon Methods showsPrec :: Int -> PrimElemRep -> ShowS # show :: PrimElemRep -> String # showList :: [PrimElemRep] -> ShowS # | |
| Outputable PrimElemRep | |
Defined in TyCon | |
data TyConFlavour #
Paints a picture of what a TyCon represents, in broad strokes.
This is used towards more informative error messages.
Constructors
Instances
| Eq TyConFlavour | |
Defined in TyCon | |
| Outputable TyConFlavour | |
Defined in TyCon | |
data RecTcChecker #
pprFunDep :: Outputable a => FunDep a -> SDoc #
pprFundeps :: Outputable a => [FunDep a] -> SDoc #
pprDefMethInfo :: DefMethInfo -> SDoc #
isAbstractClass :: Class -> Bool #
classExtraBigSig :: Class -> ([TyVar], [FunDep TyVar], [PredType], [Id], [ClassATItem], [ClassOpItem]) #
classBigSig :: Class -> ([TyVar], [PredType], [Id], [ClassOpItem]) #
classHasFds :: Class -> Bool #
classSCTheta :: Class -> [PredType] #
classATItems :: Class -> [ClassATItem] #
classOpItems :: Class -> [ClassOpItem] #
classMethods :: Class -> [Id] #
classSCSelId :: Class -> Int -> Id #
classSCSelIds :: Class -> [Id] #
classAllSelIds :: Class -> [Id] #
classArity :: Class -> Arity #
mkClass :: Name -> [TyVar] -> [FunDep TyVar] -> [PredType] -> [Id] -> [ClassATItem] -> [ClassOpItem] -> ClassMinimalDef -> TyCon -> Class #
classMinimalDef :: Class -> ClassMinimalDef #
Instances
| Eq Class | |
| Data Class | |
Defined in Class Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Class -> c Class # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Class # dataTypeOf :: Class -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Class) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Class) # gmapT :: (forall b. Data b => b -> b) -> Class -> Class # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r # gmapQ :: (forall d. Data d => d -> u) -> Class -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Class -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Class -> m Class # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class # | |
| Show Class Source # | |
| NFData Class Source # | |
Defined in Language.Haskell.Liquid.GHC.Misc | |
| NamedThing Class | |
| Uniquable Class | |
| Outputable Class | |
| Symbolic Class Source # | |
Defined in Language.Haskell.Liquid.GHC.Misc | |
| Fixpoint Class Source # | |
| PPrint Class Source # | |
Defined in Language.Haskell.Liquid.Types.PrettyPrint | |
type ClassOpItem = (Id, DefMethInfo) #
type DefMethInfo = Maybe (Name, DefMethSpec Type) #
type ClassMinimalDef = BooleanFormula Name #
Constructors
| Nominal | |
| Representational | |
| Phantom |
Instances
| Eq Role | |
| Data Role | |
Defined in CoAxiom Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Role # dataTypeOf :: Role -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Role) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Role) # gmapT :: (forall b. Data b => b -> b) -> Role -> Role # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r # gmapQ :: (forall d. Data d => d -> u) -> Role -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Role -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role -> m Role # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role # | |
| Ord Role | |
| Binary Role | |
| Outputable Role | |
conLikeName :: ConLike -> Name #
A constructor-like thing
Constructors
| RealDataCon DataCon | |
| PatSynCon PatSyn |
Instances
| Eq ConLike | |
| Data ConLike | |
Defined in ConLike Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConLike -> c ConLike # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConLike # toConstr :: ConLike -> Constr # dataTypeOf :: ConLike -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConLike) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConLike) # gmapT :: (forall b. Data b => b -> b) -> ConLike -> ConLike # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConLike -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConLike -> r # gmapQ :: (forall d. Data d => d -> u) -> ConLike -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConLike -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConLike -> m ConLike # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConLike -> m ConLike # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConLike -> m ConLike # | |
| NamedThing ConLike | |
| Uniquable ConLike | |
| Outputable ConLike | |
| OutputableBndr ConLike | |
Defined in ConLike Methods pprBndr :: BindingSite -> ConLike -> SDoc # pprPrefixOcc :: ConLike -> SDoc # pprInfixOcc :: ConLike -> SDoc # bndrIsJoin_maybe :: ConLike -> Maybe Int # | |
dataConTyCon :: DataCon -> TyCon #
The type constructor that we are building via this data constructor
dataConExTyCoVars :: DataCon -> [TyCoVar] #
The existentially-quantified type/coercion variables of the constructor including dependent (kind-) GADT equalities
dataConUserTyVars :: DataCon -> [TyVar] #
The type variables of the constructor, in the order the user wrote them
dataConUserTyVarBinders :: DataCon -> [TyVarBinder] #
TyCoVarBinders for the type variables of the constructor, in the order the
user wrote them
dataConSourceArity :: DataCon -> Arity #
Source-level arity of the data constructor
dataConFieldLabels :: DataCon -> [FieldLabel] #
The labels for the fields of this particular DataCon
dataConInstOrigArgTys :: DataCon -> [Type] -> [Type] #
Returns just the instantiated value argument types of a DataCon,
(excluding dictionary args)
dataConStupidTheta :: DataCon -> ThetaType #
The "stupid theta" of the DataCon, such as data Eq a in:
data Eq a => T a = ...
dataConFullSig :: DataCon -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, [Type], Type) #
The "full signature" of the DataCon returns, in order:
1) The result of dataConUnivTyVars
2) The result of dataConExTyCoVars
3) The non-dependent GADT equalities. Dependent GADT equalities are implied by coercion variables in return value (2).
4) The other constraints of the data constructor type, excluding GADT equalities
5) The original argument types to the DataCon (i.e. before
any change of the representation of the type)
6) The original result type of the DataCon
isUnboxedSumCon :: DataCon -> Bool #
A data constructor
Instances
data DataConRep #
Data Constructor Representation See Note [Data constructor workers and wrappers]
Constructors
| NoDataConRep | |
| DCR | |
Fields
| |
An EqSpec is a tyvar/type pair representing an equality made in
rejigging a GADT constructor
pprSpliceDecl :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SpliceExplicitFlag -> SDoc #
pprPatBind :: forall (bndr :: Pass) (p :: Pass) body. (OutputableBndrId bndr, OutputableBndrId p, Outputable body) => LPat (GhcPass bndr) -> GRHSs (GhcPass p) body -> SDoc #
pprFunBind :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc #
A Haskell expression.
Constructors
| HsVar (XVar p) (Located (IdP p)) | Variable |
| HsUnboundVar (XUnboundVar p) UnboundVar | Unbound variable; also used for "holes" (_ or _x). Turned from HsVar to HsUnboundVar by the renamer, when it finds an out-of-scope variable or hole. Turned into HsVar by type checker, to support deferred type errors. |
| HsConLikeOut (XConLikeOut p) ConLike | After typechecker only; must be different HsVar for pretty printing |
| HsRecFld (XRecFld p) (AmbiguousFieldOcc p) | Variable pointing to record selector Not in use after typechecking |
| HsOverLabel (XOverLabel p) (Maybe (IdP p)) FastString | Overloaded label (Note [Overloaded labels] in GHC.OverloadedLabels)
|
| HsIPVar (XIPVar p) HsIPName | Implicit parameter (not in use after typechecking) |
| HsOverLit (XOverLitE p) (HsOverLit p) | Overloaded literals |
| HsLit (XLitE p) (HsLit p) | Simple (non-overloaded) literals |
| HsLam (XLam p) (MatchGroup p (LHsExpr p)) | Lambda abstraction. Currently always a single match |
| HsLamCase (XLamCase p) (MatchGroup p (LHsExpr p)) | Lambda-case |
| HsApp (XApp p) (LHsExpr p) (LHsExpr p) | Application |
| HsAppType (XAppTypeE p) (LHsExpr p) (LHsWcType (NoGhcTc p)) | Visible type application Explicit type argument; e.g f @Int x y NB: Has wildcards, but no implicit quantification |
| OpApp (XOpApp p) (LHsExpr p) (LHsExpr p) (LHsExpr p) | Operator applications: NB Bracketed ops such as (+) come out as Vars. |
| NegApp (XNegApp p) (LHsExpr p) (SyntaxExpr p) | Negation operator. Contains the negated expression and the name
of |
| HsPar (XPar p) (LHsExpr p) | Parenthesised expr; see Note [Parens in HsSyn] |
| SectionL (XSectionL p) (LHsExpr p) (LHsExpr p) | |
| SectionR (XSectionR p) (LHsExpr p) (LHsExpr p) | |
| ExplicitTuple (XExplicitTuple p) [LHsTupArg p] Boxity | Used for explicit tuples and sections thereof |
| ExplicitSum (XExplicitSum p) ConTag Arity (LHsExpr p) | Used for unboxed sum types
There will be multiple |
| HsCase (XCase p) (LHsExpr p) (MatchGroup p (LHsExpr p)) |
|
| HsIf (XIf p) (Maybe (SyntaxExpr p)) (LHsExpr p) (LHsExpr p) (LHsExpr p) | |
| HsMultiIf (XMultiIf p) [LGRHS p (LHsExpr p)] | Multi-way if |
| HsLet (XLet p) (LHsLocalBinds p) (LHsExpr p) | let(rec)
|
| HsDo (XDo p) (HsStmtContext Name) (Located [ExprLStmt p]) | |
| ExplicitList (XExplicitList p) (Maybe (SyntaxExpr p)) [LHsExpr p] | Syntactic list: [a,b,c,...]
|
| RecordCon | Record construction
|
Fields
| |
| RecordUpd | Record update
|
Fields
| |
| ExprWithTySig (XExprWithTySig p) (LHsExpr p) (LHsSigWcType (NoGhcTc p)) | Expression with an explicit type signature. |
| ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) (ArithSeqInfo p) | Arithmetic sequence
|
| HsSCC (XSCC p) SourceText StringLiteral (LHsExpr p) | |
| HsCoreAnn (XCoreAnn p) SourceText StringLiteral (LHsExpr p) |
|
| HsBracket (XBracket p) (HsBracket p) | |
| HsRnBracketOut (XRnBracketOut p) (HsBracket GhcRn) [PendingRnSplice] | |
| HsTcBracketOut (XTcBracketOut p) (HsBracket GhcRn) [PendingTcSplice] | |
| HsSpliceE (XSpliceE p) (HsSplice p) | |
| HsProc (XProc p) (LPat p) (LHsCmdTop p) |
|
| HsStatic (XStatic p) (LHsExpr p) | |
| HsTick (XTick p) (Tickish (IdP p)) (LHsExpr p) | |
| HsBinTick (XBinTick p) Int Int (LHsExpr p) | |
| HsTickPragma (XTickPragma p) SourceText (StringLiteral, (Int, Int), (Int, Int)) ((SourceText, SourceText), (SourceText, SourceText)) (LHsExpr p) | |
| HsWrap (XWrap p) HsWrapper (HsExpr p) | |
| XExpr (XXExpr p) | |
Instances
Haskell Command (e.g. a "statement" in an Arrow proc block)
Constructors
| HsCmdArrApp (XCmdArrApp id) (LHsExpr id) (LHsExpr id) HsArrAppType Bool | |
| HsCmdArrForm (XCmdArrForm id) (LHsExpr id) LexicalFixity (Maybe Fixity) [LHsCmdTop id] |
|
| HsCmdApp (XCmdApp id) (LHsCmd id) (LHsExpr id) | |
| HsCmdLam (XCmdLam id) (MatchGroup id (LHsCmd id)) | |
| HsCmdPar (XCmdPar id) (LHsCmd id) |
|
| HsCmdCase (XCmdCase id) (LHsExpr id) (MatchGroup id (LHsCmd id)) |
|
| HsCmdIf (XCmdIf id) (Maybe (SyntaxExpr id)) (LHsExpr id) (LHsCmd id) (LHsCmd id) | |
| HsCmdLet (XCmdLet id) (LHsLocalBinds id) (LHsCmd id) |
|
| HsCmdDo (XCmdDo id) (Located [CmdLStmt id]) | |
| HsCmdWrap (XCmdWrap id) HsWrapper (HsCmd id) | |
| XCmd (XXCmd id) |
Instances
Haskell Splice
Constructors
| HsTypedSplice (XTypedSplice id) SpliceDecoration (IdP id) (LHsExpr id) | |
| HsUntypedSplice (XUntypedSplice id) SpliceDecoration (IdP id) (LHsExpr id) | |
| HsQuasiQuote (XQuasiQuote id) (IdP id) (IdP id) SrcSpan FastString | |
| HsSpliced (XSpliced id) ThModFinalizers (HsSplicedThing id) | |
| HsSplicedT DelayedSplice | |
| XSplice (XXSplice id) |
data MatchGroup p body #
Constructors
| MG | |
| XMatchGroup (XXMatchGroup p body) | |
Guarded Right-Hand Sides
GRHSs are used both for pattern bindings and for Matches
Constructors
| GRHSs | |
Fields
| |
| XGRHSs (XXGRHSs p body) | |
data SyntaxExpr p #
Syntax Expression
SyntaxExpr is like PostTcExpr, but it's filled in a little earlier,
by the renamer. It's used for rebindable syntax.
E.g. (>>=) is filled in before the renamer by the appropriate Name for
(>>=), and then instantiated by the type checker with its type args
etc
This should desugar to
syn_res_wrap $ syn_expr (syn_arg_wraps[0] arg0)
(syn_arg_wraps[1] arg1) ...where the actual arguments come from elsewhere in the AST.
This could be defined using GhcPass p and such, but it's
harder to get it all to work out that way. (noSyntaxExpr is hard to
write, for example.)
Constructors
| SyntaxExpr | |
Fields
| |
Instances
| OutputableBndrId p => Outputable (SyntaxExpr (GhcPass p)) | |
Defined in GHC.Hs.Expr | |
Arguments
| = Located (HsExpr p) | May have |
Located Haskell Expression
pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc #
replaceLWrappedName :: LIEWrappedName name1 -> name2 -> LIEWrappedName name2 #
replaceWrappedName :: IEWrappedName name1 -> name2 -> IEWrappedName name2 #
ieLWrappedName :: LIEWrappedName name -> Located name #
lieWrappedName :: LIEWrappedName name -> name #
ieWrappedName :: IEWrappedName name -> name #
simpleImportDecl :: forall (p :: Pass). ModuleName -> ImportDecl (GhcPass p) #
isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool #
Convenience function to answer the question if an import decl. is qualified.
importDeclQualifiedStyle :: Maybe (Located a) -> Maybe (Located a) -> ImportDeclQualifiedStyle #
type LImportDecl pass #
Arguments
| = Located (ImportDecl pass) | When in a list this may have |
Located Import Declaration
data ImportDeclQualifiedStyle #
If/how an import is qualified.
Constructors
| QualifiedPre |
|
| QualifiedPost |
|
| NotQualified | Not qualified. |
Instances
data ImportDecl pass #
Import Declaration
A single Haskell import declaration.
Constructors
| ImportDecl | |
Fields
| |
| XImportDecl (XXImportDecl pass) | |
Instances
| OutputableBndrId p => Outputable (ImportDecl (GhcPass p)) | |
Defined in GHC.Hs.ImpExp | |
data IEWrappedName name #
A name in an import or export specification which may have adornments. Used primarily for accurate pretty printing of ParsedSource, and API Annotation placement.
Constructors
| IEName (Located name) | no extra |
| IEPattern (Located name) | pattern X |
| IEType (Located name) | type (:+:) |
Instances
| Eq name => Eq (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp Methods (==) :: IEWrappedName name -> IEWrappedName name -> Bool # (/=) :: IEWrappedName name -> IEWrappedName name -> Bool # | |
| Data name => Data (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName name -> c (IEWrappedName name) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName name) # toConstr :: IEWrappedName name -> Constr # dataTypeOf :: IEWrappedName name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName name)) # gmapT :: (forall b. Data b => b -> b) -> IEWrappedName name -> IEWrappedName name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r # gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) # | |
| HasOccName name => HasOccName (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp Methods occName :: IEWrappedName name -> OccName # | |
| OutputableBndr name => Outputable (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp | |
| OutputableBndr name => OutputableBndr (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp Methods pprBndr :: BindingSite -> IEWrappedName name -> SDoc # pprPrefixOcc :: IEWrappedName name -> SDoc # pprInfixOcc :: IEWrappedName name -> SDoc # bndrIsJoin_maybe :: IEWrappedName name -> Maybe Int # | |
type LIEWrappedName name = Located (IEWrappedName name) #
Located name with possible adornment
- AnnKeywordIds : AnnType,
AnnPattern
Imported or exported entity.
Constructors
| IEVar (XIEVar pass) (LIEWrappedName (IdP pass)) | Imported or Exported Variable |
| IEThingAbs (XIEThingAbs pass) (LIEWrappedName (IdP pass)) | Imported or exported Thing with Absent list The thing is a Class/Type (can't tell)
- |
| IEThingAll (XIEThingAll pass) (LIEWrappedName (IdP pass)) | Imported or exported Thing with All imported or exported The thing is a ClassType and the All refers to methodsconstructors |
| IEThingWith (XIEThingWith pass) (LIEWrappedName (IdP pass)) IEWildcard [LIEWrappedName (IdP pass)] [Located (FieldLbl (IdP pass))] | Imported or exported Thing With given imported or exported The thing is a Class/Type and the imported or exported things are
methods/constructors and record fields; see Note [IEThingWith]
- |
| IEModuleContents (XIEModuleContents pass) (Located ModuleName) | Imported or exported module contents (Export Only) |
| IEGroup (XIEGroup pass) Int HsDocString | Doc section heading |
| IEDoc (XIEDoc pass) HsDocString | Some documentation |
| IEDocNamed (XIEDocNamed pass) String | Reference to named doc |
| XIE (XXIE pass) |
data IEWildcard #
Imported or Exported Wildcard
Constructors
| NoIEWildcard | |
| IEWildcard Int |
Instances
| Eq IEWildcard | |
Defined in GHC.Hs.ImpExp | |
| Data IEWildcard | |
Defined in GHC.Hs.ImpExp Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWildcard -> c IEWildcard # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IEWildcard # toConstr :: IEWildcard -> Constr # dataTypeOf :: IEWildcard -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IEWildcard) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard) # gmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWildcard -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWildcard -> r # gmapQ :: (forall d. Data d => d -> u) -> IEWildcard -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWildcard -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard # | |
Pattern
Constructors
| WildPat (XWildPat p) | Wildcard Pattern The sole reason for a type on a WildPat is to support hsPatType :: Pat Id -> Type |
| VarPat (XVarPat p) (Located (IdP p)) | Variable Pattern |
| LazyPat (XLazyPat p) (LPat p) | Lazy Pattern
^ - |
| AsPat (XAsPat p) (Located (IdP p)) (LPat p) | As pattern
^ - |
| ParPat (XParPat p) (LPat p) | Parenthesised pattern
See Note [Parens in HsSyn] in GHC.Hs.Expr
^ - |
| BangPat (XBangPat p) (LPat p) | Bang pattern
^ - |
| ListPat (XListPat p) [LPat p] | Syntactic List
|
| TuplePat (XTuplePat p) [LPat p] Boxity | Tuple sub-patterns
|
| SumPat (XSumPat p) (LPat p) ConTag Arity | Anonymous sum pattern
|
| ConPatIn (Located (IdP p)) (HsConPatDetails p) | Constructor Pattern In |
| ConPatOut | Constructor Pattern Out |
| ViewPat (XViewPat p) (LHsExpr p) (LPat p) | View Pattern |
| SplicePat (XSplicePat p) (HsSplice p) | Splice Pattern (Includes quasi-quotes) |
| LitPat (XLitPat p) (HsLit p) | Literal Pattern Used for *non-overloaded* literal patterns: Int, Int, Char, String, etc. |
| NPat (XNPat p) (Located (HsOverLit p)) (Maybe (SyntaxExpr p)) (SyntaxExpr p) | Natural Pattern |
| NPlusKPat (XNPlusKPat p) (Located (IdP p)) (Located (HsOverLit p)) (HsOverLit p) (SyntaxExpr p) (SyntaxExpr p) | n+k pattern |
| SigPat (XSigPat p) (LPat p) (LHsSigWcType (NoGhcTc p)) | Pattern with a type signature |
| CoPat (XCoPat p) HsWrapper (Pat p) Type | Coercion Pattern |
| XPat (XXPat p) | Trees that Grow extension point for new constructors |
Used when constructing a term with an unused extension point.
data NoExtField #
A placeholder type for TTG extension points that are not currently unused to represent any particular value.
This should not be confused with NoExtCon, which are found in unused
extension constructors and therefore should never be inhabited. In
contrast, NoExtField is used in extension points (e.g., as the field of
some constructor), so it must have an inhabitant to construct AST passes
that manipulate fields with that extension point as their type.
Constructors
| NoExtField |
Instances
| Eq NoExtField | |
Defined in GHC.Hs.Extension | |
| Data NoExtField | |
Defined in GHC.Hs.Extension Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoExtField -> c NoExtField # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoExtField # toConstr :: NoExtField -> Constr # dataTypeOf :: NoExtField -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoExtField) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoExtField) # gmapT :: (forall b. Data b => b -> b) -> NoExtField -> NoExtField # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoExtField -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoExtField -> r # gmapQ :: (forall d. Data d => d -> u) -> NoExtField -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NoExtField -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField # | |
| Ord NoExtField | |
Defined in GHC.Hs.Extension Methods compare :: NoExtField -> NoExtField -> Ordering # (<) :: NoExtField -> NoExtField -> Bool # (<=) :: NoExtField -> NoExtField -> Bool # (>) :: NoExtField -> NoExtField -> Bool # (>=) :: NoExtField -> NoExtField -> Bool # max :: NoExtField -> NoExtField -> NoExtField # min :: NoExtField -> NoExtField -> NoExtField # | |
| Outputable NoExtField | |
Defined in GHC.Hs.Extension | |
Used in TTG extension constructors that have yet to be extended with
anything. If an extension constructor has NoExtCon as its field, it is
not intended to ever be constructed anywhere, and any function that consumes
the extension constructor can eliminate it by way of noExtCon.
This should not be confused with NoExtField, which are found in unused
extension points (not constructors) and therefore can be inhabited.
Instances
| Eq NoExtCon | |
| Data NoExtCon | |
Defined in GHC.Hs.Extension Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoExtCon -> c NoExtCon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoExtCon # toConstr :: NoExtCon -> Constr # dataTypeOf :: NoExtCon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoExtCon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoExtCon) # gmapT :: (forall b. Data b => b -> b) -> NoExtCon -> NoExtCon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoExtCon -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoExtCon -> r # gmapQ :: (forall d. Data d => d -> u) -> NoExtCon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NoExtCon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoExtCon -> m NoExtCon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtCon -> m NoExtCon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtCon -> m NoExtCon # | |
| Ord NoExtCon | |
Defined in GHC.Hs.Extension | |
| Outputable NoExtCon | |
Used as a data type index for the hsSyn AST
Instances
Constructors
| Parsed | |
| Renamed | |
| Typechecked |
Instances
| Data Pass | |
Defined in GHC.Hs.Extension Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pass -> c Pass # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pass # dataTypeOf :: Pass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pass) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass) # gmapT :: (forall b. Data b => b -> b) -> Pass -> Pass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r # gmapQ :: (forall d. Data d => d -> u) -> Pass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pass -> m Pass # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass # | |
type GhcTc = GhcPass 'Typechecked #
type family XRec p (f :: Type -> Type) = (r :: Type) | r -> p f #
Maps the "normal" id type for a given pass
type family NoGhcTc p where ... #
Marks that a field uses the GhcRn variant even when the pass parameter is GhcTc. Useful for storing HsTypes in GHC.Hs.Exprs, say, because HsType GhcTc should never occur.
Equations
| NoGhcTc (GhcPass pass) = GhcPass (NoGhcTcPass pass) | |
| NoGhcTc other = other |
type family NoGhcTcPass (p :: Pass) :: Pass where ... #
Equations
| NoGhcTcPass 'Typechecked = 'Renamed | |
| NoGhcTcPass other = other |
type family XHsValBinds x x' #
Instances
| type XHsValBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type family XHsIPBinds x x' #
Instances
| type XHsIPBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type family XEmptyLocalBinds x x' #
Instances
| type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type family XXHsLocalBindsLR x x' #
Instances
| type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type ForallXHsLocalBindsLR (c :: Type -> Constraint) x x' = (c (XHsValBinds x x'), c (XHsIPBinds x x'), c (XEmptyLocalBinds x x'), c (XXHsLocalBindsLR x x')) #
Instances
| type XValBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type family XXValBindsLR x x' #
Instances
| type XXValBindsLR (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type ForallXValBindsLR (c :: Type -> Constraint) x x' = (c (XValBinds x x'), c (XXValBindsLR x x')) #
Instances
| type XFunBind (GhcPass pL) GhcTc | |
Defined in GHC.Hs.Binds | |
| type XFunBind (GhcPass pL) GhcRn | |
Defined in GHC.Hs.Binds | |
| type XFunBind (GhcPass pL) GhcPs | |
Defined in GHC.Hs.Binds | |
Instances
| type XPatBind GhcPs (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
| type XPatBind GhcRn (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
| type XPatBind GhcTc (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
Instances
| type XVarBind (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
Instances
| type XAbsBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type family XPatSynBind x x' #
Instances
| type XPatSynBind (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type family XXHsBindsLR x x' #
Instances
| type XXHsBindsLR (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type ForallXHsBindsLR (c :: Type -> Constraint) x x' = (c (XFunBind x x'), c (XPatBind x x'), c (XVarBind x x'), c (XAbsBinds x x'), c (XPatSynBind x x'), c (XXHsBindsLR x x')) #
Instances
| type XABE (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type family XXABExport x #
Instances
| type XXABExport (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type ForallXABExport (c :: Type -> Constraint) x = (c (XABE x), c (XXABExport x)) #
type family XXPatSynBind x x' #
Instances
| type XXPatSynBind (GhcPass idL) (GhcPass idR) | |
Defined in GHC.Hs.Binds | |
type ForallXPatSynBind (c :: Type -> Constraint) x x' = (c (XPSB x x'), c (XXPatSynBind x x')) #
Instances
| type XIPBinds GhcPs | |
Defined in GHC.Hs.Binds | |
| type XIPBinds GhcRn | |
Defined in GHC.Hs.Binds | |
| type XIPBinds GhcTc | |
Defined in GHC.Hs.Binds | |
type family XXHsIPBinds x #
Instances
| type XXHsIPBinds (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type ForallXHsIPBinds (c :: Type -> Constraint) x = (c (XIPBinds x), c (XXHsIPBinds x)) #
Instances
| type XCIPBind (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type ForallXIPBind (c :: Type -> Constraint) x = (c (XCIPBind x), c (XXIPBind x)) #
Instances
| type XTypeSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type family XPatSynSig x #
Instances
| type XPatSynSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type family XClassOpSig x #
Instances
| type XClassOpSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
Instances
| type XIdSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
Instances
| type XFixSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type family XInlineSig x #
Instances
| type XInlineSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
Instances
| type XSpecSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type family XSpecInstSig x #
Instances
| type XSpecInstSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type family XMinimalSig x #
Instances
| type XMinimalSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type family XSCCFunSig x #
Instances
| type XSCCFunSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type family XCompleteMatchSig x #
Instances
| type XCompleteMatchSig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type ForallXSig (c :: Type -> Constraint) x = (c (XTypeSig x), c (XPatSynSig x), c (XClassOpSig x), c (XIdSig x), c (XFixSig x), c (XInlineSig x), c (XSpecSig x), c (XSpecInstSig x), c (XMinimalSig x), c (XSCCFunSig x), c (XCompleteMatchSig x), c (XXSig x)) #
type family XFixitySig x #
Instances
| type XFixitySig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type family XXFixitySig x #
Instances
| type XXFixitySig (GhcPass p) | |
Defined in GHC.Hs.Binds | |
type ForallXFixitySig (c :: Type -> Constraint) x = (c (XFixitySig x), c (XXFixitySig x)) #
type family XStandaloneKindSig x #
Instances
| type XStandaloneKindSig (GhcPass p) | |
Defined in GHC.Hs.Decls | |
type family XXStandaloneKindSig x #
Instances
| type XXStandaloneKindSig (GhcPass p) | |
Defined in GHC.Hs.Decls | |
Instances
| type XTyClD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XDerivD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XValD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XSigD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XKindSigD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XDefD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XForD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XWarningD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XAnnD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XRuleD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XSpliceD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XDocD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XRoleAnnotD x #
Instances
| type XRoleAnnotD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXHsDecl (c :: Type -> Constraint) x = (c (XTyClD x), c (XInstD x), c (XDerivD x), c (XValD x), c (XSigD x), c (XKindSigD x), c (XDefD x), c (XForD x), c (XWarningD x), c (XAnnD x), c (XRuleD x), c (XSpliceD x), c (XDocD x), c (XRoleAnnotD x), c (XXHsDecl x)) #
Instances
| type XCHsGroup (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXHsGroup (c :: Type -> Constraint) x = (c (XCHsGroup x), c (XXHsGroup x)) #
type family XSpliceDecl x #
Instances
| type XSpliceDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXSpliceDecl x #
Instances
| type XXSpliceDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXSpliceDecl (c :: Type -> Constraint) x = (c (XSpliceDecl x), c (XXSpliceDecl x)) #
Instances
| type XFamDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XSynDecl GhcPs | |
Defined in GHC.Hs.Decls | |
| type XSynDecl GhcRn | |
Defined in GHC.Hs.Decls | |
| type XSynDecl GhcTc | |
Defined in GHC.Hs.Decls | |
Instances
| type XDataDecl GhcPs | |
Defined in GHC.Hs.Decls | |
| type XDataDecl GhcRn | |
Defined in GHC.Hs.Decls | |
| type XDataDecl GhcTc | |
Defined in GHC.Hs.Decls | |
type family XClassDecl x #
Instances
| type XClassDecl GhcPs | |
Defined in GHC.Hs.Decls | |
| type XClassDecl GhcRn | |
Defined in GHC.Hs.Decls | |
| type XClassDecl GhcTc | |
Defined in GHC.Hs.Decls | |
type family XXTyClDecl x #
Instances
| type XXTyClDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXTyClDecl (c :: Type -> Constraint) x = (c (XFamDecl x), c (XSynDecl x), c (XDataDecl x), c (XClassDecl x), c (XXTyClDecl x)) #
type family XCTyClGroup x #
Instances
| type XCTyClGroup (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXTyClGroup x #
Instances
| type XXTyClGroup (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXTyClGroup (c :: Type -> Constraint) x = (c (XCTyClGroup x), c (XXTyClGroup x)) #
Instances
| type XNoSig (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XCKindSig (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
Instances
| type XTyVarSig (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXFamilyResultSig x #
Instances
| type XXFamilyResultSig (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXFamilyResultSig (c :: Type -> Constraint) x = (c (XNoSig x), c (XCKindSig x), c (XTyVarSig x), c (XXFamilyResultSig x)) #
type family XCFamilyDecl x #
Instances
| type XCFamilyDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXFamilyDecl x #
Instances
| type XXFamilyDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXFamilyDecl (c :: Type -> Constraint) x = (c (XCFamilyDecl x), c (XXFamilyDecl x)) #
type family XCHsDataDefn x #
Instances
| type XCHsDataDefn (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXHsDataDefn x #
Instances
| type XXHsDataDefn (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXHsDataDefn (c :: Type -> Constraint) x = (c (XCHsDataDefn x), c (XXHsDataDefn x)) #
type family XCHsDerivingClause x #
Instances
| type XCHsDerivingClause (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXHsDerivingClause x #
Instances
| type XXHsDerivingClause (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXHsDerivingClause (c :: Type -> Constraint) x = (c (XCHsDerivingClause x), c (XXHsDerivingClause x)) #
type family XConDeclGADT x #
Instances
| type XConDeclGADT (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XConDeclH98 x #
Instances
| type XConDeclH98 (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXConDecl (c :: Type -> Constraint) x = (c (XConDeclGADT x), c (XConDeclH98 x), c (XXConDecl x)) #
Instances
| type XCFamEqn (GhcPass _1) r | |
Defined in GHC.Hs.Decls | |
type ForallXFamEqn (c :: Type -> Constraint) x r = (c (XCFamEqn x r), c (XXFamEqn x r)) #
type family XCClsInstDecl x #
Instances
| type XCClsInstDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXClsInstDecl x #
Instances
| type XXClsInstDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXClsInstDecl (c :: Type -> Constraint) x = (c (XCClsInstDecl x), c (XXClsInstDecl x)) #
Instances
| type XClsInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XDataFamInstD x #
Instances
| type XDataFamInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XTyFamInstD x #
Instances
| type XTyFamInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXInstDecl x #
Instances
| type XXInstDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXInstDecl (c :: Type -> Constraint) x = (c (XClsInstD x), c (XDataFamInstD x), c (XTyFamInstD x), c (XXInstDecl x)) #
type family XCDerivDecl x #
Instances
| type XCDerivDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXDerivDecl x #
Instances
| type XXDerivDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXDerivDecl (c :: Type -> Constraint) x = (c (XCDerivDecl x), c (XXDerivDecl x)) #
type family XViaStrategy x #
Instances
| type XViaStrategy GhcPs | |
Defined in GHC.Hs.Decls | |
| type XViaStrategy GhcRn | |
Defined in GHC.Hs.Decls | |
| type XViaStrategy GhcTc | |
Defined in GHC.Hs.Decls | |
type family XCDefaultDecl x #
Instances
| type XCDefaultDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXDefaultDecl x #
Instances
| type XXDefaultDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXDefaultDecl (c :: Type -> Constraint) x = (c (XCDefaultDecl x), c (XXDefaultDecl x)) #
type family XForeignImport x #
Instances
| type XForeignImport GhcPs | |
Defined in GHC.Hs.Decls | |
| type XForeignImport GhcRn | |
Defined in GHC.Hs.Decls | |
| type XForeignImport GhcTc | |
Defined in GHC.Hs.Decls | |
type family XForeignExport x #
Instances
| type XForeignExport GhcPs | |
Defined in GHC.Hs.Decls | |
| type XForeignExport GhcRn | |
Defined in GHC.Hs.Decls | |
| type XForeignExport GhcTc | |
Defined in GHC.Hs.Decls | |
type family XXForeignDecl x #
Instances
| type XXForeignDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXForeignDecl (c :: Type -> Constraint) x = (c (XForeignImport x), c (XForeignExport x), c (XXForeignDecl x)) #
type family XCRuleDecls x #
Instances
| type XCRuleDecls (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXRuleDecls x #
Instances
| type XXRuleDecls (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXRuleDecls (c :: Type -> Constraint) x = (c (XCRuleDecls x), c (XXRuleDecls x)) #
Instances
| type XHsRule GhcPs | |
Defined in GHC.Hs.Decls | |
| type XHsRule GhcRn | |
Defined in GHC.Hs.Decls | |
| type XHsRule GhcTc | |
Defined in GHC.Hs.Decls | |
type family XXRuleDecl x #
Instances
| type XXRuleDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXRuleDecl (c :: Type -> Constraint) x = (c (XHsRule x), c (XXRuleDecl x)) #
type family XCRuleBndr x #
Instances
| type XCRuleBndr (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XRuleBndrSig x #
Instances
| type XRuleBndrSig (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXRuleBndr x #
Instances
| type XXRuleBndr (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXRuleBndr (c :: Type -> Constraint) x = (c (XCRuleBndr x), c (XRuleBndrSig x), c (XXRuleBndr x)) #
Instances
| type XWarnings (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXWarnDecls x #
Instances
| type XXWarnDecls (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXWarnDecls (c :: Type -> Constraint) x = (c (XWarnings x), c (XXWarnDecls x)) #
Instances
| type XWarning (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXWarnDecl x #
Instances
| type XXWarnDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXWarnDecl (c :: Type -> Constraint) x = (c (XWarning x), c (XXWarnDecl x)) #
type family XHsAnnotation x #
Instances
| type XHsAnnotation (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXAnnDecl (c :: Type -> Constraint) x = (c (XHsAnnotation x), c (XXAnnDecl x)) #
type family XCRoleAnnotDecl x #
Instances
| type XCRoleAnnotDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type family XXRoleAnnotDecl x #
Instances
| type XXRoleAnnotDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls | |
type ForallXRoleAnnotDecl (c :: Type -> Constraint) x = (c (XCRoleAnnotDecl x), c (XXRoleAnnotDecl x)) #
Instances
| type XVar (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XUnboundVar x #
Instances
| type XUnboundVar (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XConLikeOut x #
Instances
| type XConLikeOut (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XRecFld (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XOverLabel x #
Instances
| type XOverLabel (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XIPVar (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XOverLitE (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XLitE (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XLam (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XLamCase (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XApp (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XAppTypeE (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XOpApp GhcPs | |
Defined in GHC.Hs.Expr | |
| type XOpApp GhcRn | |
Defined in GHC.Hs.Expr | |
| type XOpApp GhcTc | |
Defined in GHC.Hs.Expr | |
Instances
| type XNegApp (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XPar (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XSectionL (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XSectionR (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XExplicitTuple x #
Instances
| type XExplicitTuple (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XExplicitSum x #
Instances
| type XExplicitSum GhcPs | |
Defined in GHC.Hs.Expr | |
| type XExplicitSum GhcRn | |
Defined in GHC.Hs.Expr | |
| type XExplicitSum GhcTc | |
Defined in GHC.Hs.Expr | |
Instances
| type XCase (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XIf (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XMultiIf GhcPs | |
Defined in GHC.Hs.Expr | |
| type XMultiIf GhcRn | |
Defined in GHC.Hs.Expr | |
| type XMultiIf GhcTc | |
Defined in GHC.Hs.Expr | |
Instances
| type XLet (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XDo GhcPs | |
Defined in GHC.Hs.Expr | |
| type XDo GhcRn | |
Defined in GHC.Hs.Expr | |
| type XDo GhcTc | |
Defined in GHC.Hs.Expr | |
type family XExplicitList x #
Instances
| type XExplicitList GhcPs | |
Defined in GHC.Hs.Expr | |
| type XExplicitList GhcRn | |
Defined in GHC.Hs.Expr | |
| type XExplicitList GhcTc | |
Defined in GHC.Hs.Expr | |
type family XRecordCon x #
Instances
| type XRecordCon GhcPs | |
Defined in GHC.Hs.Expr | |
| type XRecordCon GhcRn | |
Defined in GHC.Hs.Expr | |
| type XRecordCon GhcTc | |
Defined in GHC.Hs.Expr | |
type family XRecordUpd x #
Instances
| type XRecordUpd GhcPs | |
Defined in GHC.Hs.Expr | |
| type XRecordUpd GhcRn | |
Defined in GHC.Hs.Expr | |
| type XRecordUpd GhcTc | |
Defined in GHC.Hs.Expr | |
type family XExprWithTySig x #
Instances
| type XExprWithTySig (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XArithSeq GhcPs | |
Defined in GHC.Hs.Expr | |
| type XArithSeq GhcRn | |
Defined in GHC.Hs.Expr | |
| type XArithSeq GhcTc | |
Defined in GHC.Hs.Expr | |
Instances
| type XSCC (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XCoreAnn (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XBracket (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XRnBracketOut x #
Instances
| type XRnBracketOut (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XTcBracketOut x #
Instances
| type XTcBracketOut (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XSpliceE (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XProc (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XStatic GhcPs | |
Defined in GHC.Hs.Expr | |
| type XStatic GhcRn | |
Defined in GHC.Hs.Expr | |
| type XStatic GhcTc | |
Defined in GHC.Hs.Expr | |
Instances
| type XTick (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XBinTick (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XTickPragma x #
Instances
| type XTickPragma (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XWrap (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type ForallXExpr (c :: Type -> Constraint) x = (c (XVar x), c (XUnboundVar x), c (XConLikeOut x), c (XRecFld x), c (XOverLabel x), c (XIPVar x), c (XOverLitE x), c (XLitE x), c (XLam x), c (XLamCase x), c (XApp x), c (XAppTypeE x), c (XOpApp x), c (XNegApp x), c (XPar x), c (XSectionL x), c (XSectionR x), c (XExplicitTuple x), c (XExplicitSum x), c (XCase x), c (XIf x), c (XMultiIf x), c (XLet x), c (XDo x), c (XExplicitList x), c (XRecordCon x), c (XRecordUpd x), c (XExprWithTySig x), c (XArithSeq x), c (XSCC x), c (XCoreAnn x), c (XBracket x), c (XRnBracketOut x), c (XTcBracketOut x), c (XSpliceE x), c (XProc x), c (XStatic x), c (XTick x), c (XBinTick x), c (XTickPragma x), c (XWrap x), c (XXExpr x)) #
type family XUnambiguous x #
Instances
| type XUnambiguous GhcPs | |
Defined in GHC.Hs.Types | |
| type XUnambiguous GhcRn | |
Defined in GHC.Hs.Types | |
| type XUnambiguous GhcTc | |
Defined in GHC.Hs.Types | |
type family XAmbiguous x #
Instances
| type XAmbiguous GhcPs | |
Defined in GHC.Hs.Types | |
| type XAmbiguous GhcRn | |
Defined in GHC.Hs.Types | |
| type XAmbiguous GhcTc | |
Defined in GHC.Hs.Types | |
type family XXAmbiguousFieldOcc x #
Instances
| type XXAmbiguousFieldOcc (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type ForallXAmbiguousFieldOcc (c :: Type -> Constraint) x = (c (XUnambiguous x), c (XAmbiguous x), c (XXAmbiguousFieldOcc x)) #
Instances
| type XPresent (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XMissing GhcPs | |
Defined in GHC.Hs.Expr | |
| type XMissing GhcRn | |
Defined in GHC.Hs.Expr | |
| type XMissing GhcTc | |
Defined in GHC.Hs.Expr | |
type ForallXTupArg (c :: Type -> Constraint) x = (c (XPresent x), c (XMissing x), c (XXTupArg x)) #
type family XTypedSplice x #
Instances
| type XTypedSplice (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XUntypedSplice x #
Instances
| type XUntypedSplice (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XQuasiQuote x #
Instances
| type XQuasiQuote (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XSpliced (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type ForallXSplice (c :: Type -> Constraint) x = (c (XTypedSplice x), c (XUntypedSplice x), c (XQuasiQuote x), c (XSpliced x), c (XXSplice x)) #
Instances
| type XExpBr (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XPatBr (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XDecBrL (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XDecBrG (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XTypBr (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XVarBr (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XTExpBr (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type ForallXBracket (c :: Type -> Constraint) x = (c (XExpBr x), c (XPatBr x), c (XDecBrL x), c (XDecBrG x), c (XTypBr x), c (XVarBr x), c (XTExpBr x), c (XXBracket x)) #
Instances
| type XCmdTop GhcPs | |
Defined in GHC.Hs.Expr | |
| type XCmdTop GhcRn | |
Defined in GHC.Hs.Expr | |
| type XCmdTop GhcTc | |
Defined in GHC.Hs.Expr | |
type ForallXCmdTop (c :: Type -> Constraint) x = (c (XCmdTop x), c (XXCmdTop x)) #
Instances
| type XMG GhcPs b | |
Defined in GHC.Hs.Expr | |
| type XMG GhcRn b | |
Defined in GHC.Hs.Expr | |
| type XMG GhcTc b | |
Defined in GHC.Hs.Expr | |
type family XXMatchGroup x b #
Instances
| type XXMatchGroup (GhcPass _1) b | |
Defined in GHC.Hs.Expr | |
type ForallXMatchGroup (c :: Type -> Constraint) x b = (c (XMG x b), c (XXMatchGroup x b)) #
Instances
| type XCMatch (GhcPass _1) b | |
Defined in GHC.Hs.Expr | |
type ForallXMatch (c :: Type -> Constraint) x b = (c (XCMatch x b), c (XXMatch x b)) #
Instances
| type XCGRHSs (GhcPass _1) b | |
Defined in GHC.Hs.Expr | |
type ForallXGRHSs (c :: Type -> Constraint) x b = (c (XCGRHSs x b), c (XXGRHSs x b)) #
Instances
| type XCGRHS (GhcPass _1) b | |
Defined in GHC.Hs.Expr | |
type ForallXGRHS (c :: Type -> Constraint) x b = (c (XCGRHS x b), c (XXGRHS x b)) #
type family XLastStmt x x' b #
Instances
| type XLastStmt (GhcPass _1) (GhcPass _2) b | |
Defined in GHC.Hs.Expr | |
type family XBindStmt x x' b #
Instances
| type XBindStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
| type XBindStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
| type XBindStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
type family XApplicativeStmt x x' b #
Instances
| type XApplicativeStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
| type XApplicativeStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
| type XApplicativeStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
type family XBodyStmt x x' b #
Instances
| type XBodyStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
| type XBodyStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
| type XBodyStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
Instances
| type XLetStmt (GhcPass _1) (GhcPass _2) b | |
Defined in GHC.Hs.Expr | |
Instances
| type XParStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
| type XParStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
| type XParStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
type family XTransStmt x x' b #
Instances
| type XTransStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
| type XTransStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
| type XTransStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
Instances
| type XRecStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
| type XRecStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
| type XRecStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
type ForallXStmtLR (c :: Type -> Constraint) x x' b = (c (XLastStmt x x' b), c (XBindStmt x x' b), c (XApplicativeStmt x x' b), c (XBodyStmt x x' b), c (XLetStmt x x' b), c (XParStmt x x' b), c (XTransStmt x x' b), c (XRecStmt x x' b), c (XXStmtLR x x' b)) #
type family XCmdArrApp x #
Instances
| type XCmdArrApp GhcPs | |
Defined in GHC.Hs.Expr | |
| type XCmdArrApp GhcRn | |
Defined in GHC.Hs.Expr | |
| type XCmdArrApp GhcTc | |
Defined in GHC.Hs.Expr | |
type family XCmdArrForm x #
Instances
| type XCmdArrForm (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XCmdApp (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XCmdLam (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XCmdPar (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XCmdCase (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XCmdIf (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XCmdLet (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
Instances
| type XCmdDo GhcPs | |
Defined in GHC.Hs.Expr | |
| type XCmdDo GhcRn | |
Defined in GHC.Hs.Expr | |
| type XCmdDo GhcTc | |
Defined in GHC.Hs.Expr | |
Instances
| type XCmdWrap (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type ForallXCmd (c :: Type -> Constraint) x = (c (XCmdArrApp x), c (XCmdArrForm x), c (XCmdApp x), c (XCmdLam x), c (XCmdPar x), c (XCmdCase x), c (XCmdIf x), c (XCmdLet x), c (XCmdDo x), c (XCmdWrap x), c (XXCmd x)) #
type family XParStmtBlock x x' #
Instances
| type XParStmtBlock (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Expr | |
type family XXParStmtBlock x x' #
Instances
| type XXParStmtBlock (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Expr | |
type ForallXParStmtBlock (c :: Type -> Constraint) x x' = (c (XParStmtBlock x x'), c (XXParStmtBlock x x')) #
type family XApplicativeArgOne x #
Instances
| type XApplicativeArgOne (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XApplicativeArgMany x #
Instances
| type XApplicativeArgMany (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type family XXApplicativeArg x #
Instances
| type XXApplicativeArg (GhcPass _1) | |
Defined in GHC.Hs.Expr | |
type ForallXApplicativeArg (c :: Type -> Constraint) x = (c (XApplicativeArgOne x), c (XApplicativeArgMany x), c (XXApplicativeArg x)) #
Instances
| type XHsChar (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
type family XHsCharPrim x #
Instances
| type XHsCharPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
Instances
| type XHsString (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
type family XHsStringPrim x #
Instances
| type XHsStringPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
Instances
| type XHsInt (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
type family XHsIntPrim x #
Instances
| type XHsIntPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
type family XHsWordPrim x #
Instances
| type XHsWordPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
type family XHsInt64Prim x #
Instances
| type XHsInt64Prim (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
type family XHsWord64Prim x #
Instances
| type XHsWord64Prim (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
type family XHsInteger x #
Instances
| type XHsInteger (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
Instances
| type XHsRat (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
type family XHsFloatPrim x #
Instances
| type XHsFloatPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
type family XHsDoublePrim x #
Instances
| type XHsDoublePrim (GhcPass _1) | |
Defined in GHC.Hs.Lit | |
type ForallXHsLit (c :: Type -> Constraint) x = (c (XHsChar x), c (XHsCharPrim x), c (XHsDoublePrim x), c (XHsFloatPrim x), c (XHsInt x), c (XHsInt64Prim x), c (XHsIntPrim x), c (XHsInteger x), c (XHsRat x), c (XHsString x), c (XHsStringPrim x), c (XHsWord64Prim x), c (XHsWordPrim x), c (XXLit x)) #
Helper to apply a constraint to all extension points. It has one entry per extension point type family.
Instances
| type XOverLit GhcPs | |
Defined in GHC.Hs.Lit | |
| type XOverLit GhcRn | |
Defined in GHC.Hs.Lit | |
| type XOverLit GhcTc | |
Defined in GHC.Hs.Lit | |
type ForallXOverLit (c :: Type -> Constraint) x = (c (XOverLit x), c (XXOverLit x)) #
Instances
| type XWildPat GhcPs | |
Defined in GHC.Hs.Pat | |
| type XWildPat GhcRn | |
Defined in GHC.Hs.Pat | |
| type XWildPat GhcTc | |
Defined in GHC.Hs.Pat | |
Instances
| type XVarPat (GhcPass _1) | |
Defined in GHC.Hs.Pat | |
Instances
| type XLazyPat (GhcPass _1) | |
Defined in GHC.Hs.Pat | |
Instances
| type XAsPat (GhcPass _1) | |
Defined in GHC.Hs.Pat | |
Instances
| type XParPat (GhcPass _1) | |
Defined in GHC.Hs.Pat | |
Instances
| type XBangPat (GhcPass _1) | |
Defined in GHC.Hs.Pat | |
Instances
| type XListPat GhcPs | |
Defined in GHC.Hs.Pat | |
| type XListPat GhcRn | |
Defined in GHC.Hs.Pat | |
| type XListPat GhcTc | |
Defined in GHC.Hs.Pat | |
Instances
| type XTuplePat GhcPs | |
Defined in GHC.Hs.Pat | |
| type XTuplePat GhcRn | |
Defined in GHC.Hs.Pat | |
| type XTuplePat GhcTc | |
Defined in GHC.Hs.Pat | |
Instances
| type XSumPat GhcPs | |
Defined in GHC.Hs.Pat | |
| type XSumPat GhcRn | |
Defined in GHC.Hs.Pat | |
| type XSumPat GhcTc | |
Defined in GHC.Hs.Pat | |
Instances
| type XViewPat GhcPs | |
Defined in GHC.Hs.Pat | |
| type XViewPat GhcRn | |
Defined in GHC.Hs.Pat | |
| type XViewPat GhcTc | |
Defined in GHC.Hs.Pat | |
type family XSplicePat x #
Instances
| type XSplicePat (GhcPass _1) | |
Defined in GHC.Hs.Pat | |
Instances
| type XLitPat (GhcPass _1) | |
Defined in GHC.Hs.Pat | |
Instances
| type XNPat GhcPs | |
Defined in GHC.Hs.Pat | |
| type XNPat GhcRn | |
Defined in GHC.Hs.Pat | |
| type XNPat GhcTc | |
Defined in GHC.Hs.Pat | |
type family XNPlusKPat x #
Instances
| type XNPlusKPat GhcPs | |
Defined in GHC.Hs.Pat | |
| type XNPlusKPat GhcRn | |
Defined in GHC.Hs.Pat | |
| type XNPlusKPat GhcTc | |
Defined in GHC.Hs.Pat | |
Instances
| type XSigPat GhcPs | |
Defined in GHC.Hs.Pat | |
| type XSigPat GhcRn | |
Defined in GHC.Hs.Pat | |
| type XSigPat GhcTc | |
Defined in GHC.Hs.Pat | |
Instances
| type XCoPat (GhcPass _1) | |
Defined in GHC.Hs.Pat | |
type ForallXPat (c :: Type -> Constraint) x = (c (XWildPat x), c (XVarPat x), c (XLazyPat x), c (XAsPat x), c (XParPat x), c (XBangPat x), c (XListPat x), c (XTuplePat x), c (XSumPat x), c (XViewPat x), c (XSplicePat x), c (XLitPat x), c (XNPat x), c (XNPlusKPat x), c (XSigPat x), c (XCoPat x), c (XXPat x)) #
Instances
| type XHsQTvs GhcPs | |
Defined in GHC.Hs.Types | |
| type XHsQTvs GhcRn | |
Defined in GHC.Hs.Types | |
| type XHsQTvs GhcTc | |
Defined in GHC.Hs.Types | |
type family XXLHsQTyVars x #
Instances
| type XXLHsQTyVars (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type ForallXLHsQTyVars (c :: Type -> Constraint) x = (c (XHsQTvs x), c (XXLHsQTyVars x)) #
Instances
| type XHsIB GhcPs _1 | |
Defined in GHC.Hs.Types | |
| type XHsIB GhcRn _1 | |
Defined in GHC.Hs.Types | |
| type XHsIB GhcTc _1 | |
Defined in GHC.Hs.Types | |
type family XXHsImplicitBndrs x b #
Instances
| type XXHsImplicitBndrs (GhcPass _1) _2 | |
Defined in GHC.Hs.Types | |
type ForallXHsImplicitBndrs (c :: Type -> Constraint) x b = (c (XHsIB x b), c (XXHsImplicitBndrs x b)) #
Instances
| type XHsWC GhcPs b | |
Defined in GHC.Hs.Types | |
| type XHsWC GhcRn b | |
Defined in GHC.Hs.Types | |
| type XHsWC GhcTc b | |
Defined in GHC.Hs.Types | |
type family XXHsWildCardBndrs x b #
Instances
| type XXHsWildCardBndrs (GhcPass _1) b | |
Defined in GHC.Hs.Types | |
type ForallXHsWildCardBndrs (c :: Type -> Constraint) x b = (c (XHsWC x b), c (XXHsWildCardBndrs x b)) #
Instances
| type XForAllTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XQualTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XTyVar (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XAppTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type family XAppKindTy x #
Instances
| type XAppKindTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XFunTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XListTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XTupleTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XSumTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XOpTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XParTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XIParamTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XStarTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XKindSig (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XSpliceTy GhcPs | |
Defined in GHC.Hs.Types | |
| type XSpliceTy GhcRn | |
Defined in GHC.Hs.Types | |
| type XSpliceTy GhcTc | |
Defined in GHC.Hs.Types | |
Instances
| type XDocTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XBangTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XRecTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type family XExplicitListTy x #
Instances
| type XExplicitListTy GhcPs | |
Defined in GHC.Hs.Types | |
| type XExplicitListTy GhcRn | |
Defined in GHC.Hs.Types | |
| type XExplicitListTy GhcTc | |
Defined in GHC.Hs.Types | |
type family XExplicitTupleTy x #
Instances
| type XExplicitTupleTy GhcPs | |
Defined in GHC.Hs.Types | |
| type XExplicitTupleTy GhcRn | |
Defined in GHC.Hs.Types | |
| type XExplicitTupleTy GhcTc | |
Defined in GHC.Hs.Types | |
Instances
| type XTyLit (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type family XWildCardTy x #
Instances
| type XWildCardTy (GhcPass _1) | |
Defined in GHC.Hs.Types | |
Instances
| type XXType (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type ForallXType (c :: Type -> Constraint) x = (c (XForAllTy x), c (XQualTy x), c (XTyVar x), c (XAppTy x), c (XAppKindTy x), c (XFunTy x), c (XListTy x), c (XTupleTy x), c (XSumTy x), c (XOpTy x), c (XParTy x), c (XIParamTy x), c (XStarTy x), c (XKindSig x), c (XSpliceTy x), c (XDocTy x), c (XBangTy x), c (XRecTy x), c (XExplicitListTy x), c (XExplicitTupleTy x), c (XTyLit x), c (XWildCardTy x), c (XXType x)) #
Helper to apply a constraint to all extension points. It has one entry per extension point type family.
type family XUserTyVar x #
Instances
| type XUserTyVar (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type family XKindedTyVar x #
Instances
| type XKindedTyVar (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type family XXTyVarBndr x #
Instances
| type XXTyVarBndr (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type ForallXTyVarBndr (c :: Type -> Constraint) x = (c (XUserTyVar x), c (XKindedTyVar x), c (XXTyVarBndr x)) #
type family XConDeclField x #
Instances
| type XConDeclField (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type family XXConDeclField x #
Instances
| type XXConDeclField (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type ForallXConDeclField (c :: Type -> Constraint) x = (c (XConDeclField x), c (XXConDeclField x)) #
type family XCFieldOcc x #
Instances
| type XCFieldOcc GhcPs | |
Defined in GHC.Hs.Types | |
| type XCFieldOcc GhcRn | |
Defined in GHC.Hs.Types | |
| type XCFieldOcc GhcTc | |
Defined in GHC.Hs.Types | |
type family XXFieldOcc x #
Instances
| type XXFieldOcc (GhcPass _1) | |
Defined in GHC.Hs.Types | |
type ForallXFieldOcc (c :: Type -> Constraint) x = (c (XCFieldOcc x), c (XXFieldOcc x)) #
type family XCImportDecl x #
Instances
| type XCImportDecl (GhcPass _1) | |
Defined in GHC.Hs.ImpExp | |
type family XXImportDecl x #
Instances
| type XXImportDecl (GhcPass _1) | |
Defined in GHC.Hs.ImpExp | |
type ForallXImportDecl (c :: Type -> Constraint) x = (c (XCImportDecl x), c (XXImportDecl x)) #
Instances
| type XIEVar (GhcPass _1) | |
Defined in GHC.Hs.ImpExp | |
type family XIEThingAbs x #
Instances
| type XIEThingAbs (GhcPass _1) | |
Defined in GHC.Hs.ImpExp | |
type family XIEThingAll x #
Instances
| type XIEThingAll (GhcPass _1) | |
Defined in GHC.Hs.ImpExp | |
type family XIEThingWith x #
Instances
| type XIEThingWith (GhcPass _1) | |
Defined in GHC.Hs.ImpExp | |
type family XIEModuleContents x #
Instances
| type XIEModuleContents (GhcPass _1) | |
Defined in GHC.Hs.ImpExp | |
Instances
| type XIEGroup (GhcPass _1) | |
Defined in GHC.Hs.ImpExp | |
Instances
| type XIEDoc (GhcPass _1) | |
Defined in GHC.Hs.ImpExp | |
type family XIEDocNamed x #
Instances
| type XIEDocNamed (GhcPass _1) | |
Defined in GHC.Hs.ImpExp | |
type ForallXIE (c :: Type -> Constraint) x = (c (XIEVar x), c (XIEThingAbs x), c (XIEThingAll x), c (XIEThingWith x), c (XIEModuleContents x), c (XIEGroup x), c (XIEDoc x), c (XIEDocNamed x), c (XXIE x)) #
class Convertable a b | a -> b where #
Conversion of annotations from one type index to another. This is required
where the AST is converted from one pass to another, and the extension values
need to be brought along if possible. So for example a SourceText is
converted via id, but needs a type signature to keep the type checker
happy.
Instances
| Convertable a a | |
Defined in GHC.Hs.Extension | |
type ConvertIdX a b = (XHsDoublePrim a ~ XHsDoublePrim b, XHsFloatPrim a ~ XHsFloatPrim b, XHsRat a ~ XHsRat b, XHsInteger a ~ XHsInteger b, XHsWord64Prim a ~ XHsWord64Prim b, XHsInt64Prim a ~ XHsInt64Prim b, XHsWordPrim a ~ XHsWordPrim b, XHsIntPrim a ~ XHsIntPrim b, XHsInt a ~ XHsInt b, XHsStringPrim a ~ XHsStringPrim b, XHsString a ~ XHsString b, XHsCharPrim a ~ XHsCharPrim b, XHsChar a ~ XHsChar b, XXLit a ~ XXLit b) #
A constraint capturing all the extension points that can be converted via
instance Convertable a a
type OutputableX p = (Outputable (XIPBinds p), Outputable (XViaStrategy p), Outputable (XViaStrategy GhcRn)) #
Provide a summary constraint that gives all am Outputable constraint to extension points needing one
type OutputableBndrId (pass :: Pass) = (OutputableBndr (NameOrRdrName (IdP (GhcPass pass))), OutputableBndr (IdP (GhcPass pass)), OutputableBndr (NameOrRdrName (IdP (NoGhcTc (GhcPass pass)))), OutputableBndr (IdP (NoGhcTc (GhcPass pass))), NoGhcTc (GhcPass pass) ~ NoGhcTc (NoGhcTc (GhcPass pass)), OutputableX (GhcPass pass), OutputableX (NoGhcTc (GhcPass pass))) #
Constraint type to bundle up the requirement for OutputableBndr on both
the p and the NameOrRdrName type for it
type family NameOrRdrName id where ... #
Follow the id, but never beyond Name. This is used in a HsMatchContext,
for printing messages related to a Match
Equations
| NameOrRdrName Id = Name | |
| NameOrRdrName Name = Name | |
| NameOrRdrName RdrName = RdrName |
isExportedId :: Var -> Bool #
isExportedIdVar means "don't throw this away"
mustHaveLocalBinding :: Var -> Bool #
mustHaveLocalBinding returns True of Ids and TyVars
that must have a binding in this module. The converse
is not quite right: there are some global Ids that must have
bindings, such as record selectors. But that doesn't matter,
because it's only used for assertions
isGlobalId :: Var -> Bool #
isLocalVar :: Var -> Bool #
isLocalVar returns True for type variables as well as local Ids
These are the variables that we need to pay attention to when finding free
variables, or doing dependency analysis.
isNonCoVarId :: Var -> Bool #
Is this a term variable (Id) that is not a coercion variable?
Satisfies .isId v ==> isCoVar v == not (isNonCoVarId v)
Is this a coercion variable?
Satisfies .isId v ==> isCoVar v == not (isNonCoVarId v)
Is this a value-level (i.e., computationally relevant) Identifier?
Satisfies isId = not . isTyVar.
Is this a type-level (i.e., computationally irrelevant, thus erasable)
variable? Satisfies isTyVar = not . isId.
setIdNotExported :: Id -> Id #
We can only do this to LocalIds
setIdExported :: Id -> Id #
globaliseId :: Id -> Id #
If it's a local, make it global
setIdDetails :: Id -> IdDetails -> Id #
lazySetIdInfo :: Id -> IdInfo -> Var #
mkExportedLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id #
Exported Vars will not be removed as dead code
idInfo :: HasDebugCallStack => Id -> IdInfo #
setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVar #
tcTyVarDetails :: TyVar -> TcTyVarDetails #
setTyVarKind :: TyVar -> Kind -> TyVar #
setTyVarName :: TyVar -> Name -> TyVar #
setTyVarUnique :: TyVar -> Unique -> TyVar #
isTyVarBinder :: TyCoVarBinder -> Bool #
mkTyVarBinders :: ArgFlag -> [TyVar] -> [TyVarBinder] #
Make many named binders Input vars should be type variables
mkTyCoVarBinders :: ArgFlag -> [TyCoVar] -> [TyCoVarBinder] #
Make many named binders
mkTyVarBinder :: ArgFlag -> TyVar -> TyVarBinder #
Make a named binder
var should be a type variable
mkTyCoVarBinder :: ArgFlag -> TyCoVar -> TyCoVarBinder #
Make a named binder
binderType :: VarBndr TyCoVar argf -> Type #
binderArgFlag :: VarBndr tv argf -> argf #
binderVars :: [VarBndr tv argf] -> [tv] #
argToForallVisFlag :: ArgFlag -> ForallVisFlag #
Convert an ArgFlag to its corresponding ForallVisFlag.
isInvisibleArgFlag :: ArgFlag -> Bool #
Does this ArgFlag classify an argument that is not written in Haskell?
isVisibleArgFlag :: ArgFlag -> Bool #
Does this ArgFlag classify an argument that is written in Haskell?
setVarType :: Id -> Type -> Id #
setVarName :: Var -> Name -> Var #
setVarUnique :: Var -> Unique -> Var #
nonDetCmpVar :: Var -> Var -> Ordering #
Compare Vars by their Uniques. This is what Ord Var does, provided here to make it explicit at the call-site that it can introduce non-determinism. See Note [Unique Determinism]
data ForallVisFlag #
Is a forall invisible (e.g., forall a b. {...}, with a dot) or visible
(e.g., forall a b -> {...}, with an arrow)?
Constructors
| ForallVis | A visible |
| ForallInvis | An invisible |
Instances
Constructors
| Bndr var argf |
Instances
| (Eq tyvar, Eq argf) => Eq (VarBndr tyvar argf) Source # | |
| (Data var, Data argf) => Data (VarBndr var argf) | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VarBndr var argf -> c (VarBndr var argf) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VarBndr var argf) # toConstr :: VarBndr var argf -> Constr # dataTypeOf :: VarBndr var argf -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (VarBndr var argf)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VarBndr var argf)) # gmapT :: (forall b. Data b => b -> b) -> VarBndr var argf -> VarBndr var argf # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VarBndr var argf -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VarBndr var argf -> r # gmapQ :: (forall d. Data d => d -> u) -> VarBndr var argf -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VarBndr var argf -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VarBndr var argf -> m (VarBndr var argf) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VarBndr var argf -> m (VarBndr var argf) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VarBndr var argf -> m (VarBndr var argf) # | |
| NamedThing tv => NamedThing (VarBndr tv flag) | |
| (Binary tv, Binary vis) => Binary (VarBndr tv vis) | |
| OutputableBndr tv => Outputable (VarBndr tv TyConBndrVis) | |
| Outputable tv => Outputable (VarBndr tv ArgFlag) | |
type TyCoVarBinder = VarBndr TyCoVar ArgFlag #
Variable Binder
A TyCoVarBinder is the binder of a ForAllTy
It's convenient to define this synonym here rather its natural
home in TyCoRep, because it's used in DataCon.hs-boot
A TyVarBinder is a binder with only TyVar
type TyVarBinder = VarBndr TyVar ArgFlag #
unicodeAnn :: AnnKeywordId -> AnnKeywordId #
Convert a normal annotation into its unicode equivalent one
getAndRemoveAnnotationComments :: ApiAnns -> SrcSpan -> ([Located AnnotationComment], ApiAnns) #
Retrieve the comments allocated to the current SrcSpan, and
remove them from the annotations
getAnnotationComments :: ApiAnns -> SrcSpan -> [Located AnnotationComment] #
getAndRemoveAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> ([SrcSpan], ApiAnns) #
getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan] #
data AnnKeywordId #
API Annotations exist so that tools can perform source to source conversions of Haskell code. They are used to keep track of the various syntactic keywords that are not captured in the existing AST.
The annotations, together with original source comments are made
available in the field of pm_annotations.
Comments are only retained if ParsedModule is set in
Opt_KeepRawTokenStream before parsing.DynFlags
The wiki page describing this feature is https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations
Note: in general the names of these are taken from the corresponding token, unless otherwise noted See note [Api annotations] above for details of the usage
Constructors
Instances
data AnnotationComment #
Constructors
| AnnDocCommentNext String | something beginning '-- |' |
| AnnDocCommentPrev String | something beginning '-- ^' |
| AnnDocCommentNamed String | something beginning '-- $' |
| AnnDocSection Int String | a section heading |
| AnnDocOptions String | doc options (prune, ignore-exports, etc) |
| AnnLineComment String | comment starting by "--" |
| AnnBlockComment String | comment in {- -} |
Instances
nilDataConKey :: Unique #
listTyConKey :: Unique #
starInfo :: Bool -> RdrName -> SDoc #
Display info about the treatment of * under NoStarIsType.
With StarIsType, three properties of * hold:
(a) it is not an infix operator (b) it is always in scope (c) it is a synonym for Data.Kind.Type
However, the user might not know that he's working on a module with NoStarIsType and write code that still assumes (a), (b), and (c), which actually do not hold in that module.
Violation of (a) shows up in the parser. For instance, in the following
examples, we have * not applied to enough arguments:
data A :: * data F :: * -> *
Violation of (b) or (c) show up in the renamer and the typechecker respectively. For instance:
type K = Either * Bool
This will parse differently depending on whether StarIsType is enabled, but it will parse nonetheless. With NoStarIsType it is parsed as a type operator, thus we have ((*) Either Bool). Now there are two cases to consider:
- There is no definition of (*) in scope. In this case the renamer will fail to look it up. This is a violation of assumption (b).
- There is a definition of the (*) type operator in scope (for example coming from GHC.TypeNats). In this case the user will get a kind mismatch error. This is a violation of assumption (c).
The user might unknowingly be working on a module with NoStarIsType
or use * as Type out of habit. So it is important to give a
hint whenever an assumption about * is violated. Unfortunately, it is
somewhat difficult to deal with (c), so we limit ourselves to (a) and (b).
starInfo generates an appropriate hint to the user depending on the
extensions enabled in the module and the name that triggered the error.
That is, if we have NoStarIsType and the error is related to * or its
Unicode variant, the resulting SDoc will contain a helpful suggestion.
Otherwise it is empty.
pprNameProvenance :: GlobalRdrElt -> SDoc #
Print out one place where the name was define/imported (With -dppr-debug, print them all)
isExplicitItem :: ImpItemSpec -> Bool #
importSpecLoc :: ImportSpec -> SrcSpan #
qualSpecOK :: ModuleName -> ImportSpec -> Bool #
Is in scope qualified with the given module?
unQualSpecOK :: ImportSpec -> Bool #
Is in scope unqualified?
bestImport :: [ImportSpec] -> ImportSpec #
shadowNames :: GlobalRdrEnv -> [Name] -> GlobalRdrEnv #
transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv #
Apply a transformation function to the GREs for these OccNames
mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv #
pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)] #
Pick GREs that are in scope *both* qualified *and* unqualified Return each GRE that is, as a pair (qual_gre, unqual_gre) These two GREs are the original GRE with imports filtered to express how it is in scope qualified an unqualified respectively
Used only for the 'module M' item in export list; see RnNames.exports_from_avail
pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt] #
Takes a list of GREs which have the right OccName x
Pick those GREs that are in scope
* Qualified, as x if want_qual is Qual M _
* Unqualified, as x if want_unqual is Unqual _
Return each such GRE, with its ImportSpecs filtered, to reflect how it is in scope qualified or unqualified respectively. See Note [GRE filtering]
unQualOK :: GlobalRdrElt -> Bool #
Test if an unqualified version of this thing would be in scope
isOverloadedRecFldGRE :: GlobalRdrElt -> Bool #
Is this a record field defined with DuplicateRecordFields? (See Note [Parents for record fields])
isRecFldGRE :: GlobalRdrElt -> Bool #
isLocalGRE :: GlobalRdrElt -> Bool #
getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]] #
lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt #
Look for precisely this Name in the environment, but with an OccName
that might differ from that of the Name. See lookupGRE_FieldLabel and
Note [Parents for record fields].
lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt #
Look for a particular record field selector in the environment, where the selector name and field label may be different: the GlobalRdrEnv is keyed on the label. See Note [Parents for record fields] for why this happens.
lookupGRE_Name :: GlobalRdrEnv -> Name -> Maybe GlobalRdrElt #
lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] #
greOccName :: GlobalRdrElt -> OccName #
lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt] #
pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc #
globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt] #
availFromGRE :: GlobalRdrElt -> AvailInfo #
gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo] #
Takes a list of distinct GREs and folds them
into AvailInfos. This is more efficient than mapping each individual
GRE to an AvailInfo and the folding using plusAvail but needs the
uniqueness assumption.
greParent_maybe :: GlobalRdrElt -> Maybe Name #
greSrcSpan :: GlobalRdrElt -> SrcSpan #
greRdrNames :: GlobalRdrElt -> [RdrName] #
gresFromAvail :: (Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt] #
localGREsFromAvail :: AvailInfo -> [GlobalRdrElt] #
gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt] #
make a GlobalRdrEnv where all the elements point to the same
Provenance (useful for "hiding" imports, or imports with no details).
delLocalRdrEnvList :: LocalRdrEnv -> [OccName] -> LocalRdrEnv #
inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool #
localRdrEnvElts :: LocalRdrEnv -> [Name] #
elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool #
lookupLocalRdrOcc :: LocalRdrEnv -> OccName -> Maybe Name #
lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name #
extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv #
extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv #
isExact_maybe :: RdrName -> Maybe Name #
isQual_maybe :: RdrName -> Maybe (ModuleName, OccName) #
isSrcRdrName :: RdrName -> Bool #
isRdrTyVar :: RdrName -> Bool #
isRdrDataCon :: RdrName -> Bool #
nameRdrName :: Name -> RdrName #
getRdrName :: NamedThing thing => thing -> RdrName #
mkQual :: NameSpace -> (FastString, FastString) -> RdrName #
Make a qualified RdrName in the given namespace and where the ModuleName and
the OccName are taken from the first and second elements of the tuple respectively
mkVarUnqual :: FastString -> RdrName #
mkUnqual :: NameSpace -> FastString -> RdrName #
mkRdrQual :: ModuleName -> OccName -> RdrName #
mkRdrUnqual :: OccName -> RdrName #
demoteRdrName :: RdrName -> Maybe RdrName #
rdrNameSpace :: RdrName -> NameSpace #
rdrNameOcc :: RdrName -> OccName #
Reader Name
Do not use the data constructors of RdrName directly: prefer the family
of functions that creates them, such as mkRdrUnqual
- Note: A Located RdrName will only have API Annotations if it is a compound one, e.g.
`bar` ( ~ )
AnnKeywordId:AnnType,AnnOpen'('or'['or'[:',AnnClose')'or']'or':]',,AnnBackquote'`',AnnValAnnTilde,
Constructors
| Unqual OccName | Unqualified name Used for ordinary, unqualified occurrences, e.g. |
| Qual ModuleName OccName | Qualified name A qualified name written by the user in
source code. The module isn't necessarily
the module where the thing is defined;
just the one from which it is imported.
Examples are |
| Orig Module OccName | Original name An original name; the module is the defining module.
This is used when GHC generates code that will be fed
into the renamer (e.g. from deriving clauses), but where
we want to say "Use Prelude.map dammit". One of these
can be created with |
| Exact Name | Exact name We know exactly the
Such a |
Instances
| Eq RdrName | |
| Data RdrName | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RdrName -> c RdrName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RdrName # toConstr :: RdrName -> Constr # dataTypeOf :: RdrName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RdrName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName) # gmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r # gmapQ :: (forall d. Data d => d -> u) -> RdrName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RdrName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName # | |
| Ord RdrName | |
| DisambInfixOp RdrName | |
| HasOccName RdrName | |
| Outputable RdrName | |
| OutputableBndr RdrName | |
Defined in RdrName Methods pprBndr :: BindingSite -> RdrName -> SDoc # pprPrefixOcc :: RdrName -> SDoc # pprInfixOcc :: RdrName -> SDoc # bndrIsJoin_maybe :: RdrName -> Maybe Int # | |
data LocalRdrEnv #
Local Reader Environment
This environment is used to store local bindings
(let, where, lambda, case).
It is keyed by OccName, because we never use it for qualified names
We keep the current mapping, *and* the set of all Names in scope
Reason: see Note [Splicing Exact names] in RnEnv
Instances
| Outputable LocalRdrEnv | |
Defined in RdrName | |
type GlobalRdrEnv = OccEnv [GlobalRdrElt] #
Global Reader Environment
Keyed by OccName; when looking up a qualified name
we look up the OccName part, and then check the Provenance
to see if the appropriate qualification is valid. This
saves routinely doubling the size of the env by adding both
qualified and unqualified names to the domain.
The list in the codomain is required because there may be name clashes These only get reported on lookup, not on construction
INVARIANT 1: All the members of the list have distinct
gre_name fields; that is, no duplicate Names
INVARIANT 2: Imported provenance => Name is an ExternalName However LocalDefs can have an InternalName. This happens only when type-checking a [d| ... |] Template Haskell quotation; see this note in RnNames Note [Top-level Names in Template Haskell decl quotes]
INVARIANT 3: If the GlobalRdrEnv maps [occ -> gre], then greOccName gre = occ
NB: greOccName gre is usually the same as nameOccName (gre_name gre), but not always in the case of record seectors; see greOccName
data GlobalRdrElt #
Global Reader Element
An element of the GlobalRdrEnv
Constructors
| GRE | |
Instances
| Eq GlobalRdrElt | |
Defined in RdrName | |
| Data GlobalRdrElt | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalRdrElt -> c GlobalRdrElt # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalRdrElt # toConstr :: GlobalRdrElt -> Constr # dataTypeOf :: GlobalRdrElt -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GlobalRdrElt) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalRdrElt) # gmapT :: (forall b. Data b => b -> b) -> GlobalRdrElt -> GlobalRdrElt # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r # gmapQ :: (forall d. Data d => d -> u) -> GlobalRdrElt -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt # | |
| Outputable GlobalRdrElt | |
Defined in RdrName | |
The children of a Name are the things that are abbreviated by the ".." notation in export lists. See Note [Parents]
Constructors
| NoParent | |
| ParentIs | |
| FldParent | See Note [Parents for record fields] |
Fields
| |
Instances
| Eq Parent | |
| Data Parent | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parent -> c Parent # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Parent # toConstr :: Parent -> Constr # dataTypeOf :: Parent -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Parent) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent) # gmapT :: (forall b. Data b => b -> b) -> Parent -> Parent # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r # gmapQ :: (forall d. Data d => d -> u) -> Parent -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Parent -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parent -> m Parent # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parent -> m Parent # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parent -> m Parent # | |
| Outputable Parent | |
data ImportSpec #
Import Specification
The ImportSpec of something says how it came to be imported
It's quite elaborate so that we can give accurate unused-name warnings.
Constructors
| ImpSpec | |
Fields
| |
Instances
| Eq ImportSpec | |
Defined in RdrName | |
| Data ImportSpec | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportSpec -> c ImportSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportSpec # toConstr :: ImportSpec -> Constr # dataTypeOf :: ImportSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImportSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec) # gmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> ImportSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec # | |
| Ord ImportSpec | |
Defined in RdrName Methods compare :: ImportSpec -> ImportSpec -> Ordering # (<) :: ImportSpec -> ImportSpec -> Bool # (<=) :: ImportSpec -> ImportSpec -> Bool # (>) :: ImportSpec -> ImportSpec -> Bool # (>=) :: ImportSpec -> ImportSpec -> Bool # max :: ImportSpec -> ImportSpec -> ImportSpec # min :: ImportSpec -> ImportSpec -> ImportSpec # | |
| Outputable ImportSpec | |
Defined in RdrName | |
data ImpDeclSpec #
Import Declaration Specification
Describes a particular import declaration and is
shared among all the Provenances for that decl
Constructors
| ImpDeclSpec | |
Fields
| |
Instances
| Eq ImpDeclSpec | |
Defined in RdrName | |
| Data ImpDeclSpec | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpDeclSpec # toConstr :: ImpDeclSpec -> Constr # dataTypeOf :: ImpDeclSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpDeclSpec) # gmapT :: (forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> ImpDeclSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec # | |
| Ord ImpDeclSpec | |
Defined in RdrName Methods compare :: ImpDeclSpec -> ImpDeclSpec -> Ordering # (<) :: ImpDeclSpec -> ImpDeclSpec -> Bool # (<=) :: ImpDeclSpec -> ImpDeclSpec -> Bool # (>) :: ImpDeclSpec -> ImpDeclSpec -> Bool # (>=) :: ImpDeclSpec -> ImpDeclSpec -> Bool # max :: ImpDeclSpec -> ImpDeclSpec -> ImpDeclSpec # min :: ImpDeclSpec -> ImpDeclSpec -> ImpDeclSpec # | |
data ImpItemSpec #
Import Item Specification
Describes import info a particular Name
Constructors
| ImpAll | The import had no import list, or had a hiding list |
| ImpSome | The import had an import list.
The import C( T(..) ) Here the constructors of |
Fields
| |
Instances
| Eq ImpItemSpec | |
Defined in RdrName | |
| Data ImpItemSpec | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpItemSpec # toConstr :: ImpItemSpec -> Constr # dataTypeOf :: ImpItemSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpItemSpec) # gmapT :: (forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> ImpItemSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec # | |
| Ord ImpItemSpec | |
Defined in RdrName Methods compare :: ImpItemSpec -> ImpItemSpec -> Ordering # (<) :: ImpItemSpec -> ImpItemSpec -> Bool # (<=) :: ImpItemSpec -> ImpItemSpec -> Bool # (>) :: ImpItemSpec -> ImpItemSpec -> Bool # (>=) :: ImpItemSpec -> ImpItemSpec -> Bool # max :: ImpItemSpec -> ImpItemSpec -> ImpItemSpec # min :: ImpItemSpec -> ImpItemSpec -> ImpItemSpec # | |
nubAvails :: [AvailInfo] -> [AvailInfo] #
Combines AvailInfos from the same family
avails may have several items with the same availName
E.g import Ix( Ix(..), index )
will give Ix(Ix,index,range) and Ix(index)
We want to combine these; addAvail does that
filterAvail :: (Name -> Bool) -> AvailInfo -> [AvailInfo] -> [AvailInfo] #
filters an AvailInfo by the given predicate
filterAvails :: (Name -> Bool) -> [AvailInfo] -> [AvailInfo] #
filters AvailInfos by the given predicate
availNamesWithOccs :: AvailInfo -> [(Name, OccName)] #
Names made available by the availability information, paired with
the OccName used to refer to each one.
When DuplicateRecordFields is in use, the Name may be the
mangled name of a record selector (e.g. $sel:foo:MkT) while the
OccName will be the label of the field (e.g. foo).
See Note [Representing fields in AvailInfo].
availsNamesWithOccs :: [AvailInfo] -> [(Name, OccName)] #
availFlds :: AvailInfo -> [FieldLabel] #
Fields made available by the availability information
availNonFldNames :: AvailInfo -> [Name] #
Names for non-fields made available by the availability information
availNamesWithSelectors :: AvailInfo -> [Name] #
All names made available by the availability information (including overloaded selectors)
availNames :: AvailInfo -> [Name] #
All names made available by the availability information (excluding overloaded selectors)
availName :: AvailInfo -> Name #
Just the main name made available, i.e. not the available pieces
of type or class brought into scope by the GenAvailInfo
availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo #
availsToNameSet :: [AvailInfo] -> NameSet #
stableAvailCmp :: AvailInfo -> AvailInfo -> Ordering #
Compare lexicographically
Records what things are "available", i.e. in scope
Constructors
| Avail Name | An ordinary identifier in scope |
| AvailTC | A type or class in scope The AvailTC Invariant: If the type or class is itself to be in scope, it must be first in this list. Thus, typically: AvailTC Eq [Eq, ==, \/=] [] |
Fields
| |
Instances
| Eq AvailInfo | Used when deciding if the interface has changed |
| Data AvailInfo | |
Defined in Avail Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AvailInfo -> c AvailInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AvailInfo # toConstr :: AvailInfo -> Constr # dataTypeOf :: AvailInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AvailInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AvailInfo) # gmapT :: (forall b. Data b => b -> b) -> AvailInfo -> AvailInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AvailInfo -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AvailInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> AvailInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AvailInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AvailInfo -> m AvailInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AvailInfo -> m AvailInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AvailInfo -> m AvailInfo # | |
| Binary AvailInfo | |
| Outputable AvailInfo | |
type FieldLabelString = FastString #
Field labels are just represented as strings; they are not necessarily unique (even within a module)
type FieldLabel = FieldLbl Name #
Fields in an algebraic record type
Constructors
| FieldLabel | |
Fields
| |
Instances
| Functor FieldLbl | |
| Foldable FieldLbl | |
Defined in FieldLabel Methods fold :: Monoid m => FieldLbl m -> m # foldMap :: Monoid m => (a -> m) -> FieldLbl a -> m # foldMap' :: Monoid m => (a -> m) -> FieldLbl a -> m # foldr :: (a -> b -> b) -> b -> FieldLbl a -> b # foldr' :: (a -> b -> b) -> b -> FieldLbl a -> b # foldl :: (b -> a -> b) -> b -> FieldLbl a -> b # foldl' :: (b -> a -> b) -> b -> FieldLbl a -> b # foldr1 :: (a -> a -> a) -> FieldLbl a -> a # foldl1 :: (a -> a -> a) -> FieldLbl a -> a # elem :: Eq a => a -> FieldLbl a -> Bool # maximum :: Ord a => FieldLbl a -> a # minimum :: Ord a => FieldLbl a -> a # | |
| Traversable FieldLbl | |
| Eq a => Eq (FieldLbl a) | |
| Data a => Data (FieldLbl a) | |
Defined in FieldLabel Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldLbl a -> c (FieldLbl a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLbl a) # toConstr :: FieldLbl a -> Constr # dataTypeOf :: FieldLbl a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLbl a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLbl a)) # gmapT :: (forall b. Data b => b -> b) -> FieldLbl a -> FieldLbl a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLbl a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLbl a -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldLbl a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLbl a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) # | |
| Binary a => Binary (FieldLbl a) | |
| Outputable a => Outputable (FieldLbl a) | |
concatDocs :: [HsDocString] -> Maybe HsDocString #
Concat docstrings with two newlines in between.
Empty docstrings are skipped.
If all inputs are empty, Nothing is returned.
appendDocs :: HsDocString -> HsDocString -> HsDocString #
Join two docstrings.
Non-empty docstrings are joined with two newlines in between, resulting in separate paragraphs.
ppr_mbDoc :: Maybe LHsDocString -> SDoc #
hsDocStringToByteString :: HsDocString -> ByteString #
Return the contents of a HsDocString as a UTF8-encoded ByteString.
unpackHDS :: HsDocString -> String #
mkHsDocStringUtf8ByteString :: ByteString -> HsDocString #
Create a HsDocString from a UTF8-encoded ByteString.
mkHsDocString :: String -> HsDocString #
data HsDocString #
Haskell Documentation String
Internally this is a UTF8-Encoded ByteString.
Instances
| Eq HsDocString | |
Defined in GHC.Hs.Doc | |
| Data HsDocString | |
Defined in GHC.Hs.Doc Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDocString -> c HsDocString # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsDocString # toConstr :: HsDocString -> Constr # dataTypeOf :: HsDocString -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsDocString) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsDocString) # gmapT :: (forall b. Data b => b -> b) -> HsDocString -> HsDocString # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDocString -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDocString -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDocString -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDocString -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDocString -> m HsDocString # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDocString -> m HsDocString # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDocString -> m HsDocString # | |
| Show HsDocString | |
Defined in GHC.Hs.Doc Methods showsPrec :: Int -> HsDocString -> ShowS # show :: HsDocString -> String # showList :: [HsDocString] -> ShowS # | |
| Binary HsDocString | |
Defined in GHC.Hs.Doc Methods put_ :: BinHandle -> HsDocString -> IO () # put :: BinHandle -> HsDocString -> IO (Bin HsDocString) # get :: BinHandle -> IO HsDocString # | |
| Outputable HsDocString | |
Defined in GHC.Hs.Doc | |
type LHsDocString = Located HsDocString #
Located Haskell Documentation String
newtype DeclDocMap #
Docs for declarations: functions, data types, instances, methods etc.
Constructors
| DeclDocMap (Map Name HsDocString) |
Instances
| Binary DeclDocMap | |
Defined in GHC.Hs.Doc Methods put_ :: BinHandle -> DeclDocMap -> IO () # put :: BinHandle -> DeclDocMap -> IO (Bin DeclDocMap) # get :: BinHandle -> IO DeclDocMap # | |
| Outputable DeclDocMap | |
Defined in GHC.Hs.Doc | |
Docs for arguments. E.g. function arguments, method arguments.
Instances
intersectFVs :: FreeVars -> FreeVars -> FreeVars #
isEmptyFVs :: NameSet -> Bool #
nameSetElemsStable :: NameSet -> [Name] #
Get the elements of a NameSet with some stable ordering. This only works for Names that originate in the source code or have been tidied. See Note [Deterministic UniqFM] to learn about nondeterminism
intersectsNameSet :: NameSet -> NameSet -> Bool #
True if there is a non-empty intersection.
s1 doesn't compute intersectsNameSet s2s2 if s1 is empty
delListFromNameSet :: NameSet -> [Name] -> NameSet #
intersectNameSet :: NameSet -> NameSet -> NameSet #
delFromNameSet :: NameSet -> Name -> NameSet #
elemNameSet :: Name -> NameSet -> Bool #
minusNameSet :: NameSet -> NameSet -> NameSet #
unionNameSets :: [NameSet] -> NameSet #
unionNameSet :: NameSet -> NameSet -> NameSet #
extendNameSet :: NameSet -> Name -> NameSet #
extendNameSetList :: NameSet -> [Name] -> NameSet #
unitNameSet :: Name -> NameSet #
emptyNameSet :: NameSet #
isEmptyNameSet :: NameSet -> Bool #
type DefUse = (Maybe Defs, Uses) #
(Just ds, us) => The use of any member of the ds
implies that all the us are used too.
Also, us may mention ds.
Nothing => Nothing is defined in this group, but
nevertheless all the uses are essential.
Used for instance declarations, for example
typeSymbolKind :: Kind #
typeNatKind :: Kind #
mkBoxedTupleTy :: [Type] -> Type #
Build the type of a small tuple that holds the specified type of thing Flattens 1-tuples. See Note [One-tuples].
coercibleTyCon :: TyCon #
liftedTypeKind :: Kind #
constraintKind :: Kind #
vecElemTyCon :: TyCon #
vecCountTyCon :: TyCon #
runtimeRepTy :: Type #
intRepDataConTy :: Type #
vec64DataConTy :: Type #
vec32DataConTy :: Type #
vec16DataConTy :: Type #
vec8DataConTy :: Type #
vec4DataConTy :: Type #
vec2DataConTy :: Type #
anyTypeOfKind :: Kind -> Type #
unboxedTupleKind :: [Type] -> Kind #
Specialization of unboxedTupleSumKind for tuples
Make a *promoted* list.
tupleTyConName :: TupleSort -> Arity -> Name #
pprPrefixName :: NamedThing a => a -> SDoc #
pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc #
getOccFS :: NamedThing a => a -> FastString #
getOccString :: NamedThing a => a -> String #
getSrcSpan :: NamedThing a => a -> SrcSpan #
getSrcLoc :: NamedThing a => a -> SrcLoc #
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"
pprNameDefnLoc :: Name -> SDoc #
pprDefinedAt :: Name -> SDoc #
pprNameUnqualified :: Name -> SDoc #
Print the string of Name unqualifiedly directly.
stableNameCmp :: Name -> Name -> Ordering #
Compare Names lexicographically This only works for Names that originate in the source code or have been tidied.
localiseName :: Name -> Name #
Make the Name into an internal name, regardless of what it was to begin with
tidyNameOcc :: Name -> OccName -> Name #
setNameLoc :: Name -> SrcSpan -> Name #
setNameUnique :: Name -> Unique -> Name #
mkFCallName :: Unique -> String -> Name #
Make a name for a foreign call
mkSysTvName :: Unique -> FastString -> Name #
mkSystemVarName :: Unique -> FastString -> Name #
mkSystemName :: Unique -> OccName -> Name #
Create a name brought into being by the compiler
mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name #
Create a name which is actually defined by the compiler itself
mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name #
Create a name which definitely originates in the given module
mkClonedInternalName :: Unique -> Name -> Name #
isSystemName :: Name -> Bool #
isDataConName :: Name -> Bool #
isTyConName :: Name -> Bool #
isTyVarName :: Name -> Bool #
nameIsFromExternalPackage :: UnitId -> Name -> Bool #
Returns True if the Name comes from some other package: neither this package nor the interactive package.
nameIsHomePackageImport :: Module -> Name -> Bool #
nameIsHomePackage :: Module -> Name -> Bool #
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 HscTypes
nameModule_maybe :: Name -> Maybe Module #
nameModule :: HasDebugCallStack => Name -> Module #
isHoleName :: Name -> Bool #
isInternalName :: Name -> Bool #
isExternalName :: Name -> Bool #
isBuiltInSyntax :: Name -> Bool #
isWiredInName :: Name -> Bool #
nameSrcSpan :: Name -> SrcSpan #
nameSrcLoc :: Name -> SrcLoc #
nameNameSpace :: Name -> NameSpace #
nameOccName :: Name -> OccName #
nameUnique :: Name -> Unique #
data BuiltInSyntax #
BuiltInSyntax is for things like (:), [] and tuples,
which have special syntactic forms. They aren't in scope
as such.
Constructors
| BuiltInSyntax | |
| UserSyntax |
class NamedThing a where #
A class allowing convenient access to the Name of various datatypes
Minimal complete definition
Instances
| NamedThing HoleFitCandidate | |
Defined in TcHoleFitTypes | |
| NamedThing ClsInst | |
| NamedThing FamInst | |
Defined in FamInstEnv | |
| NamedThing IfaceDecl | |
| NamedThing IfaceClassOp | |
Defined in IfaceSyn | |
| NamedThing IfaceConDecl | |
Defined in IfaceSyn | |
| NamedThing Class | |
| NamedThing ConLike | |
| NamedThing DataCon | |
| NamedThing PatSyn | |
| NamedThing TyThing | |
| NamedThing Var | |
| NamedThing TyCon | |
| NamedThing Name | |
| NamedThing (HsTyVarBndr GhcRn) | |
Defined in GHC.Hs.Types | |
| NamedThing (CoAxiom br) | |
| NamedThing e => NamedThing (Located e) | |
| NamedThing tv => NamedThing (VarBndr tv flag) | |
mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type #
Like mkTyCoForAllTy, but does not check the occurrence of the binder
See Note [Unused coercion variable in ForAllTy]
Constructors
| TyVarTy Var | Vanilla type or kind variable (*never* a coercion variable) |
| AppTy Type Type | Type application to something other than a 1) Function: must not be a 2) Argument type |
| TyConApp TyCon [KindOrType] | Application of a 1) Type constructor being applied to. 2) Type arguments. Might not have enough type arguments here to saturate the constructor. Even type synonyms are not necessarily saturated; for example unsaturated type synonyms can appear as the right hand side of a type synonym. |
| ForAllTy !TyCoVarBinder Type | A Π type. |
| FunTy | t1 -> t2 Very common, so an important special case See Note [Function types] |
| LitTy TyLit | Type literals are similar to type constructors. |
| CastTy Type KindCoercion | A kind cast. The coercion is always nominal. INVARIANT: The cast is never refl. INVARIANT: The Type is not a CastTy (use TransCo instead) See Note Respecting definitional equality and (EQ3) |
| CoercionTy Coercion | Injection of a Coercion into a type This should only ever be used in the RHS of an AppTy, in the list of a TyConApp, when applying a promoted GADT data constructor |
Instances
| Eq Type Source # | |
| Data Type | |
Defined in TyCoRep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type # 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 # | |
| NFData Type Source # | |
Defined in Language.Haskell.Liquid.GHC.Misc | |
| Default Type Source # | |
Defined in Language.Haskell.Liquid.Synthesize.GHC | |
| Outputable Type | |
| Fixpoint Type Source # | |
| PPrint Type Source # | |
Defined in Language.Haskell.Liquid.Types.PrettyPrint | |
| Subable Type Source # | |
| SubsTy TyVar Type SpecType Source # | |
| Eq (DeBruijn Type) | |
| Show (Axiom Var Type CoreExpr) Source # | |
A global typecheckable-thing, essentially anything that has a name.
Not to be confused with a TcTyThing, which is also a typecheckable
thing but in the *local* context. See TcEnv for how to retrieve
a TyThing given a Name.
Instances
A Coercion is concrete evidence of the equality/convertibility
of two types.
Constructors
| Refl Type | |
| GRefl Role Type MCoercionN | |
| TyConAppCo Role TyCon [Coercion] | |
| AppCo Coercion CoercionN | |
| ForAllCo TyCoVar KindCoercion Coercion | |
| FunCo Role Coercion Coercion | |
| CoVarCo CoVar | |
| AxiomInstCo (CoAxiom Branched) BranchIndex [Coercion] | |
| AxiomRuleCo CoAxiomRule [Coercion] | |
| UnivCo UnivCoProvenance Role Type Type | |
| SymCo Coercion | |
| TransCo Coercion Coercion | |
| NthCo Role Int Coercion | |
| LRCo LeftOrRight CoercionN | |
| InstCo Coercion CoercionN | |
| KindCo Coercion | |
| SubCo CoercionN | |
| HoleCo CoercionHole | See Note [Coercion holes] Only present during typechecking |
Instances
| Eq Coercion Source # | |
| Data Coercion | |
Defined in TyCoRep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Coercion -> c Coercion # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Coercion # toConstr :: Coercion -> Constr # dataTypeOf :: Coercion -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Coercion) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Coercion) # gmapT :: (forall b. Data b => b -> b) -> Coercion -> Coercion # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coercion -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coercion -> r # gmapQ :: (forall d. Data d => d -> u) -> Coercion -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Coercion -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coercion -> m Coercion # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion -> m Coercion # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion -> m Coercion # | |
| Outputable Coercion | |
| Subable Coercion Source # | |
| Eq (DeBruijn Coercion) | |
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.
Constructors
| UnsafeCoerceProv | From |
| PhantomProv KindCoercion | See Note [Phantom coercions]. Only in Phantom roled coercions |
| ProofIrrelProv KindCoercion | From the fact that any two coercions are considered equivalent. See Note [ProofIrrelProv]. Can be used in Nominal or Representational coercions |
| PluginProv String | From a plugin, which asserts that this coercion is sound. The string is for the use of the plugin. |
Instances
| Data UnivCoProvenance | |
Defined in TyCoRep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnivCoProvenance -> c UnivCoProvenance # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnivCoProvenance # toConstr :: UnivCoProvenance -> Constr # dataTypeOf :: UnivCoProvenance -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnivCoProvenance) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnivCoProvenance) # gmapT :: (forall b. Data b => b -> b) -> UnivCoProvenance -> UnivCoProvenance # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnivCoProvenance -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnivCoProvenance -> r # gmapQ :: (forall d. Data d => d -> u) -> UnivCoProvenance -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnivCoProvenance -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnivCoProvenance -> m UnivCoProvenance # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnivCoProvenance -> m UnivCoProvenance # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnivCoProvenance -> m UnivCoProvenance # | |
| Outputable UnivCoProvenance | |
Defined in TyCoRep | |
Constructors
| NumTyLit Integer | |
| StrTyLit FastString |
Instances
| Eq TyLit | |
| Data TyLit | |
Defined in TyCoRep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyLit -> c TyLit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyLit # dataTypeOf :: TyLit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyLit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyLit) # gmapT :: (forall b. Data b => b -> b) -> TyLit -> TyLit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r # gmapQ :: (forall d. Data d => d -> u) -> TyLit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyLit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit # | |
| Ord TyLit | |
| Outputable TyLit | |
data TyCoBinder #
A TyCoBinder represents an argument to a function. TyCoBinders can be
dependent (Named) or nondependent (Anon). They may also be visible or
not. See Note [TyCoBinders]
Constructors
| Named TyCoVarBinder | |
| Anon AnonArgFlag Type |
Instances
| Data TyCoBinder | |
Defined in TyCoRep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyCoBinder -> c TyCoBinder # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyCoBinder # toConstr :: TyCoBinder -> Constr # dataTypeOf :: TyCoBinder -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyCoBinder) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCoBinder) # gmapT :: (forall b. Data b => b -> b) -> TyCoBinder -> TyCoBinder # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r # gmapQ :: (forall d. Data d => d -> u) -> TyCoBinder -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyCoBinder -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder # | |
| Outputable TyCoBinder | |
Defined in TyCoRep | |
A semantically more meaningful type to represent what may or may not be a
useful Coercion.
Instances
| Data MCoercion | |
Defined in TyCoRep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MCoercion -> c MCoercion # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MCoercion # toConstr :: MCoercion -> Constr # dataTypeOf :: MCoercion -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MCoercion) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MCoercion) # gmapT :: (forall b. Data b => b -> b) -> MCoercion -> MCoercion # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MCoercion -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MCoercion -> r # gmapQ :: (forall d. Data d => d -> u) -> MCoercion -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MCoercion -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MCoercion -> m MCoercion # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MCoercion -> m MCoercion # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MCoercion -> m MCoercion # | |
| Outputable MCoercion | |
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"
type MCoercionN = MCoercion #
Argument Flag
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, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep
Instances
| Eq ArgFlag | |
| Data ArgFlag | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArgFlag -> c ArgFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArgFlag # toConstr :: ArgFlag -> Constr # dataTypeOf :: ArgFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArgFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgFlag) # gmapT :: (forall b. Data b => b -> b) -> ArgFlag -> ArgFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArgFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArgFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> ArgFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArgFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # | |
| Ord ArgFlag | |
| Binary ArgFlag | |
| Outputable ArgFlag | |
| Outputable tv => Outputable (VarBndr tv ArgFlag) | |
data AnonArgFlag #
The non-dependent version of ArgFlag.
Constructors
| VisArg | Used for |
| InvisArg | Used for |
Instances
| Eq AnonArgFlag | |
Defined in Var | |
| Data AnonArgFlag | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnonArgFlag -> c AnonArgFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnonArgFlag # toConstr :: AnonArgFlag -> Constr # dataTypeOf :: AnonArgFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnonArgFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnonArgFlag) # gmapT :: (forall b. Data b => b -> b) -> AnonArgFlag -> AnonArgFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnonArgFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnonArgFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> AnonArgFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnonArgFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnonArgFlag -> m AnonArgFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnonArgFlag -> m AnonArgFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnonArgFlag -> m AnonArgFlag # | |
| Ord AnonArgFlag | |
Defined in Var Methods compare :: AnonArgFlag -> AnonArgFlag -> Ordering # (<) :: AnonArgFlag -> AnonArgFlag -> Bool # (<=) :: AnonArgFlag -> AnonArgFlag -> Bool # (>) :: AnonArgFlag -> AnonArgFlag -> Bool # (>=) :: AnonArgFlag -> AnonArgFlag -> Bool # max :: AnonArgFlag -> AnonArgFlag -> AnonArgFlag # min :: AnonArgFlag -> AnonArgFlag -> AnonArgFlag # | |
| Binary AnonArgFlag | |
Defined in Var Methods put_ :: BinHandle -> AnonArgFlag -> IO () # put :: BinHandle -> AnonArgFlag -> IO (Bin AnonArgFlag) # get :: BinHandle -> IO AnonArgFlag # | |
| Outputable AnonArgFlag | |
Defined in Var | |
Variable
Essentially a typed Name, that may also contain some additional information
about the Var and its use sites.
Instances
| Eq Var | |
| Data Var | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Var -> c Var # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Var # dataTypeOf :: Var -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Var) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Var) # gmapT :: (forall b. Data b => b -> b) -> Var -> Var # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r # gmapQ :: (forall d. Data d => d -> u) -> Var -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Var -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Var -> m Var # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var # | |
| Ord Var | |
| Show CoreExpr Source # | |
| Show Var Source # | |
| NFData Var Source # | |
Defined in Language.Haskell.Liquid.GHC.Misc | |
| Hashable Var Source # | |
Defined in Language.Haskell.Liquid.GHC.Misc | |
| Default Var Source # | |
Defined in Language.Haskell.Liquid.Synthesize.GHC | |
| NamedThing Var | |
| HasOccName Var | |
| Uniquable Var | |
| Outputable Var | |
| Expression Var Source # | Converting to Fixpoint ---------------------------------------------------- |
Defined in Language.Haskell.Liquid.Types.RefType | |
| Symbolic Var Source # |
|
Defined in Language.Haskell.Liquid.GHC.Misc | |
| Loc Var Source # | |
Defined in Language.Haskell.Liquid.GHC.Misc | |
| Fixpoint Var Source # | |
| PPrint Var Source # | |
Defined in Language.Haskell.Liquid.Types.PrettyPrint | |
| CBVisitable CoreBind Source # | |
| Subable CoreExpr Source # | |
| Subable Var Source # | |
| ResolveSym Var Source # | |
| SubsTy TyVar Type SpecType Source # | |
| Eq (DeBruijn CoreExpr) | |
| Eq (DeBruijn CoreAlt) | |
| PPrint (Expr Var) Source # | |
Defined in Language.Haskell.Liquid.Types.PrettyPrint | |
| PPrint (Bind Var) Source # | |
Defined in Language.Haskell.Liquid.Types.PrettyPrint | |
| CBVisitable [CoreBind] Source # | |
| CBVisitable (Expr Var) Source # | |
| CBVisitable (Alt Var) Source # | |
| Subable (Alt Var) Source # | |
| Subable (Bind Var) Source # | |
| Show (Axiom Var Type CoreExpr) Source # | |
isWarnMsgFatal :: DynFlags -> WarnMsg -> Maybe (Maybe WarningFlag) #
Checks if given WarnMsg is a fatal warning.
prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a #
printOutputForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO () #
printInfoForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO () #
Arguments
| :: (MonadIO m, HasDynFlags m) | |
| => SDoc | The name of the phase |
| -> (a -> ()) | A function to force the result
(often either |
| -> m a | The body of the phase to be timed |
| -> m a |
Same as withTiming, but doesn't print timings in the
console (when given -vN, N >= 2 or -ddump-timings)
and gets the DynFlags from the given Monad.
See Note [withTiming] for more.
Arguments
| :: MonadIO m | |
| => DynFlags | DynFlags |
| -> SDoc | The name of the phase |
| -> (a -> ()) | A function to force the result
(often either |
| -> m a | The body of the phase to be timed |
| -> m a |
Same as withTiming, but doesn't print timings in the
console (when given -vN, N >= 2 or -ddump-timings).
See Note [withTiming] for more.
Arguments
| :: (MonadIO m, HasDynFlags m) | |
| => SDoc | The name of the phase |
| -> (a -> ()) | A function to force the result
(often either |
| -> m a | The body of the phase to be timed |
| -> m a |
Like withTiming but get DynFlags from the Monad.
Arguments
| :: MonadIO m | |
| => DynFlags | DynFlags |
| -> SDoc | The name of the phase |
| -> (a -> ()) | A function to force the result
(often either |
| -> m a | The body of the phase to be timed |
| -> m a |
Time a compilation phase.
When timings are enabled (e.g. with the -v2 flag), the allocations
and CPU time used by the phase will be reported to stderr. Consider
a typical usage:
withTiming getDynFlags (text "simplify") force PrintTimings pass.
When timings are enabled the following costs are included in the
produced accounting,
- The cost of executing
passto a resultrin WHNF - The cost of evaluating
force rto WHNF (e.g.())
The choice of the force function depends upon the amount of forcing
desired; the goal here is to ensure that the cost of evaluating the result
is, to the greatest extent possible, included in the accounting provided by
withTiming. Often the pass already sufficiently forces its result during
construction; in this case const () is a reasonable choice.
In other cases, it is necessary to evaluate the result to normal form, in
which case something like Control.DeepSeq.rnf is appropriate.
To avoid adversely affecting compiler performance when timings are not requested, the result is only forced when timings are enabled.
See Note [withTiming] for more.
compilationProgressMsg :: DynFlags -> String -> IO () #
fatalErrorMsg'' :: FatalMessager -> String -> IO () #
fatalErrorMsg :: DynFlags -> MsgDoc -> IO () #
warningMsg :: DynFlags -> MsgDoc -> IO () #
dumpSDocWithStyle :: PprStyle -> DynFlags -> DumpFlag -> String -> SDoc -> IO () #
Write out a dump. If --dump-to-file is set then this goes to a file. otherwise emit to stdout.
When hdr is empty, we print in a more compact format (no separators and
blank lines)
The DumpFlag is used only to choose the filename to use if --dump-to-file
is used; it is not used to decide whether to dump the output
dumpSDocForUser :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO () #
A wrapper around dumpSDocWithStyle which uses PprUser style.
dumpIfSet_dyn_printer :: PrintUnqualified -> DynFlags -> DumpFlag -> SDoc -> IO () #
a wrapper around dumpSDoc.
First check whether the dump flag is set
Do nothing if it is unset
Unlike dumpIfSet_dyn,
has a printer argument but no header argument
dumpIfSet_dyn :: DynFlags -> DumpFlag -> String -> SDoc -> IO () #
a wrapper around dumpSDoc.
First check whether the dump flag is set
Do nothing if it is unset
doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO () #
pprLocErrMsg :: ErrMsg -> SDoc #
pprErrMsgBagWithLoc :: Bag ErrMsg -> [SDoc] #
formatErrDoc :: DynFlags -> ErrDoc -> SDoc #
warningsToMessages :: DynFlags -> WarningMessages -> Messages #
errorsFound :: DynFlags -> Messages -> Bool #
isEmptyMessages :: Messages -> Bool #
mkPlainWarnMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg #
Variant that doesn't care about qualified/unqualified names
mkWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg #
A short (one-line) error message
mkLongWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg #
A long (multi-line) error message
mkPlainErrMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg #
Variant that doesn't care about qualified/unqualified names
mkErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg #
A short (one-line) error message
mkLongErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg #
A long (multi-line) error message
makeIntoWarning :: WarnReason -> ErrMsg -> ErrMsg #
pprMessageBag :: Bag MsgDoc -> SDoc #
unionMessages :: Messages -> Messages -> Messages #
getInvalids :: [Validity] -> [MsgDoc] #
type Messages = (WarningMessages, ErrorMessages) #
type WarningMessages = Bag WarnMsg #
type ErrorMessages = Bag ErrMsg #
Categorise error msgs by their importance. This is so each section can be rendered visually distinct. See Note [Error report] for where these come from.
tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName) #
avoidClashesOccEnv :: TidyOccEnv -> [OccName] -> TidyOccEnv #
initTidyOccEnv :: [OccName] -> TidyOccEnv #
mkMethodOcc :: OccName -> OccName #
Derive a name for the representation type constructor of a
data/newtype instance.
mkSuperDictAuxOcc :: Int -> OccName -> OccName #
mkDataConWorkerOcc :: OccName -> OccName #
mkRecFldSelOcc :: String -> OccName #
mkTyConRepOcc :: OccName -> OccName #
mkMaxTagOcc :: OccName -> OccName #
mkTag2ConOcc :: OccName -> OccName #
mkCon2TagOcc :: OccName -> OccName #
mkEqPredCoOcc :: OccName -> OccName #
mkInstTyCoOcc :: OccName -> OccName #
mkNewTyCoOcc :: OccName -> OccName #
mkClassDataConOcc :: OccName -> OccName #
mkRepEqOcc :: OccName -> OccName #
mkForeignExportOcc :: OccName -> OccName #
mkClassOpAuxOcc :: OccName -> OccName #
mkDefaultMethodOcc :: OccName -> OccName #
mkBuilderOcc :: OccName -> OccName #
mkMatcherOcc :: OccName -> OccName #
mkWorkerOcc :: OccName -> OccName #
mkDataConWrapperOcc :: OccName -> OccName #
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 TcTypeable.
isDefaultMethodOcc :: OccName -> Bool #
isDerivedOccName :: OccName -> Bool #
Test for definitions internally generated by GHC. This predicte is used to suppress printing of internal definitions in some debug prints
startsWithUnderscore :: OccName -> Bool #
Haskell 98 encourages compilers to suppress warnings about unsed
names in a pattern if they start with _: this implements that test
parenSymOcc :: OccName -> SDoc -> SDoc #
Wrap parens around an operator
Test if the OccName is that for any operator (whether
it is a data constructor or variable or whatever)
isDataSymOcc :: OccName -> Bool #
Test if the OccName is a data constructor that starts with
a symbol (e.g. :, or [])
Value OccNamess are those that are either in
the variable or data constructor namespaces
setOccNameSpace :: NameSpace -> OccName -> OccName #
occNameString :: OccName -> String #
intersectsOccSet :: OccSet -> OccSet -> Bool #
intersectOccSet :: OccSet -> OccSet -> OccSet #
isEmptyOccSet :: OccSet -> Bool #
elemOccSet :: OccName -> OccSet -> Bool #
minusOccSet :: OccSet -> OccSet -> OccSet #
unionManyOccSets :: [OccSet] -> OccSet #
unionOccSets :: OccSet -> OccSet -> OccSet #
extendOccSetList :: OccSet -> [OccName] -> OccSet #
extendOccSet :: OccSet -> OccName -> OccSet #
unitOccSet :: OccName -> OccSet #
emptyOccSet :: OccSet #
filterOccEnv :: (elt -> Bool) -> OccEnv elt -> OccEnv elt #
delListFromOccEnv :: OccEnv a -> [OccName] -> OccEnv a #
delFromOccEnv :: OccEnv a -> OccName -> OccEnv a #
mkOccEnv_C :: (a -> a -> a) -> [(OccName, a)] -> OccEnv a #
extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b #
extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a #
plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a #
plusOccEnv :: OccEnv a -> OccEnv a -> OccEnv a #
occEnvElts :: OccEnv a -> [a] #
foldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b #
elemOccEnv :: OccName -> OccEnv a -> Bool #
lookupOccEnv :: OccEnv a -> OccName -> Maybe a #
extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a #
extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a #
unitOccEnv :: OccName -> a -> OccEnv a #
emptyOccEnv :: OccEnv a #
nameSpacesRelated :: NameSpace -> NameSpace -> Bool #
demoteOccName :: OccName -> Maybe OccName #
mkClsOccFS :: FastString -> OccName #
mkTcOccFS :: FastString -> OccName #
mkTyVarOccFS :: FastString -> OccName #
mkTyVarOcc :: String -> OccName #
mkDataOccFS :: FastString -> OccName #
mkVarOccFS :: FastString -> OccName #
mkOccNameFS :: NameSpace -> FastString -> OccName #
pprOccName :: OccName -> SDoc #
pprNameSpaceBrief :: NameSpace -> SDoc #
pprNonVarNameSpace :: NameSpace -> SDoc #
pprNameSpace :: NameSpace -> SDoc #
isValNameSpace :: NameSpace -> Bool #
isVarNameSpace :: NameSpace -> Bool #
isTvNameSpace :: NameSpace -> Bool #
isTcClsNameSpace :: NameSpace -> Bool #
isDataConNameSpace :: NameSpace -> Bool #
Instances
| Eq NameSpace | |
| Ord NameSpace | |
| Binary NameSpace | |
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 HoleFitCandidate | |
Defined in TcHoleFitTypes Methods occName :: HoleFitCandidate -> OccName # | |
| HasOccName TcBinder | |
| HasOccName IfaceDecl | |
| HasOccName IfaceClassOp | |
Defined in IfaceSyn Methods occName :: IfaceClassOp -> OccName # | |
| HasOccName IfaceConDecl | |
Defined in IfaceSyn Methods occName :: IfaceConDecl -> OccName # | |
| HasOccName RdrName | |
| HasOccName Var | |
| HasOccName OccName | |
| HasOccName Name | |
| HasOccName name => HasOccName (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp Methods occName :: IEWrappedName name -> OccName # | |
Instances
| Data a => Data (OccEnv a) | |
Defined in OccName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OccEnv a -> c (OccEnv a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (OccEnv a) # toConstr :: OccEnv a -> Constr # dataTypeOf :: OccEnv a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (OccEnv a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (OccEnv a)) # gmapT :: (forall b. Data b => b -> b) -> OccEnv a -> OccEnv a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OccEnv a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OccEnv a -> r # gmapQ :: (forall d. Data d => d -> u) -> OccEnv a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OccEnv a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OccEnv a -> m (OccEnv a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OccEnv a -> m (OccEnv a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OccEnv a -> m (OccEnv a) # | |
| Outputable a => Outputable (OccEnv a) | |
type TidyOccEnv = UniqFM Int #
emptyFilesToClean :: FilesToClean #
An empty FilesToClean
isBmi2Enabled :: DynFlags -> Bool #
isBmiEnabled :: DynFlags -> Bool #
isAvx512pfEnabled :: DynFlags -> Bool #
isAvx512fEnabled :: DynFlags -> Bool #
isAvx512erEnabled :: DynFlags -> Bool #
isAvx512cdEnabled :: DynFlags -> Bool #
isAvx2Enabled :: DynFlags -> Bool #
isAvxEnabled :: DynFlags -> Bool #
isSse4_2Enabled :: DynFlags -> Bool #
isSse2Enabled :: DynFlags -> Bool #
isSseEnabled :: DynFlags -> Bool #
setUnsafeGlobalDynFlags :: DynFlags -> IO () #
tARGET_MAX_WORD :: DynFlags -> Integer #
tARGET_MAX_INT :: DynFlags -> Integer #
tARGET_MIN_INT :: DynFlags -> Integer #
mAX_PTR_TAG :: DynFlags -> Int #
wordAlignment :: DynFlags -> Alignment #
wORD_SIZE_IN_BITS :: DynFlags -> Int #
bLOCK_SIZE_W :: DynFlags -> Int #
iLDV_STATE_USE :: DynFlags -> Integer #
iLDV_STATE_CREATE :: DynFlags -> Integer #
iLDV_CREATE_MASK :: DynFlags -> Integer #
dYNAMIC_BY_DEFAULT :: DynFlags -> Bool #
wORDS_BIGENDIAN :: DynFlags -> Bool #
bITMAP_BITS_SHIFT :: DynFlags -> Int #
cLONG_LONG_SIZE :: DynFlags -> Int #
cLONG_SIZE :: DynFlags -> Int #
dOUBLE_SIZE :: DynFlags -> Int #
aP_STACK_SPLIM :: DynFlags -> Int #
rESERVED_STACK_WORDS :: DynFlags -> Int #
rESERVED_C_STACK_BYTES :: DynFlags -> Int #
mAX_Real_Long_REG :: DynFlags -> Int #
mAX_Real_XMM_REG :: DynFlags -> Int #
mAX_Real_Double_REG :: DynFlags -> Int #
mAX_Real_Float_REG :: DynFlags -> Int #
mAX_Real_Vanilla_REG :: DynFlags -> Int #
mAX_XMM_REG :: DynFlags -> Int #
mAX_Long_REG :: DynFlags -> Int #
mAX_Double_REG :: DynFlags -> Int #
mAX_Float_REG :: DynFlags -> Int #
mAX_Vanilla_REG :: DynFlags -> Int #
mUT_ARR_PTRS_CARD_BITS :: DynFlags -> Int #
mAX_CHARLIKE :: DynFlags -> Int #
mIN_CHARLIKE :: DynFlags -> Int #
mAX_INTLIKE :: DynFlags -> Int #
mIN_INTLIKE :: DynFlags -> Int #
mIN_PAYLOAD_SIZE :: DynFlags -> Int #
mAX_SPEC_AP_SIZE :: DynFlags -> Int #
mAX_SPEC_SELECTEE_SIZE :: DynFlags -> Int #
oFFSET_StgStack_stack :: DynFlags -> Int #
oFFSET_StgStack_sp :: DynFlags -> Int #
oFFSET_StgTSO_stackobj :: DynFlags -> Int #
oFFSET_StgTSO_cccs :: DynFlags -> Int #
oFFSET_StgArrBytes_bytes :: DynFlags -> Int #
sIZEOF_StgArrBytes_NoHdr :: DynFlags -> Int #
sIZEOF_StgSMPThunkHeader :: DynFlags -> Int #
oFFSET_StgHeader_ldvw :: DynFlags -> Int #
oFFSET_StgHeader_ccs :: DynFlags -> Int #
sIZEOF_CostCentreStack :: DynFlags -> Int #
oFFSET_bdescr_flags :: DynFlags -> Int #
oFFSET_bdescr_blocks :: DynFlags -> Int #
oFFSET_bdescr_free :: DynFlags -> Int #
oFFSET_bdescr_start :: DynFlags -> Int #
oFFSET_Capability_r :: DynFlags -> Int #
oFFSET_stgGCFun :: DynFlags -> Int #
oFFSET_stgGCEnter1 :: DynFlags -> Int #
oFFSET_StgRegTable_rCCCS :: DynFlags -> Int #
oFFSET_StgRegTable_rHp :: DynFlags -> Int #
oFFSET_StgRegTable_rSp :: DynFlags -> Int #
oFFSET_StgRegTable_rL1 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM6 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM5 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM4 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM3 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM2 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM1 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM6 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM5 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM4 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM3 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM2 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM1 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM6 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM5 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM4 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM3 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM2 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM1 :: DynFlags -> Int #
oFFSET_StgRegTable_rD6 :: DynFlags -> Int #
oFFSET_StgRegTable_rD5 :: DynFlags -> Int #
oFFSET_StgRegTable_rD4 :: DynFlags -> Int #
oFFSET_StgRegTable_rD3 :: DynFlags -> Int #
oFFSET_StgRegTable_rD2 :: DynFlags -> Int #
oFFSET_StgRegTable_rD1 :: DynFlags -> Int #
oFFSET_StgRegTable_rF6 :: DynFlags -> Int #
oFFSET_StgRegTable_rF5 :: DynFlags -> Int #
oFFSET_StgRegTable_rF4 :: DynFlags -> Int #
oFFSET_StgRegTable_rF3 :: DynFlags -> Int #
oFFSET_StgRegTable_rF2 :: DynFlags -> Int #
oFFSET_StgRegTable_rF1 :: DynFlags -> Int #
oFFSET_StgRegTable_rR10 :: DynFlags -> Int #
oFFSET_StgRegTable_rR9 :: DynFlags -> Int #
oFFSET_StgRegTable_rR8 :: DynFlags -> Int #
oFFSET_StgRegTable_rR7 :: DynFlags -> Int #
oFFSET_StgRegTable_rR6 :: DynFlags -> Int #
oFFSET_StgRegTable_rR5 :: DynFlags -> Int #
oFFSET_StgRegTable_rR4 :: DynFlags -> Int #
oFFSET_StgRegTable_rR3 :: DynFlags -> Int #
oFFSET_StgRegTable_rR2 :: DynFlags -> Int #
oFFSET_StgRegTable_rR1 :: DynFlags -> Int #
tICKY_BIN_COUNT :: DynFlags -> Int #
bLOCKS_PER_MBLOCK :: DynFlags -> Int #
bLOCK_SIZE :: DynFlags -> Int #
pROF_HDR_SIZE :: DynFlags -> Int #
sTD_HDR_SIZE :: DynFlags -> Int #
cONTROL_GROUP_CONST_291 :: DynFlags -> Int #
compilerInfo :: DynFlags -> [(String, String)] #
setFlagsFromEnvFile :: FilePath -> String -> DynP () #
canonicalizeModuleIfHome :: DynFlags -> Module -> Module #
canonicalizeHomeModule :: DynFlags -> ModuleName -> Module #
Given a ModuleName of a signature in the home library, find
out how it is instantiated. E.g., the canonical form of
A in p[A=q[]:A] is q[]:A.
unSetGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags #
setGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags #
dynamicGhc :: Bool #
rtsIsProfiled :: Bool #
Was the runtime system built with profiling enabled?
glasgowExtsFlags :: [Extension] #
warningHierarchies :: [[String]] #
Warning group hierarchies, where there is an explicit inclusion relation.
Each inner list is a hierarchy of warning groups, ordered from smallest to largest, where each group is a superset of the one before it.
Separating this from warningGroups allows for multiple
hierarchies with no inherent relation to be defined.
The special-case Weverything group is not included.
warningGroups :: [(String, [WarningFlag])] #
Warning groups.
As all warnings are in the Weverything set, it is ignored when displaying to the user which group a warning is in.
fLangFlags :: [FlagSpec Extension] #
These -f<blah> flags can all be reversed with -fno-<blah>
fFlags :: [FlagSpec GeneralFlag] #
These -f<blah> flags can all be reversed with -fno-<blah>
wWarningFlags :: [FlagSpec WarningFlag] #
These -W<blah> flags can all be reversed with -Wno-<blah>
flagsForCompletion :: Bool -> [String] #
Make a list of flags for shell completion. Filter all available flags into two groups, for interactive GHC vs all other.
flagsPackage :: [Flag (CmdLineP DynFlags)] #
flagsDynamic :: [Flag (CmdLineP DynFlags)] #
allNonDeprecatedFlags :: [String] #
All dynamic flags option strings without the deprecated ones. These are the user facing strings for enabling and disabling options.
updateWays :: DynFlags -> DynFlags #
putLogMsg :: DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO () #
Write an error or warning to the LogOutput.
Arguments
| :: MonadIO m | |
| => [Flag (CmdLineP DynFlags)] | valid flags to match against |
| -> Bool | are the arguments from the command line? |
| -> DynFlags | current dynamic flags |
| -> [Located String] | arguments to parse |
| -> m (DynFlags, [Located String], [Warn]) |
Parses the dynamically set flags for GHC. This is the most general form of the dynamic flag parser that the other methods simply wrap. It allows saying which flags are valid flags and indicating if we are parsing arguments from the command line or from a file pragma.
Arguments
| :: MonadIO m | |
| => DynFlags | |
| -> [Located String] | |
| -> m (DynFlags, [Located String], [Warn]) | Updated |
Like parseDynamicFlagsCmdLine but does not allow the package flags
(-package, -hide-package, -ignore-package, -hide-all-packages, -package-db).
Used to parse flags set in a modules pragma.
Arguments
| :: MonadIO m | |
| => DynFlags | |
| -> [Located String] | |
| -> m (DynFlags, [Located String], [Warn]) | Updated |
Parse dynamic flags from a list of command line arguments. Returns
the parsed DynFlags, the left-over arguments, and a list of warnings.
Throws a UsageError if errors occurred during parsing (such as unknown
flags or missing arguments).
updOptLevel :: Int -> DynFlags -> DynFlags #
Sets the DynFlags to be appropriate to the optimisation level
addPluginModuleName :: String -> DynFlags -> DynFlags #
thisPackage :: DynFlags -> UnitId #
thisUnitIdInsts :: DynFlags -> [(ModuleName, Module)] #
thisComponentId :: DynFlags -> ComponentId #
getVerbFlags :: DynFlags -> [String] #
Gets the verbosity flag for the current verbosity level. This is fed to
other tools, so GHC-specific verbosity flags like -ddump-most are not included
Arguments
| :: DynFlags |
|
| -> (DynFlags -> [a]) | Relevant record accessor: one of the |
| -> [a] | Correctly ordered extracted options |
Retrieve the options corresponding to a particular opt_* field in the correct order
unsafeFlagsForInfer :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)] #
A list of unsafe flags under Safe Haskell. Tuple elements are: * name of the flag * function to get srcspan that enabled the flag * function to test if the flag is on * function to turn the flag off
unsafeFlags :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)] #
A list of unsafe flags under Safe Haskell. Tuple elements are: * name of the flag * function to get srcspan that enabled the flag * function to test if the flag is on * function to turn the flag off
safeImplicitImpsReq :: DynFlags -> Bool #
Are all implicit imports required to be safe for this Safe Haskell mode? Implicit imports are things in the prelude. e.g System.IO when print is used.
safeDirectImpsReq :: DynFlags -> Bool #
Are all direct imports required to be safe for this Safe Haskell mode? Direct imports are when the code explicitly imports a module
safeImportsOn :: DynFlags -> Bool #
Test if Safe Imports are on in some form
safeInferOn :: DynFlags -> Bool #
Is the Safe Haskell safe inference mode active
safeLanguageOn :: DynFlags -> Bool #
Is the Safe Haskell safe language in use
safeHaskellModeEnabled :: DynFlags -> Bool #
safeHaskellOn :: DynFlags -> Bool #
Is Safe Haskell on in some way (including inference mode)
packageTrustOn :: DynFlags -> Bool #
Is the -fpackage-trust mode on
dynFlagDependencies :: DynFlags -> [ModuleName] #
Some modules have dependencies on others through the DynFlags rather than textual imports
xopt_set_unlessExplSpec :: Extension -> (DynFlags -> Extension -> DynFlags) -> DynFlags -> DynFlags #
Set or unset a Extension, unless it has been explicitly
set or unset before.
wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags #
Mark a WarningFlag as not fatal
wopt_set_fatal :: DynFlags -> WarningFlag -> DynFlags #
Mark a WarningFlag as fatal (do not set the flag)
wopt_fatal :: WarningFlag -> DynFlags -> Bool #
Test whether a WarningFlag is set as fatal
wopt_unset :: DynFlags -> WarningFlag -> DynFlags #
Unset a WarningFlag
wopt_set :: DynFlags -> WarningFlag -> DynFlags #
Set a WarningFlag
wopt :: WarningFlag -> DynFlags -> Bool #
Test whether a WarningFlag is set
gopt_unset :: DynFlags -> GeneralFlag -> DynFlags #
Unset a GeneralFlag
gopt_set :: DynFlags -> GeneralFlag -> DynFlags #
Set a GeneralFlag
gopt :: GeneralFlag -> DynFlags -> Bool #
Test whether a GeneralFlag is set
hasNoOptCoercion :: DynFlags -> Bool #
hasNoStateHack :: DynFlags -> Bool #
languageExtensions :: Maybe Language -> [Extension] #
The language extensions implied by the various language variants.
When updating this be sure to update the flag documentation in
docsusers-guideglasgow_exts.rst.
defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO () #
Like defaultLogActionHPutStrDoc but appends an extra newline.
interpreterDynamic :: DynFlags -> Bool #
interpreterProfiled :: DynFlags -> Bool #
interpWays :: [Way] #
defaultWays :: Settings -> [Way] #
defaultDynFlags :: Settings -> LlvmConfig -> DynFlags #
initDynFlags :: DynFlags -> IO DynFlags #
dynamicOutputFile :: DynFlags -> FilePath -> FilePath #
Compute the path of the dynamic object corresponding to an object file.
whenCannotGenerateDynamicToo :: MonadIO m => DynFlags -> m () -> m () #
ifGeneratingDynamicToo :: MonadIO m => DynFlags -> m a -> m a -> m a #
whenGeneratingDynamicToo :: MonadIO m => DynFlags -> m () -> m () #
wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag] #
wayGeneralFlags :: Platform -> Way -> [GeneralFlag] #
wayRTSOnly :: Way -> Bool #
mkBuildTag :: [Way] -> String #
positionIndependent :: DynFlags -> Bool #
Are we building with -fPIE or -fPIC enabled?
packageFlagsChanged :: DynFlags -> DynFlags -> Bool #
targetRetainsAllBindings :: HscTarget -> Bool #
Does this target retain *all* top-level bindings for a module, rather than just the exported bindings, in the TypeEnv and compiled code (if any)? In interpreted mode we do this, so that GHCi can call functions inside a module. In HscNothing mode we also do it, so that Haddock can get access to the GlobalRdrEnv for a module after typechecking it.
isObjectTarget :: HscTarget -> Bool #
Will this target result in an object file on the disk?
versionedFilePath :: DynFlags -> FilePath #
versionedAppDir :: DynFlags -> MaybeT IO FilePath #
The directory for this version of ghc in the user's app directory
(typically something like ~.ghcx86_64-linux-7.6.3)
tablesNextToCode :: DynFlags -> Bool #
opt_windres :: DynFlags -> [String] #
opt_P_signature :: DynFlags -> ([String], Fingerprint) #
pgm_ranlib :: DynFlags -> String #
pgm_libtool :: DynFlags -> String #
pgm_windres :: DynFlags -> String #
systemPackageConfig :: DynFlags -> FilePath #
extraGccViaCFlags :: DynFlags -> [String] #
ghciUsagePath :: DynFlags -> FilePath #
ghcUsagePath :: DynFlags -> FilePath #
projectVersion :: DynFlags -> String #
programName :: DynFlags -> String #
backendMaintainsCfg :: DynFlags -> Bool #
flattenIncludes :: IncludeSpecs -> [String] #
Concatenate and flatten the list of global and quoted includes returning just a flat list of paths.
addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs #
Append to the list of includes a path that shall be included using `-iquote` when the C compiler is called. These paths only apply when quoted includes are used. e.g. #include "foo.h"
addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs #
Append to the list of includes a path that shall be included using `-I` when the C compiler is called. These paths override system search paths.
data WarnReason #
Used when outputting warnings: if a reason is given, it is displayed. If a warning isn't controlled by a flag, this is made explicit at the point of use.
Constructors
| NoReason | |
| Reason !WarningFlag | Warning was enabled with the flag |
| ErrReason !(Maybe WarningFlag) | Warning was made an error because of -Werror or -Werror=WarningFlag |
Instances
| Show WarnReason | |
Defined in DynFlags Methods showsPrec :: Int -> WarnReason -> ShowS # show :: WarnReason -> String # showList :: [WarnReason] -> ShowS # | |
| ToJson WarnReason | |
Defined in DynFlags Methods json :: WarnReason -> JsonDoc # | |
| Outputable WarnReason | |
Defined in DynFlags | |
data IncludeSpecs #
Used to differentiate the scope an include needs to apply to. We have to split the include paths to avoid accidentally forcing recursive includes since -I overrides the system search paths. See #14312.
Constructors
| IncludeSpecs | |
Fields
| |
Instances
| Show IncludeSpecs | |
Defined in DynFlags Methods showsPrec :: Int -> IncludeSpecs -> ShowS # show :: IncludeSpecs -> String # showList :: [IncludeSpecs] -> ShowS # | |
data WarningFlag #
Constructors
Instances
| Enum WarningFlag | |
Defined in DynFlags Methods succ :: WarningFlag -> WarningFlag # pred :: WarningFlag -> WarningFlag # toEnum :: Int -> WarningFlag # fromEnum :: WarningFlag -> Int # enumFrom :: WarningFlag -> [WarningFlag] # enumFromThen :: WarningFlag -> WarningFlag -> [WarningFlag] # enumFromTo :: WarningFlag -> WarningFlag -> [WarningFlag] # enumFromThenTo :: WarningFlag -> WarningFlag -> WarningFlag -> [WarningFlag] # | |
| Eq WarningFlag | |
Defined in DynFlags | |
| Show WarningFlag | |
Defined in DynFlags Methods showsPrec :: Int -> WarningFlag -> ShowS # show :: WarningFlag -> String # showList :: [WarningFlag] -> ShowS # | |
Constructors
| Haskell98 | |
| Haskell2010 |
Instances
| Enum Language | |
| Eq Language | |
| Show Language | |
| Outputable Language | |
data SafeHaskellMode #
The various Safe Haskell modes
Constructors
| Sf_None | inferred unsafe |
| Sf_Unsafe | declared and checked |
| Sf_Trustworthy | declared and checked |
| Sf_Safe | declared and checked |
| Sf_SafeInferred | inferred as safe |
| Sf_Ignore |
|
Instances
| Eq SafeHaskellMode | |
Defined in DynFlags Methods (==) :: SafeHaskellMode -> SafeHaskellMode -> Bool # (/=) :: SafeHaskellMode -> SafeHaskellMode -> Bool # | |
| Show SafeHaskellMode | |
Defined in DynFlags Methods showsPrec :: Int -> SafeHaskellMode -> ShowS # show :: SafeHaskellMode -> String # showList :: [SafeHaskellMode] -> ShowS # | |
| Outputable SafeHaskellMode | |
Defined in DynFlags | |
data CfgWeights #
Edge weights to use when generating a CFG from CMM
Constructors
| CFGWeights | |
Fields
| |
class HasDynFlags (m :: Type -> Type) where #
Methods
getDynFlags :: m DynFlags #
Instances
class ContainsDynFlags t where #
Methods
extractDynFlags :: t -> DynFlags #
Instances
| ContainsDynFlags (Env gbl lcl) | |
Defined in TcRnTypes Methods extractDynFlags :: Env gbl lcl -> DynFlags # | |
Constructors
| NoProfAuto | no SCC annotations added |
| ProfAutoAll | top-level and nested functions are annotated |
| ProfAutoTop | top-level functions annotated only |
| ProfAutoExports | exported functions annotated only |
| ProfAutoCalls | annotate call-sites |
Instances
| Enum ProfAuto | |
| Eq ProfAuto | |
data LlvmTarget #
Constructors
| LlvmTarget | |
Fields
| |
data LlvmConfig #
See Note [LLVM Configuration] in SysTools.
Constructors
| LlvmConfig | |
Fields
| |
The target code type of the compilation (if any).
Whenever you change the target, also make sure to set ghcLink to
something sensible.
HscNothing can be used to avoid generating any output, however, note
that:
- If a program uses Template Haskell the typechecker may need to run code from an imported module. To facilitate this, code generation is enabled for modules imported by modules that use template haskell. See Note [-fno-code mode].
Constructors
| HscC | Generate C code. |
| HscAsm | Generate assembly using the native code generator. |
| HscLlvm | Generate assembly using the llvm code generator. |
| HscInterpreted | Generate bytecode. (Requires |
| HscNothing | Don't generate any code. See notes above. |
The GhcMode tells us whether we're doing multi-module
compilation (controlled via the GHC API) or one-shot
(single-module) compilation. This makes a difference primarily to
the Finder: in one-shot mode we look for interface files for
imported modules, but in multi-module mode we look for source files
in order to check whether they need to be recompiled.
Constructors
| CompManager |
|
| OneShot | ghc -c Foo.hs |
| MkDepend |
|
What to do in the link step, if there is one.
Constructors
| NoLink | Don't link at all |
| LinkBinary | Link object code into a binary |
| LinkInMemory | Use the in-memory dynamic linker (works for both bytecode and object code). |
| LinkDynLib | Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms) |
| LinkStaticLib | Link objects into a static lib |
data PackageArg #
We accept flags which make packages visible, but how they select the package varies; this data type reflects what selection criterion is used.
Constructors
| PackageArg String |
|
| UnitIdArg UnitId |
|
Instances
| Eq PackageArg | |
Defined in DynFlags | |
| Show PackageArg | |
Defined in DynFlags Methods showsPrec :: Int -> PackageArg -> ShowS # show :: PackageArg -> String # showList :: [PackageArg] -> ShowS # | |
| Outputable PackageArg | |
Defined in DynFlags | |
data ModRenaming #
Represents the renaming that may be associated with an exposed
package, e.g. the rns part of -package "foo (rns)".
Here are some example parsings of the package flags (where
a string literal is punned to be a ModuleName:
Constructors
| ModRenaming | |
Fields
| |
Instances
| Eq ModRenaming | |
Defined in DynFlags | |
| Outputable ModRenaming | |
Defined in DynFlags | |
newtype IgnorePackageFlag #
Flags for manipulating the set of non-broken packages.
Constructors
| IgnorePackage String | -ignore-package |
Instances
| Eq IgnorePackageFlag | |
Defined in DynFlags Methods (==) :: IgnorePackageFlag -> IgnorePackageFlag -> Bool # (/=) :: IgnorePackageFlag -> IgnorePackageFlag -> Bool # | |
Flags for manipulating package trust.
Constructors
| TrustPackage String | -trust |
| DistrustPackage String | -distrust |
data PackageFlag #
Flags for manipulating packages visibility.
Constructors
| ExposePackage String PackageArg ModRenaming |
|
| HidePackage String | -hide-package |
Instances
| Eq PackageFlag | |
Defined in DynFlags | |
| Outputable PackageFlag | |
Defined in DynFlags | |
data PackageDBFlag #
Instances
| Eq PackageDBFlag | |
Defined in DynFlags Methods (==) :: PackageDBFlag -> PackageDBFlag -> Bool # (/=) :: PackageDBFlag -> PackageDBFlag -> Bool # | |
data DynLibLoader #
Constructors
| Deployable | |
| SystemDependent |
Instances
| Eq DynLibLoader | |
Defined in DynFlags | |
data RtsOptsEnabled #
Instances
| Show RtsOptsEnabled | |
Defined in DynFlags Methods showsPrec :: Int -> RtsOptsEnabled -> ShowS # show :: RtsOptsEnabled -> String # showList :: [RtsOptsEnabled] -> ShowS # | |
Constructors
| WayCustom String | |
| WayThreaded | |
| WayDebug | |
| WayProf | |
| WayEventLog | |
| WayDyn |
type FatalMessager = String -> IO () #
Constructors
| FlagSpec | |
Fields
| |
data PkgConfRef #
Constructors
| GlobalPkgConf | |
| UserPkgConf | |
| PkgConfFile FilePath |
Instances
| Eq PkgConfRef | |
Defined in DynFlags | |
data LinkerInfo #
Constructors
| GnuLD [Option] | |
| GnuGold [Option] | |
| LlvmLLD [Option] | |
| DarwinLD [Option] | |
| SolarisLD [Option] | |
| AixLD [Option] | |
| UnknownLD |
Instances
| Eq LinkerInfo | |
Defined in DynFlags | |
data CompilerInfo #
Constructors
| GCC | |
| Clang | |
| AppleClang | |
| AppleClang51 | |
| UnknownCC |
Instances
| Eq CompilerInfo | |
Defined in DynFlags | |
data FilesToClean #
A collection of files that must be deleted before ghc exits.
The current collection
is stored in an IORef in DynFlags, filesToClean.
Constructors
| FilesToClean | |
Fields
| |
isHsigFile :: HscSource -> Bool #
isHsBootOrSig :: HscSource -> Bool #
hscSourceString :: HscSource -> String #
Constructors
| HsSrcFile | |
| HsBootFile | |
| HsigFile |
Instances
| Eq HscSource | |
| Ord HscSource | |
| Show HscSource | |
| Binary HscSource | |
unitModuleSet :: Module -> ModuleSet #
unionModuleSet :: ModuleSet -> ModuleSet -> ModuleSet #
delModuleSet :: ModuleSet -> Module -> ModuleSet #
minusModuleSet :: ModuleSet -> ModuleSet -> ModuleSet #
intersectModuleSet :: ModuleSet -> ModuleSet -> ModuleSet #
elemModuleSet :: Module -> ModuleSet -> Bool #
moduleSetElts :: ModuleSet -> [Module] #
extendModuleSetList :: ModuleSet -> [Module] -> ModuleSet #
extendModuleSet :: ModuleSet -> Module -> ModuleSet #
mkModuleSet :: [Module] -> ModuleSet #
isEmptyModuleEnv :: ModuleEnv a -> Bool #
unitModuleEnv :: Module -> a -> ModuleEnv a #
moduleEnvToList :: ModuleEnv a -> [(Module, a)] #
moduleEnvElts :: ModuleEnv a -> [a] #
moduleEnvKeys :: ModuleEnv a -> [Module] #
emptyModuleEnv :: ModuleEnv a #
mkModuleEnv :: [(Module, a)] -> ModuleEnv a #
mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b #
lookupWithDefaultModuleEnv :: ModuleEnv a -> a -> Module -> a #
lookupModuleEnv :: ModuleEnv a -> Module -> Maybe a #
plusModuleEnv :: ModuleEnv a -> ModuleEnv a -> ModuleEnv a #
delModuleEnv :: ModuleEnv a -> Module -> ModuleEnv a #
delModuleEnvList :: ModuleEnv a -> [Module] -> ModuleEnv a #
plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a #
extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a #
extendModuleEnvList :: ModuleEnv a -> [(Module, a)] -> ModuleEnv a #
extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a #
extendModuleEnv :: ModuleEnv a -> Module -> a -> ModuleEnv a #
elemModuleEnv :: Module -> ModuleEnv a -> Bool #
wiredInUnitIds :: [UnitId] #
isHoleModule :: Module -> Bool #
isInteractiveModule :: Module -> Bool #
mainUnitId :: UnitId #
This is the package Id for the current program. It is the default package Id if you don't specify a package name. We don't add this prefix to symbol names, since there can be only one main package per program.
thisGhcUnitId :: UnitId #
baseUnitId :: UnitId #
integerUnitId :: UnitId #
primUnitId :: UnitId #
parseModSubst :: ReadP [(ModuleName, Module)] #
parseUnitId :: ReadP UnitId #
splitUnitIdInsts :: UnitId -> (InstalledUnitId, Maybe IndefUnitId) #
See splitModuleInsts.
splitModuleInsts :: Module -> (InstalledModule, Maybe IndefModule) #
Given a possibly on-the-fly instantiated module, split it into
a Module that we definitely can find on-disk, as well as an
instantiation if we need to instantiate it on the fly. If the
instantiation is Nothing no on-the-fly renaming is needed.
renameHoleUnitId' :: PackageConfigMap -> ShHoleSubst -> UnitId -> UnitId #
Like 'renameHoleUnitId, but requires only PackageConfigMap
so it can be used by Packages.
renameHoleModule' :: PackageConfigMap -> ShHoleSubst -> Module -> Module #
Like renameHoleModule, but requires only PackageConfigMap
so it can be used by Packages.
renameHoleUnitId :: DynFlags -> ShHoleSubst -> UnitId -> UnitId #
renameHoleModule :: DynFlags -> ShHoleSubst -> Module -> Module #
stringToUnitId :: String -> UnitId #
fsToUnitId :: FastString -> UnitId #
Create a new simple unit identifier from a FastString. Internally,
this is primarily used to specify wired-in unit identifiers.
newSimpleUnitId :: ComponentId -> UnitId #
Create a new simple unit identifier (no holes) from a ComponentId.
stableUnitIdCmp :: UnitId -> UnitId -> Ordering #
Compares package ids lexically, rather than by their Uniques
newUnitId :: ComponentId -> [(ModuleName, Module)] -> UnitId #
Create a new, un-hashed unit identifier.
hashUnitId :: ComponentId -> [(ModuleName, Module)] -> FastString #
Generate a uniquely identifying FastString for a unit
identifier. This is a one-way function. You can rely on one special
property: if a unit identifier is in most general form, its FastString
coincides with its ComponentId. This hash is completely internal
to GHC and is not used for symbol names or file paths.
unitIdIsDefinite :: UnitId -> Bool #
A UnitId is definite if it has no free holes.
unitIdFreeHoles :: UnitId -> UniqDSet ModuleName #
Retrieve the set of free holes of a UnitId.
filterInstalledModuleEnv :: (InstalledModule -> a -> Bool) -> InstalledModuleEnv a -> InstalledModuleEnv a #
extendInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> a -> InstalledModuleEnv a #
lookupInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> Maybe a #
installedUnitIdEq :: InstalledUnitId -> UnitId -> Bool #
Test if a UnitId corresponds to a given InstalledUnitId,
modulo instantiation.
installedModuleEq :: InstalledModule -> Module -> Bool #
Test if a Module corresponds to a given InstalledModule,
modulo instantiation.
toInstalledUnitId :: UnitId -> InstalledUnitId #
Lossy conversion to the on-disk InstalledUnitId for a component.
indefModuleToModule :: DynFlags -> IndefModule -> Module #
Injects an IndefModule to Module (see also
indefUnitIdToUnitId.
indefUnitIdToUnitId :: DynFlags -> IndefUnitId -> UnitId #
Injects an IndefUnitId (indefinite library which
was on-the-fly instantiated) to a UnitId (either
an indefinite or definite library).
newIndefUnitId :: ComponentId -> [(ModuleName, Module)] -> IndefUnitId #
Create a new IndefUnitId given an explicit module substitution.
unitIdFS :: UnitId -> FastString #
mkModule :: UnitId -> ModuleName -> Module #
stableModuleCmp :: Module -> Module -> Ordering #
This gives a stable ordering, as opposed to the Ord instance which
gives an ordering based on the Uniques of the components, which may
not be stable from run to run of the compiler.
mkHoleModule :: ModuleName -> Module #
Create a module variable at some ModuleName.
See Note [Representation of module/name variables]
moduleIsDefinite :: Module -> Bool #
A Module is definite if it has no free holes.
moduleFreeHoles :: Module -> UniqDSet ModuleName #
Calculate the free holes of a Module. If this set is non-empty,
this module was defined in an indefinite library that had required
signatures.
If a module has free holes, that means that substitutions can operate on it; if it has no free holes, substituting over a module has no effect.
moduleNameColons :: ModuleName -> String #
Returns the string version of the module name, with dots replaced by colons.
moduleNameSlashes :: ModuleName -> String #
Returns the string version of the module name, with dots replaced by slashes.
mkModuleNameFS :: FastString -> ModuleName #
mkModuleName :: String -> ModuleName #
moduleStableString :: Module -> String #
Get a string representation of a Module that's unique and stable
across recompilations.
eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal"
moduleNameString :: ModuleName -> String #
moduleNameFS :: ModuleName -> FastString #
pprModuleName :: ModuleName -> SDoc #
stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering #
Compares module names lexically, rather than by their Uniques
addBootSuffixLocnOut :: ModLocation -> ModLocation #
Add the -boot suffix to all output file paths associated with the
module, not including the input file itself
addBootSuffixLocn :: ModLocation -> ModLocation #
Add the -boot suffix to all file paths associated with the module
addBootSuffix_maybe :: Bool -> FilePath -> FilePath #
Add the -boot suffix if the Bool argument is True
addBootSuffix :: FilePath -> FilePath #
Add the -boot suffix to .hs, .hi and .o files
data ModLocation #
Module Location
Where a module lives on the file system: the actual locations of the .hs, .hi and .o files, if we have them
Constructors
| ModLocation | |
Fields
| |
Instances
| Show ModLocation | |
Defined in Module Methods showsPrec :: Int -> ModLocation -> ShowS # show :: ModLocation -> String # showList :: [ModLocation] -> ShowS # | |
| Outputable ModLocation | |
Defined in Module | |
class ContainsModule t where #
Methods
extractModule :: t -> Module #
Instances
| ContainsModule DsGblEnv | |
Defined in TcRnTypes Methods extractModule :: DsGblEnv -> Module # | |
| ContainsModule TcGblEnv | |
Defined in TcRnTypes Methods extractModule :: TcGblEnv -> Module # | |
| ContainsModule gbl => ContainsModule (Env gbl lcl) | |
Defined in TcRnTypes Methods extractModule :: Env gbl lcl -> Module # | |
data IndefUnitId #
A unit identifier which identifies an indefinite
library (with holes) that has been *on-the-fly* instantiated
with a substitution indefUnitIdInsts. In fact, an indefinite
unit identifier could have no holes, but we haven't gotten
around to compiling the actual library yet.
An indefinite unit identifier pretty-prints to something like
p[H=H,A=aimpl:A>] (p is the ComponentId, and the
brackets enclose the module substitution).
Constructors
| IndefUnitId | |
Fields
| |
Instances
| Eq IndefUnitId | |
Defined in Module | |
| Ord IndefUnitId | |
Defined in Module Methods compare :: IndefUnitId -> IndefUnitId -> Ordering # (<) :: IndefUnitId -> IndefUnitId -> Bool # (<=) :: IndefUnitId -> IndefUnitId -> Bool # (>) :: IndefUnitId -> IndefUnitId -> Bool # (>=) :: IndefUnitId -> IndefUnitId -> Bool # max :: IndefUnitId -> IndefUnitId -> IndefUnitId # min :: IndefUnitId -> IndefUnitId -> IndefUnitId # | |
| Binary IndefUnitId | |
Defined in Module Methods put_ :: BinHandle -> IndefUnitId -> IO () # put :: BinHandle -> IndefUnitId -> IO (Bin IndefUnitId) # get :: BinHandle -> IO IndefUnitId # | |
| Outputable IndefUnitId | |
Defined in Module | |
data IndefModule #
Constructors
| IndefModule | |
Fields | |
Instances
| Eq IndefModule | |
Defined in Module | |
| Ord IndefModule | |
Defined in Module Methods compare :: IndefModule -> IndefModule -> Ordering # (<) :: IndefModule -> IndefModule -> Bool # (<=) :: IndefModule -> IndefModule -> Bool # (>) :: IndefModule -> IndefModule -> Bool # (>=) :: IndefModule -> IndefModule -> Bool # max :: IndefModule -> IndefModule -> IndefModule # min :: IndefModule -> IndefModule -> IndefModule # | |
| Outputable IndefModule | |
Defined in Module | |
data InstalledModule #
A InstalledModule is a Module which contains a InstalledUnitId.
Constructors
| InstalledModule | |
Fields | |
Instances
| Eq InstalledModule | |
Defined in Module Methods (==) :: InstalledModule -> InstalledModule -> Bool # (/=) :: InstalledModule -> InstalledModule -> Bool # | |
| Ord InstalledModule | |
Defined in Module Methods compare :: InstalledModule -> InstalledModule -> Ordering # (<) :: InstalledModule -> InstalledModule -> Bool # (<=) :: InstalledModule -> InstalledModule -> Bool # (>) :: InstalledModule -> InstalledModule -> Bool # (>=) :: InstalledModule -> InstalledModule -> Bool # max :: InstalledModule -> InstalledModule -> InstalledModule # min :: InstalledModule -> InstalledModule -> InstalledModule # | |
| Outputable InstalledModule | |
Defined in Module | |
A DefUnitId is an InstalledUnitId with the invariant that
it only refers to a definite library; i.e., one we have generated
code for.
Constructors
| DefUnitId | |
Fields | |
Instances
| Eq DefUnitId | |
| Ord DefUnitId | |
| Binary DefUnitId | |
| Outputable DefUnitId | |
data InstalledModuleEnv elt #
A map keyed off of InstalledModule
type ShHoleSubst = ModuleNameEnv Module #
Substitution on module variables, mapping module names to module identifiers.
type ModuleNameEnv elt = UniqFM elt #
A map keyed off of ModuleNames (actually, their Uniques)
type DModuleNameEnv elt = UniqDFM elt #
A map keyed off of ModuleNames (actually, their Uniques)
Has deterministic folds and can be deterministically converted to a list
mkFsEnv :: [(FastString, a)] -> FastStringEnv a #
lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a #
extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a #
emptyFsEnv :: FastStringEnv a #
type FastStringEnv a = UniqFM a #
A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in UniqDFM 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.
mkTcOccUnique :: FastString -> Unique #
mkTvOccUnique :: FastString -> Unique #
mkDataOccUnique :: FastString -> Unique #
mkVarOccUnique :: FastString -> Unique #
mkCostCentreUnique :: Int -> Unique #
mkRegClassUnique :: Int -> Unique #
mkRegPairUnique :: Int -> Unique #
mkRegSubUnique :: Int -> Unique #
mkRegSingleUnique :: Int -> Unique #
mkPseudoUniqueH :: Int -> Unique #
mkPseudoUniqueE :: Int -> Unique #
mkPseudoUniqueD :: Int -> Unique #
mkBuiltinUnique :: Int -> Unique #
mkPreludeMiscIdUnique :: Int -> Unique #
mkPrimOpWrapperUnique :: Int -> Unique #
mkPrimOpIdUnique :: Int -> Unique #
dataConTyRepNameUnique :: Unique -> Unique #
dataConWorkerUnique :: Unique -> Unique #
mkPreludeDataConUnique :: Arity -> Unique #
tyConRepNameUnique :: Unique -> Unique #
mkPreludeTyConUnique :: Int -> Unique #
mkPreludeClassUnique :: Int -> Unique #
mkCoVarUnique :: Int -> Unique #
mkAlphaTyVarUnique :: Int -> Unique #
pprUniqueAlways :: Unique -> SDoc #
nonDetCmpUnique :: Unique -> Unique -> Ordering #
isValidKnownKeyUnique :: Unique -> Bool #
The interface file symbol-table encoding assumes that known-key uniques fit in 30-bits; verify this.
See Note [Symbol table representation of names] in BinIface for details.
unpkUnique :: Unique -> (Char, Int) #
newTagUnique :: Unique -> Char -> Unique #
deriveUnique :: Unique -> Int -> Unique #
mkUniqueGrimily :: Int -> Unique #
uNIQUE_BITS :: Int #
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.
Class of things that we can obtain a Unique from
Instances
isKindLevel :: TypeOrKind -> Bool #
isTypeLevel :: TypeOrKind -> Bool #
mkIntWithInf :: Int -> IntWithInf #
Inject any integer into an IntWithInf
treatZeroAsInf :: Int -> IntWithInf #
Turn a positive number into an IntWithInf, where 0 represents infinity
intGtLimit :: Int -> IntWithInf -> Bool #
infinity :: IntWithInf #
A representation of infinity
integralFractionalLit :: Bool -> Integer -> FractionalLit #
mkFractionalLit :: Real a => a -> FractionalLit #
mkIntegralLit :: Integral a => a -> IntegralLit #
isEarlyActive :: Activation -> Bool #
isAlwaysActive :: Activation -> Bool #
isNeverActive :: Activation -> Bool #
competesWith :: Activation -> Activation -> Bool #
isActiveIn :: PhaseNum -> Activation -> Bool #
isActive :: CompilerPhase -> Activation -> Bool #
pprInlineDebug :: InlinePragma -> SDoc #
pprInline :: InlinePragma -> SDoc #
inlinePragmaSat :: InlinePragma -> Maybe Arity #
isAnyInlinePragma :: InlinePragma -> Bool #
isInlinablePragma :: InlinePragma -> Bool #
isInlinePragma :: InlinePragma -> Bool #
noUserInlineSpec :: InlineSpec -> Bool #
isFunLike :: RuleMatchInfo -> Bool #
isConLike :: RuleMatchInfo -> Bool #
pprWithSourceText :: SourceText -> SDoc -> SDoc #
Special combinator for showing string literals.
failed :: SuccessFlag -> Bool #
succeeded :: SuccessFlag -> Bool #
successIf :: Bool -> SuccessFlag #
zapFragileOcc :: OccInfo -> OccInfo #
isStrongLoopBreaker :: OccInfo -> Bool #
isWeakLoopBreaker :: OccInfo -> Bool #
isAlwaysTailCalled :: OccInfo -> Bool #
zapOccTailCallInfo :: OccInfo -> OccInfo #
tailCallInfo :: OccInfo -> TailCallInfo #
seqOccInfo :: OccInfo -> () #
isManyOccs :: OccInfo -> Bool #
Arguments
| :: (a -> SDoc) | The pretty printing function to use |
| -> a | The things to be pretty printed |
| -> ConTag | Alternative (one-based) |
| -> Arity | Arity |
| -> SDoc |
|
Pretty print an alternative in an unboxed sum e.g. "| a | |".
tupleParens :: TupleSort -> SDoc -> SDoc #
boxityTupleSort :: Boxity -> TupleSort #
tupleSortBoxity :: TupleSort -> Boxity #
hasOverlappingFlag :: OverlapMode -> Bool #
hasOverlappableFlag :: OverlapMode -> Bool #
hasIncoherentFlag :: OverlapMode -> Bool #
isGenerated :: Origin -> Bool #
boolToRecFlag :: Bool -> RecFlag #
isTopLevel :: TopLevelFlag -> Bool #
isNotTopLevel :: TopLevelFlag -> Bool #
funTyFixity :: Fixity #
negateFixity :: Fixity #
defaultFixity :: Fixity #
minPrecedence :: Int #
maxPrecedence :: Int #
pprRuleName :: RuleName -> SDoc #
pprWarningTxtForMsg :: WarningTxt -> SDoc #
bumpVersion :: Version -> Version #
isPromoted :: PromotionFlag -> Bool #
bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo #
worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo #
hasNoOneShotInfo :: OneShotInfo -> Bool #
isOneShotInfo :: OneShotInfo -> Bool #
noOneShotInfo :: OneShotInfo #
It is always safe to assume that an Id has no lambda-bound variable information
alignmentOf :: Int -> Alignment #
mkAlignment :: Int -> Alignment #
pickLR :: LeftOrRight -> (a, a) -> a #
data LeftOrRight #
Instances
| Eq LeftOrRight | |
Defined in BasicTypes | |
| Data LeftOrRight | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LeftOrRight # toConstr :: LeftOrRight -> Constr # dataTypeOf :: LeftOrRight -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LeftOrRight) # gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r # gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # | |
| Outputable LeftOrRight | |
Defined in BasicTypes | |
The number of value arguments that can be applied to a value before it does "real work". So: fib 100 has arity 0 x -> fib x has arity 1 See also Note [Definition of arity] in CoreArity
The number of arguments that a join point takes. Unlike the arity of a function, this is a purely syntactic property and is fixed when the join point is created (or converted from a value). Both type and value arguments are counted.
Constructor Tag
Type of the tags associated with each constructor possibility or superclass selector
A power-of-two alignment
Instances
| Eq Alignment | |
| Ord Alignment | |
| Outputable Alignment | |
data OneShotInfo #
If the Id is a lambda-bound variable then it may have lambda-bound
variable info. Sometimes we know whether the lambda binding this variable
is a "one-shot" lambda; that is, whether it is applied at most once.
This information may be useful in optimisation, as computations may safely be floated inside such a lambda without risk of duplicating work.
Constructors
| NoOneShotInfo | No information |
| OneShotLam | The lambda is applied at most once. |
Instances
| Eq OneShotInfo | |
Defined in BasicTypes | |
| Outputable OneShotInfo | |
Defined in BasicTypes | |
Constructors
| NotSwapped | |
| IsSwapped |
data PromotionFlag #
Is a TyCon a promoted data constructor or just a normal type constructor?
Constructors
| NotPromoted | |
| IsPromoted |
Instances
| Eq PromotionFlag | |
Defined in BasicTypes Methods (==) :: PromotionFlag -> PromotionFlag -> Bool # (/=) :: PromotionFlag -> PromotionFlag -> Bool # | |
| Data PromotionFlag | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PromotionFlag # toConstr :: PromotionFlag -> Constr # dataTypeOf :: PromotionFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PromotionFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PromotionFlag) # gmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> PromotionFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # | |
data FunctionOrData #
Constructors
| IsFunction | |
| IsData |
Instances
data StringLiteral #
A String Literal in the source, including its original raw format for use by source to source manipulation tools.
Constructors
| StringLiteral | |
Fields
| |
Instances
| Eq StringLiteral | |
Defined in BasicTypes Methods (==) :: StringLiteral -> StringLiteral -> Bool # (/=) :: StringLiteral -> StringLiteral -> Bool # | |
| Data StringLiteral | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StringLiteral -> c StringLiteral # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StringLiteral # toConstr :: StringLiteral -> Constr # dataTypeOf :: StringLiteral -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StringLiteral) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StringLiteral) # gmapT :: (forall b. Data b => b -> b) -> StringLiteral -> StringLiteral # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StringLiteral -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StringLiteral -> r # gmapQ :: (forall d. Data d => d -> u) -> StringLiteral -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StringLiteral -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral # | |
| Outputable StringLiteral | |
Defined in BasicTypes | |
data WarningTxt #
Warning Text
reason/explanation from a WARNING or DEPRECATED pragma
Constructors
| WarningTxt (Located SourceText) [Located StringLiteral] | |
| DeprecatedTxt (Located SourceText) [Located StringLiteral] |
Instances
| Eq WarningTxt | |
Defined in BasicTypes | |
| Data WarningTxt | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarningTxt -> c WarningTxt # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WarningTxt # toConstr :: WarningTxt -> Constr # dataTypeOf :: WarningTxt -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WarningTxt) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WarningTxt) # gmapT :: (forall b. Data b => b -> b) -> WarningTxt -> WarningTxt # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarningTxt -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarningTxt -> r # gmapQ :: (forall d. Data d => d -> u) -> WarningTxt -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarningTxt -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt # | |
| Outputable WarningTxt | |
Defined in BasicTypes | |
type RuleName = FastString #
Constructors
| Fixity SourceText Int FixityDirection |
Instances
| Eq Fixity | |
| Data Fixity | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixity -> c Fixity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixity # toConstr :: Fixity -> Constr # dataTypeOf :: Fixity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Fixity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity) # gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r # gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # | |
| Outputable Fixity | |
data FixityDirection #
Instances
| Eq FixityDirection | |
Defined in BasicTypes Methods (==) :: FixityDirection -> FixityDirection -> Bool # (/=) :: FixityDirection -> FixityDirection -> Bool # | |
| Data FixityDirection | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixityDirection -> c FixityDirection # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FixityDirection # toConstr :: FixityDirection -> Constr # dataTypeOf :: FixityDirection -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FixityDirection) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FixityDirection) # gmapT :: (forall b. Data b => b -> b) -> FixityDirection -> FixityDirection # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r # gmapQ :: (forall d. Data d => d -> u) -> FixityDirection -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FixityDirection -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # | |
| Outputable FixityDirection | |
Defined in BasicTypes | |
data LexicalFixity #
Captures the fixity of declarations as they are parsed. This is not necessarily the same as the fixity declaration, as the normal fixity may be overridden using parens or backticks.
Instances
| Eq LexicalFixity | |
Defined in BasicTypes Methods (==) :: LexicalFixity -> LexicalFixity -> Bool # (/=) :: LexicalFixity -> LexicalFixity -> Bool # | |
| Data LexicalFixity | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LexicalFixity # toConstr :: LexicalFixity -> Constr # dataTypeOf :: LexicalFixity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LexicalFixity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LexicalFixity) # gmapT :: (forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r # gmapQ :: (forall d. Data d => d -> u) -> LexicalFixity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # | |
| Outputable LexicalFixity | |
Defined in BasicTypes | |
data TopLevelFlag #
Constructors
| TopLevel | |
| NotTopLevel |
Instances
| Outputable TopLevelFlag | |
Defined in BasicTypes | |
Instances
| Eq Boxity | |
| Data Boxity | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Boxity -> c Boxity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Boxity # toConstr :: Boxity -> Constr # dataTypeOf :: Boxity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Boxity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boxity) # gmapT :: (forall b. Data b => b -> b) -> Boxity -> Boxity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r # gmapQ :: (forall d. Data d => d -> u) -> Boxity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Boxity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # | |
| Outputable Boxity | |
Recursivity Flag
Constructors
| Recursive | |
| NonRecursive |
Instances
| Eq RecFlag | |
| Data RecFlag | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecFlag -> c RecFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecFlag # toConstr :: RecFlag -> Constr # dataTypeOf :: RecFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag) # gmapT :: (forall b. Data b => b -> b) -> RecFlag -> RecFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> RecFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # | |
| Outputable RecFlag | |
Constructors
| FromSource | |
| Generated |
Instances
| Eq Origin | |
| Data Origin | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Origin -> c Origin # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Origin # toConstr :: Origin -> Constr # dataTypeOf :: Origin -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Origin) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin) # gmapT :: (forall b. Data b => b -> b) -> Origin -> Origin # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r # gmapQ :: (forall d. Data d => d -> u) -> Origin -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Origin -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Origin -> m Origin # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Origin -> m Origin # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Origin -> m Origin # | |
| Outputable Origin | |
data OverlapFlag #
The semantics allowed for overlapping instances for a particular
instance. See Note [Safe Haskell isSafeOverlap] (in hs) for a
explanation of the isSafeOverlap field.
AnnKeywordId:AnnOpen'{-# OVERLAPPABLE'or'{-# OVERLAPPING'or'{-# OVERLAPS'or'{-# INCOHERENT',AnnClose`#-}`,
Constructors
| OverlapFlag | |
Fields | |
Instances
| Eq OverlapFlag | |
Defined in BasicTypes | |
| Data OverlapFlag | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapFlag # toConstr :: OverlapFlag -> Constr # dataTypeOf :: OverlapFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapFlag) # gmapT :: (forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> OverlapFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # | |
| Outputable OverlapFlag | |
Defined in BasicTypes | |
data OverlapMode #
Constructors
| NoOverlap SourceText | This instance must not overlap another |
| Overlappable SourceText | Silently ignore this instance if you find a more specific one that matches the constraint you are trying to resolve Example: constraint (Foo [Int]) instance Foo [Int] instance {--} Foo [a] Since the second instance has the Overlappable flag, the first instance will be chosen (otherwise its ambiguous which to choose) |
| Overlapping SourceText | Silently ignore any more general instances that may be used to solve the constraint. Example: constraint (Foo [Int]) instance {--} Foo [Int] instance Foo [a] Since the first instance has the Overlapping flag, the second---more general---instance will be ignored (otherwise it is ambiguous which to choose) |
| Overlaps SourceText | Equivalent to having both |
| Incoherent SourceText | Behave like Overlappable and Overlapping, and in addition pick an an arbitrary one if there are multiple matching candidates, and don't worry about later instantiation Example: constraint (Foo [b])
instance {-# INCOHERENT -} Foo [Int]
instance Foo [a]
Without the Incoherent flag, we'd complain that
instantiating |
Instances
| Eq OverlapMode | |
Defined in BasicTypes | |
| Data OverlapMode | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlapMode -> c OverlapMode # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapMode # toConstr :: OverlapMode -> Constr # dataTypeOf :: OverlapMode -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapMode) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapMode) # gmapT :: (forall b. Data b => b -> b) -> OverlapMode -> OverlapMode # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r # gmapQ :: (forall d. Data d => d -> u) -> OverlapMode -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapMode -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # | |
| Outputable OverlapMode | |
Defined in BasicTypes | |
Constructors
| BoxedTuple | |
| UnboxedTuple | |
| ConstraintTuple |
Instances
| Eq TupleSort | |
| Data TupleSort | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TupleSort -> c TupleSort # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TupleSort # toConstr :: TupleSort -> Constr # dataTypeOf :: TupleSort -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TupleSort) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort) # gmapT :: (forall b. Data b => b -> b) -> TupleSort -> TupleSort # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r # gmapQ :: (forall d. Data d => d -> u) -> TupleSort -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TupleSort -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # | |
| Outputable TupleSort | |
identifier Occurrence Information
Constructors
| ManyOccs | There are many occurrences, or unknown occurrences |
Fields
| |
| IAmDead | Marks unused variables. Sometimes useful for lambda and case-bound variables. |
| OneOcc | Occurs exactly once (per branch), not inside a rule |
Fields
| |
| IAmALoopBreaker | This identifier breaks a loop of mutually recursive functions. The field marks whether it is only a loop breaker due to a reference in a rule |
Fields
| |
type InterestingCxt = Bool #
Interesting Context
data TailCallInfo #
Constructors
| AlwaysTailCalled JoinArity | |
| NoTailCallInfo |
Instances
| Eq TailCallInfo | |
Defined in BasicTypes | |
| Outputable TailCallInfo | |
Defined in BasicTypes | |
data DefMethSpec ty #
Default Method Specification
Instances
| Binary (DefMethSpec IfaceType) | |
| Outputable (DefMethSpec ty) | |
Defined in BasicTypes | |
data SuccessFlag #
Instances
| Outputable SuccessFlag | |
Defined in BasicTypes | |
data SourceText #
Constructors
| SourceText String | |
| NoSourceText | For when code is generated, e.g. TH, deriving. The pretty printer will then make its own representation of the item. |
Instances
| Eq SourceText | |
Defined in BasicTypes | |
| Data SourceText | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceText -> c SourceText # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceText # toConstr :: SourceText -> Constr # dataTypeOf :: SourceText -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceText) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceText) # gmapT :: (forall b. Data b => b -> b) -> SourceText -> SourceText # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceText -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceText -> r # gmapQ :: (forall d. Data d => d -> u) -> SourceText -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceText -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # | |
| Show SourceText | |
Defined in BasicTypes Methods showsPrec :: Int -> SourceText -> ShowS # show :: SourceText -> String # showList :: [SourceText] -> ShowS # | |
| Outputable SourceText | |
Defined in BasicTypes | |
data CompilerPhase #
Constructors
| Phase PhaseNum | |
| InitialPhase |
Instances
| Outputable CompilerPhase | |
Defined in BasicTypes | |
data Activation #
Constructors
| NeverActive | |
| AlwaysActive | |
| ActiveBefore SourceText PhaseNum | |
| ActiveAfter SourceText PhaseNum |
Instances
| Eq Activation | |
Defined in BasicTypes | |
| Data Activation | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Activation -> c Activation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Activation # toConstr :: Activation -> Constr # dataTypeOf :: Activation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Activation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation) # gmapT :: (forall b. Data b => b -> b) -> Activation -> Activation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r # gmapQ :: (forall d. Data d => d -> u) -> Activation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Activation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Activation -> m Activation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation # | |
| Outputable Activation | |
Defined in BasicTypes | |
data RuleMatchInfo #
Rule Match Information
Instances
| Eq RuleMatchInfo | |
Defined in BasicTypes Methods (==) :: RuleMatchInfo -> RuleMatchInfo -> Bool # (/=) :: RuleMatchInfo -> RuleMatchInfo -> Bool # | |
| Data RuleMatchInfo | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleMatchInfo -> c RuleMatchInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RuleMatchInfo # toConstr :: RuleMatchInfo -> Constr # dataTypeOf :: RuleMatchInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RuleMatchInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RuleMatchInfo) # gmapT :: (forall b. Data b => b -> b) -> RuleMatchInfo -> RuleMatchInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleMatchInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleMatchInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo # | |
| Show RuleMatchInfo | |
Defined in BasicTypes Methods showsPrec :: Int -> RuleMatchInfo -> ShowS # show :: RuleMatchInfo -> String # showList :: [RuleMatchInfo] -> ShowS # | |
| Outputable RuleMatchInfo | |
Defined in BasicTypes | |
data InlinePragma #
Constructors
| InlinePragma | |
Fields
| |
Instances
| Eq InlinePragma | |
Defined in BasicTypes | |
| Data InlinePragma | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlinePragma -> c InlinePragma # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlinePragma # toConstr :: InlinePragma -> Constr # dataTypeOf :: InlinePragma -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlinePragma) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlinePragma) # gmapT :: (forall b. Data b => b -> b) -> InlinePragma -> InlinePragma # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma -> r # gmapQ :: (forall d. Data d => d -> u) -> InlinePragma -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InlinePragma -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # | |
| Outputable InlinePragma | |
Defined in BasicTypes | |
data InlineSpec #
Inline Specification
Constructors
| Inline | |
| Inlinable | |
| NoInline | |
| NoUserInline |
Instances
| Eq InlineSpec | |
Defined in BasicTypes | |
| Data InlineSpec | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlineSpec -> c InlineSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlineSpec # toConstr :: InlineSpec -> Constr # dataTypeOf :: InlineSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlineSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec) # gmapT :: (forall b. Data b => b -> b) -> InlineSpec -> InlineSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> InlineSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InlineSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # | |
| Show InlineSpec | |
Defined in BasicTypes Methods showsPrec :: Int -> InlineSpec -> ShowS # show :: InlineSpec -> String # showList :: [InlineSpec] -> ShowS # | |
| Outputable InlineSpec | |
Defined in BasicTypes | |
data IntegralLit #
Integral Literal
Used (instead of Integer) to represent negative zegative zero which is required for NegativeLiterals extension to correctly parse `-0::Double` as negative zero. See also #13211.
Instances
| Eq IntegralLit | |
Defined in BasicTypes | |
| Data IntegralLit | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntegralLit -> c IntegralLit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntegralLit # toConstr :: IntegralLit -> Constr # dataTypeOf :: IntegralLit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IntegralLit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntegralLit) # gmapT :: (forall b. Data b => b -> b) -> IntegralLit -> IntegralLit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntegralLit -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntegralLit -> r # gmapQ :: (forall d. Data d => d -> u) -> IntegralLit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IntegralLit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit # | |
| Ord IntegralLit | |
Defined in BasicTypes Methods compare :: IntegralLit -> IntegralLit -> Ordering # (<) :: IntegralLit -> IntegralLit -> Bool # (<=) :: IntegralLit -> IntegralLit -> Bool # (>) :: IntegralLit -> IntegralLit -> Bool # (>=) :: IntegralLit -> IntegralLit -> Bool # max :: IntegralLit -> IntegralLit -> IntegralLit # min :: IntegralLit -> IntegralLit -> IntegralLit # | |
| Show IntegralLit | |
Defined in BasicTypes Methods showsPrec :: Int -> IntegralLit -> ShowS # show :: IntegralLit -> String # showList :: [IntegralLit] -> ShowS # | |
| Outputable IntegralLit | |
Defined in BasicTypes | |
data FractionalLit #
Fractional Literal
Used (instead of Rational) to represent exactly the floating point literal that we encountered in the user's source program. This allows us to pretty-print exactly what the user wrote, which is important e.g. for floating point numbers that can't represented as Doubles (we used to via Double for pretty-printing). See also #2245.
Instances
data IntWithInf #
An integer or infinity
Instances
| Eq IntWithInf | |
Defined in BasicTypes | |
| Num IntWithInf | |
Defined in BasicTypes Methods (+) :: IntWithInf -> IntWithInf -> IntWithInf # (-) :: IntWithInf -> IntWithInf -> IntWithInf # (*) :: IntWithInf -> IntWithInf -> IntWithInf # negate :: IntWithInf -> IntWithInf # abs :: IntWithInf -> IntWithInf # signum :: IntWithInf -> IntWithInf # fromInteger :: Integer -> IntWithInf # | |
| Ord IntWithInf | |
Defined in BasicTypes Methods compare :: IntWithInf -> IntWithInf -> Ordering # (<) :: IntWithInf -> IntWithInf -> Bool # (<=) :: IntWithInf -> IntWithInf -> Bool # (>) :: IntWithInf -> IntWithInf -> Bool # (>=) :: IntWithInf -> IntWithInf -> Bool # max :: IntWithInf -> IntWithInf -> IntWithInf # min :: IntWithInf -> IntWithInf -> IntWithInf # | |
| Outputable IntWithInf | |
Defined in BasicTypes | |
data SpliceExplicitFlag #
Constructors
| ExplicitSplice | = $(f x y) |
| ImplicitSplice | = f x y, i.e. a naked top level expression |
Instances
| Data SpliceExplicitFlag | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceExplicitFlag -> c SpliceExplicitFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpliceExplicitFlag # toConstr :: SpliceExplicitFlag -> Constr # dataTypeOf :: SpliceExplicitFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SpliceExplicitFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpliceExplicitFlag) # gmapT :: (forall b. Data b => b -> b) -> SpliceExplicitFlag -> SpliceExplicitFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> SpliceExplicitFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceExplicitFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag # | |
data TypeOrKind #
Flag to see whether we're type-checking terms or kind-checking types
Instances
| Eq TypeOrKind | |
Defined in BasicTypes | |
| Outputable TypeOrKind | |
Defined in BasicTypes | |
mkLocMessage :: Severity -> SrcSpan -> MsgDoc -> MsgDoc #
Make an unannotated error message with location info.
Arguments
| :: Maybe String | optional annotation |
| -> Severity | severity |
| -> SrcSpan | location |
| -> MsgDoc | message |
| -> MsgDoc |
Make a possibly annotated error message with location info.
dumpSDoc :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO () #
A wrapper around dumpSDocWithStyle which uses PprDump style.
Constructors
| SevOutput | |
| SevFatal | |
| SevInteractive | |
| SevDump | Log message intended for compiler developers No filelinecolumn stuff |
| SevInfo | Log messages intended for end users. No filelinecolumn stuff. |
| SevWarning | |
| SevError | SevWarning and SevError are used for warnings and errors o The message has a filelinecolumn heading, plus "warning:" or "error:", added by mkLocMessags o Output is intended for end users |
unRealSrcSpan :: RealLocated a -> a #
getRealSrcSpan :: RealLocated a -> RealSrcSpan #
liftL :: (HasSrcSpan a, HasSrcSpan b, Monad m) => (SrcSpanLess a -> m (SrcSpanLess b)) -> a -> m b #
onHasSrcSpan :: (HasSrcSpan a, HasSrcSpan b) => (SrcSpanLess a -> SrcSpanLess b) -> a -> b #
Lifts a function of undecorated entities to one of decorated ones
cL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a #
An abbreviated form of composeSrcSpan,
mainly to replace the hardcoded L
dL :: HasSrcSpan a => a -> Located (SrcSpanLess a) #
An abbreviated form of decomposeSrcSpan, mainly to be used in ViewPatterns
Arguments
| :: SrcSpan | The span that may be enclosed by the other |
| -> SrcSpan | The span it may be enclosed by |
| -> Bool |
Determines whether a span is enclosed by another one
spans :: SrcSpan -> (Int, Int) -> Bool #
Determines whether a span encloses a given line and column index
cmpLocated :: (HasSrcSpan a, Ord (SrcSpanLess a)) => a -> a -> Ordering #
Tests the ordering of the two located things
eqLocated :: (HasSrcSpan a, Eq (SrcSpanLess a)) => a -> a -> Bool #
Tests whether the two located things are equal
addCLoc :: (HasSrcSpan a, HasSrcSpan b, HasSrcSpan c) => a -> b -> SrcSpanLess c -> c #
Combine locations from two Located things and add them to a third thing
combineLocs :: (HasSrcSpan a, HasSrcSpan b) => a -> b -> SrcSpan #
mkGeneralLocated :: HasSrcSpan e => String -> SrcSpanLess e -> e #
noLoc :: HasSrcSpan a => SrcSpanLess a -> a #
getLoc :: HasSrcSpan a => a -> SrcSpan #
unLoc :: HasSrcSpan a => a -> SrcSpanLess a #
mapLoc :: (a -> b) -> GenLocated l a -> GenLocated l b #
pprUserRealSpan :: Bool -> RealSrcSpan -> SDoc #
srcSpanFileName_maybe :: SrcSpan -> Maybe FastString #
Obtains the filename for a SrcSpan if it is "good"
realSrcSpanEnd :: RealSrcSpan -> RealSrcLoc #
srcSpanEnd :: SrcSpan -> SrcLoc #
srcSpanStart :: SrcSpan -> SrcLoc #
srcSpanEndCol :: RealSrcSpan -> Int #
srcSpanStartCol :: RealSrcSpan -> Int #
srcSpanEndLine :: RealSrcSpan -> Int #
srcSpanStartLine :: RealSrcSpan -> Int #
containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool #
Tests whether the first span "contains" the other span, meaning that it covers at least as much source code. True where spans are equal.
isOneLineSpan :: SrcSpan -> Bool #
True if the span is known to straddle only one line.
For "bad" SrcSpan, it returns False
isGoodSrcSpan :: SrcSpan -> Bool #
Test if a SrcSpan is "good", i.e. has precise location information
srcSpanFirstCharacter :: SrcSpan -> SrcSpan #
Convert a SrcSpan into one that represents only its first character
combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan #
Combines two SrcSpan into one that spans at least all the characters
within both spans. Returns UnhelpfulSpan if the files differ.
mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan #
Create a SrcSpan between two points in a file
realSrcLocSpan :: RealSrcLoc -> RealSrcSpan #
srcLocSpan :: SrcLoc -> SrcSpan #
Create a SrcSpan corresponding to a single point
mkGeneralSrcSpan :: FastString -> SrcSpan #
Create a "bad" SrcSpan that has not location information
interactiveSrcSpan :: SrcSpan #
Built-in "bad" SrcSpans for common sources of location uncertainty
Built-in "bad" SrcSpans for common sources of location uncertainty
sortLocated :: HasSrcSpan a => [a] -> [a] #
advanceSrcLoc :: RealSrcLoc -> Char -> RealSrcLoc #
Move the SrcLoc down by one line if the character is a newline,
to the next 8-char tabstop if it is a tab, and across by one
character in any other case
srcLocCol :: RealSrcLoc -> Int #
Raises an error when used on a "bad" SrcLoc
srcLocLine :: RealSrcLoc -> Int #
Raises an error when used on a "bad" SrcLoc
srcLocFile :: RealSrcLoc -> FastString #
Gives the filename of the RealSrcLoc
mkGeneralSrcLoc :: FastString -> SrcLoc #
Creates a "bad" SrcLoc that has no detailed information about its location
Built-in "bad" SrcLoc values for particular locations
Built-in "bad" SrcLoc values for particular locations
mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc #
pattern LL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a #
A Pattern Synonym to Set/Get SrcSpans
data RealSrcLoc #
Real Source Location
Represents a single point within a file
Instances
| Eq RealSrcLoc | |
Defined in SrcLoc | |
| Ord RealSrcLoc | |
Defined in SrcLoc Methods compare :: RealSrcLoc -> RealSrcLoc -> Ordering # (<) :: RealSrcLoc -> RealSrcLoc -> Bool # (<=) :: RealSrcLoc -> RealSrcLoc -> Bool # (>) :: RealSrcLoc -> RealSrcLoc -> Bool # (>=) :: RealSrcLoc -> RealSrcLoc -> Bool # max :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # min :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # | |
| Show RealSrcLoc | |
Defined in SrcLoc Methods showsPrec :: Int -> RealSrcLoc -> ShowS # show :: RealSrcLoc -> String # showList :: [RealSrcLoc] -> ShowS # | |
| Outputable RealSrcLoc | |
Defined in SrcLoc | |
Source Location
Constructors
| RealSrcLoc !RealSrcLoc | |
| UnhelpfulLoc FastString |
data RealSrcSpan #
A RealSrcSpan delimits a portion of a text file. It could be represented
by a pair of (line,column) coordinates, but in fact we optimise
slightly by using more compact representations for single-line and
zero-length spans, both of which are quite common.
The end position is defined to be the column after the end of the span. That is, a span of (1,1)-(1,2) is one character long, and a span of (1,1)-(1,1) is zero characters long.
Real Source Span
Instances
Source Span
A SrcSpan identifies either a specific portion of a text file
or a human-readable description of a location.
Constructors
| RealSrcSpan !RealSrcSpan | |
| UnhelpfulSpan !FastString |
Instances
data GenLocated l e #
We attach SrcSpans to lots of things, so let's have a datatype for it.
Constructors
| L l e |
Instances
| Functor (GenLocated l) | |
Defined in SrcLoc Methods fmap :: (a -> b) -> GenLocated l a -> GenLocated l b # (<$) :: a -> GenLocated l b -> GenLocated l a # | |
| Foldable (GenLocated l) | |
Defined in SrcLoc Methods fold :: Monoid m => GenLocated l m -> m # foldMap :: Monoid m => (a -> m) -> GenLocated l a -> m # foldMap' :: Monoid m => (a -> m) -> GenLocated l a -> m # foldr :: (a -> b -> b) -> b -> GenLocated l a -> b # foldr' :: (a -> b -> b) -> b -> GenLocated l a -> b # foldl :: (b -> a -> b) -> b -> GenLocated l a -> b # foldl' :: (b -> a -> b) -> b -> GenLocated l a -> b # foldr1 :: (a -> a -> a) -> GenLocated l a -> a # foldl1 :: (a -> a -> a) -> GenLocated l a -> a # toList :: GenLocated l a -> [a] # null :: GenLocated l a -> Bool # length :: GenLocated l a -> Int # elem :: Eq a => a -> GenLocated l a -> Bool # maximum :: Ord a => GenLocated l a -> a # minimum :: Ord a => GenLocated l a -> a # sum :: Num a => GenLocated l a -> a # product :: Num a => GenLocated l a -> a # | |
| Traversable (GenLocated l) | |
Defined in SrcLoc Methods traverse :: Applicative f => (a -> f b) -> GenLocated l a -> f (GenLocated l b) # sequenceA :: Applicative f => GenLocated l (f a) -> f (GenLocated l a) # mapM :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b) # sequence :: Monad m => GenLocated l (m a) -> m (GenLocated l a) # | |
| NamedThing e => NamedThing (Located e) | |
| HasSrcSpan (Located a) | |
Defined in SrcLoc Methods composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) # | |
| (Eq l, Eq e) => Eq (GenLocated l e) | |
Defined in SrcLoc Methods (==) :: GenLocated l e -> GenLocated l e -> Bool # (/=) :: GenLocated l e -> GenLocated l e -> Bool # | |
| (Data l, Data e) => Data (GenLocated l e) | |
Defined in SrcLoc Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenLocated l e) # toConstr :: GenLocated l e -> Constr # dataTypeOf :: GenLocated l e -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e)) # dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (GenLocated l e)) # gmapT :: (forall b. Data b => b -> b) -> GenLocated l e -> GenLocated l e # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r # gmapQ :: (forall d. Data d => d -> u) -> GenLocated l e -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # | |
| (Ord l, Ord e) => Ord (GenLocated l e) | |
Defined in SrcLoc Methods compare :: GenLocated l e -> GenLocated l e -> Ordering # (<) :: GenLocated l e -> GenLocated l e -> Bool # (<=) :: GenLocated l e -> GenLocated l e -> Bool # (>) :: GenLocated l e -> GenLocated l e -> Bool # (>=) :: GenLocated l e -> GenLocated l e -> Bool # max :: GenLocated l e -> GenLocated l e -> GenLocated l e # min :: GenLocated l e -> GenLocated l e -> GenLocated l e # | |
| (Outputable l, Outputable e) => Outputable (GenLocated l e) | |
Defined in SrcLoc | |
| type SrcSpanLess (GenLocated l e) | |
Defined in SrcLoc | |
type Located = GenLocated SrcSpan #
type RealLocated = GenLocated RealSrcSpan #
type family SrcSpanLess a #
Determines the type of undecorated syntactic entities
For most syntactic entities E, where source location spans are
introduced by a wrapper construtor of the same syntactic entity,
we have `SrcSpanLess E = E`.
However, some syntactic entities have a different type compared to
a syntactic entity `e :: E` may have the type `Located E` when
decorated by wrapping it with `L sp e` for a source span sp.
Instances
| type SrcSpanLess Name | |
Defined in Name | |
| type SrcSpanLess (GenLocated l e) | |
Defined in SrcLoc | |
class HasSrcSpan a where #
A typeclass to set/get SrcSpans
Methods
composeSrcSpan :: Located (SrcSpanLess a) -> a #
Composes a SrcSpan decoration with an undecorated syntactic
entity to form its decorated variant
decomposeSrcSpan :: a -> Located (SrcSpanLess a) #
Decomposes a decorated syntactic entity into its SrcSpan
decoration and its undecorated variant
Instances
| HasSrcSpan Name | |
Defined in Name Methods composeSrcSpan :: Located (SrcSpanLess Name) -> Name # decomposeSrcSpan :: Name -> Located (SrcSpanLess Name) # | |
| HasSrcSpan (Located a) | |
Defined in SrcLoc Methods composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) # | |
data PrintUnqualified #
When printing code that contains original names, we need to map the
original names back to something the user understands. This is the
purpose of the triple of functions that gets passed around
when rendering SDoc.
unitIdString :: UnitId -> String #
A Module is a pair of a UnitId and a ModuleName.
Module variables (i.e. H) which can be instantiated to a
specific module at some later point in time are represented
with moduleUnitId set to holeUnitId (this allows us to
avoid having to make moduleUnitId a partial operation.)
Constructors
| Module | |
Fields
| |
Instances
data ModuleName #
A ModuleName is essentially a simple string, e.g. Data.List.
Instances
A unit identifier identifies a (possibly partially) instantiated
library. It is primarily used as part of Module, which in turn
is used in Name, which is used to give names to entities when
typechecking.
There are two possible forms for a UnitId. It can be a
DefiniteUnitId, in which case we just have a string that uniquely
identifies some fully compiled, installed library we have on disk.
However, when we are typechecking a library with missing holes,
we may need to instantiate a library on the fly (in which case
we don't have any on-disk representation.) In that case, you
have an IndefiniteUnitId, which explicitly records the
instantiation, so that we can substitute over it.
Constructors
| IndefiniteUnitId !IndefUnitId | |
| DefiniteUnitId !DefUnitId |
Instances
newtype InstalledUnitId #
An installed unit identifier identifies a library which has
been installed to the package database. These strings are
provided to us via the -this-unit-id flag. The library
in question may be definite or indefinite; if it is indefinite,
none of the holes have been filled (we never install partially
instantiated libraries.) Put another way, an installed unit id
is either fully instantiated, or not instantiated at all.
Installed unit identifiers look something like p+af23SAj2dZ219,
or maybe just p if they don't use Backpack.
Constructors
| InstalledUnitId | |
Fields
| |
Instances
newtype ComponentId #
A ComponentId consists of the package name, package version, component
ID, the transitive dependencies of the component, and other information to
uniquely identify the source code and build configuration of a component.
This used to be known as an InstalledPackageId, but a package can contain
multiple components and a ComponentId uniquely identifies a component
within a package. When a package only has one component, the ComponentId
coincides with the InstalledPackageId
Constructors
| ComponentId FastString |
Instances
fsLit :: String -> FastString #
unpackPtrString :: PtrString -> String #
mkPtrString :: String -> PtrString #
mkPtrString# :: Addr# -> PtrString #
Wrap an unboxed address into a PtrString.
hPutFS :: Handle -> FastString -> IO () #
Outputs a FastString with no decoding at all, that is, you
get the actual bytes in the FastString written to the Handle.
getFastStringTable :: IO [[[FastString]]] #
isUnderscoreFS :: FastString -> Bool #
nilFS :: FastString #
uniqueOfFS :: FastString -> Int #
consFS :: Char -> FastString -> FastString #
tailFS :: FastString -> FastString #
headFS :: FastString -> Char #
concatFS :: [FastString] -> FastString #
appendFS :: FastString -> FastString -> FastString #
zEncodeFS :: FastString -> FastZString #
Returns a Z-encoded version of a FastString. This might be the
original, if it was already Z-encoded. The first time this
function is applied to a particular FastString, the results are
memoized.
unpackFS :: FastString -> String #
Unpacks and decodes the FastString
nullFS :: FastString -> Bool #
Returns True if the FastString is empty
lengthFS :: FastString -> Int #
Returns the length of the FastString in characters
mkFastStringByteList :: [Word8] -> FastString #
Creates a FastString from a UTF-8 encoded [Word8]
mkFastString :: String -> FastString #
Creates a UTF-8 encoded FastString from a String
mkFastStringByteString :: ByteString -> FastString #
Create a FastString from an existing ForeignPtr; the difference
between this and mkFastStringBytes is that we don't have to copy
the bytes if the string is new to the table.
mkFastStringForeignPtr :: Ptr Word8 -> ForeignPtr Word8 -> Int -> IO FastString #
Create a FastString from an existing ForeignPtr; the difference
between this and mkFastStringBytes is that we don't have to copy
the bytes if the string is new to the table.
mkFastStringBytes :: Ptr Word8 -> Int -> FastString #
mkFastString# :: Addr# -> FastString #
lengthFZS :: FastZString -> Int #
zString :: FastZString -> String #
hPutFZS :: Handle -> FastZString -> IO () #
unsafeMkByteString :: String -> ByteString #
bytesFS :: FastString -> ByteString #
Gives the UTF-8 encoded bytes corresponding to a FastString
data FastZString #
Instances
| NFData FastZString | |
Defined in FastString Methods rnf :: FastZString -> () # | |
data FastString #
A FastString is a UTF-8 encoded string together with a unique ID. All
FastStrings are stored in a global hashtable to support fast O(1)
comparison.
It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally.
Constructors
| FastString | |
Fields
| |
Instances
A PtrString is a pointer to some array of Latin-1 encoded chars.
isTupleTyCon :: TyCon -> Bool #
Does this TyCon represent a tuple?
NB: when compiling Data.Tuple, the tycons won't reply True to
isTupleTyCon, because they are built as AlgTyCons. However they
get spat into the interface file as tuple tycons, so I don't think
it matters.
isUnboxedTupleTyCon :: TyCon -> Bool #
Is this the TyCon for an unboxed tuple?
isFunTyCon :: TyCon -> Bool #
TyCons represent type constructors. Type constructors are introduced by things such as:
1) Data declarations: data Foo = ... creates the Foo type constructor of
kind *
2) Type synonyms: type Foo = ... creates the Foo type constructor
3) Newtypes: newtype Foo a = MkFoo ... creates the Foo type constructor
of kind * -> *
4) Class declarations: class Foo where creates the Foo type constructor
of kind *
This data type also encodes a number of primitive, built in type constructors such as those for function and tuple types.
Instances
| Eq TyCon | |
| Data TyCon | |
Defined in TyCon Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyCon -> c TyCon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyCon # dataTypeOf :: TyCon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyCon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCon) # gmapT :: (forall b. Data b => b -> b) -> TyCon -> TyCon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyCon -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyCon -> r # gmapQ :: (forall d. Data d => d -> u) -> TyCon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyCon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon # | |
| Ord TyCon Source # | |
| Show TyCon Source # | |
| NFData TyCon Source # | |
Defined in Language.Haskell.Liquid.GHC.Misc | |
| Hashable TyCon Source # | |
Defined in Language.Haskell.Liquid.GHC.Misc | |
| NamedThing TyCon | |
| Uniquable TyCon | |
| Outputable TyCon | |
| Symbolic TyCon Source # | Symbol Instances |
Defined in Language.Haskell.Liquid.GHC.Misc | |
| PPrint TyCon Source # | |
Defined in Language.Haskell.Liquid.Types.PrettyPrint | |
| TyConable TyCon Source # | |
Defined in Language.Haskell.Liquid.Types.Types | |
| ResolveSym TyCon Source # | |
sGhcRtsWithLibdw :: Settings -> Bool #
sGhcDebugged :: Settings -> Bool #
sGhcThreaded :: Settings -> Bool #
sLeadingUnderscore :: Settings -> Bool #
sTablesNextToCode :: Settings -> Bool #
sGhcRTSWays :: Settings -> String #
sGhcWithSMP :: Settings -> Bool #
sGhcWithNativeCodeGen :: Settings -> Bool #
sGhcWithInterpreter :: Settings -> Bool #
sIntegerLibrary :: Settings -> String #
sTargetPlatformString :: Settings -> String #
sExtraGccViaCFlags :: Settings -> [String] #
sOpt_windres :: Settings -> [String] #
sPgm_ranlib :: Settings -> String #
sPgm_libtool :: Settings -> String #
sPgm_windres :: Settings -> String #
sGccSupportsNoPie :: Settings -> Bool #
sLdIsGnuLd :: Settings -> Bool #
sLdSupportsFilelist :: Settings -> Bool #
sLdSupportsBuildId :: Settings -> Bool #
sGhciUsagePath :: Settings -> FilePath #
sGhcUsagePath :: Settings -> FilePath #
sProjectVersion :: Settings -> String #
sProgramName :: Settings -> String #
Constructors
| Settings | |
Fields | |
data PlatformConstants #
Constructors
Instances
| Read PlatformConstants | |
Defined in PlatformConstants Methods readsPrec :: Int -> ReadS PlatformConstants # readList :: ReadS [PlatformConstants] # | |
withSignalHandlers :: (ExceptionMonad m, MonadIO m) => m a -> m a #
Temporarily install standard signal handlers for catching ^C, which just throw an exception in the current thread.
showGhcException :: GhcException -> ShowS #
Append a description of the given exception to this string.
Note that this uses unsafeGlobalDynFlags, which may have some
uninitialized fields if invoked before initGhcMonad has been called.
If the error message to be printed includes a pretty-printer document
which forces one of these fields this call may bottom.
data GhcException #
GHC's own exception type error messages all take the form:
location: error
If the location is on the command line, or in GHC itself, then location="ghc". All of the error types below correspond to a location of "ghc", except for ProgramError (where the string is assumed to contain a location already, so we don't print one).
Constructors
| Signal Int | Some other fatal signal (SIGHUP,SIGTERM) |
| UsageError String | Prints the short usage msg after the error |
| CmdLineError String | A problem with the command line arguments, but don't print usage. |
| Panic String | The |
| PprPanic String SDoc | |
| Sorry String | The user tickled something that's known not to work yet, but we're not counting it as a bug. |
| PprSorry String SDoc | |
| InstallationError String | An installation problem. |
| ProgramError String | An error in the user's code, probably. |
| PprProgramError String SDoc |
Instances
| Show GhcException | |
Defined in Panic Methods showsPrec :: Int -> GhcException -> ShowS # show :: GhcException -> String # showList :: [GhcException] -> ShowS # | |
| Exception GhcException | |
Defined in Panic Methods toException :: GhcException -> SomeException # fromException :: SomeException -> Maybe GhcException # displayException :: GhcException -> String # | |
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
| Eq OccName | |
| Data OccName | |
Defined in OccName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OccName -> c OccName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OccName # toConstr :: OccName -> Constr # dataTypeOf :: OccName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OccName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OccName) # gmapT :: (forall b. Data b => b -> b) -> OccName -> OccName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r # gmapQ :: (forall d. Data d => d -> u) -> OccName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OccName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OccName -> m OccName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName # | |
| Ord OccName | |
| NFData OccName | |
| HasOccName OccName | |
| Binary OccName | |
| Uniquable OccName | |
| Outputable OccName | |
| OutputableBndr OccName | |
Defined in OccName Methods pprBndr :: BindingSite -> OccName -> SDoc # pprPrefixOcc :: OccName -> SDoc # pprInfixOcc :: OccName -> SDoc # bndrIsJoin_maybe :: OccName -> Maybe Int # | |
A unique, unambiguous name for something, containing information about where that thing originated.
Instances
| Eq Name | |
| Data Name | |
Defined in Name Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # dataTypeOf :: Name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) # gmapT :: (forall b. Data b => b -> b) -> Name -> Name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
| Ord Name | Caution: This instance is implemented via See |
| Show Name Source # | |
| NFData Name | |
| NamedThing Name | |
| HasOccName Name | |
| Binary Name | Assumes that the |
| Uniquable Name | |
| HasSrcSpan Name | |
Defined in Name Methods composeSrcSpan :: Located (SrcSpanLess Name) -> Name # decomposeSrcSpan :: Name -> Located (SrcSpanLess Name) # | |
| Outputable Name | |
| OutputableBndr Name | |
Defined in Name Methods pprBndr :: BindingSite -> Name -> SDoc # pprPrefixOcc :: Name -> SDoc # pprInfixOcc :: Name -> SDoc # bndrIsJoin_maybe :: Name -> Maybe Int # | |
| Symbolic Name Source # | |
Defined in Language.Haskell.Liquid.GHC.Misc | |
| Fixpoint Name Source # | |
| PPrint Name Source # | |
Defined in Language.Haskell.Liquid.Types.PrettyPrint | |
| type SrcSpanLess Name | |
Defined in Name | |
When invoking external tools as part of the compilation pipeline, we pass these a sequence of options on the command-line. Rather than just using a list of Strings, we use a type that allows us to distinguish between filepaths and 'other stuff'. The reason for this is that this type gives us a handle on transforming filenames, and filenames only, to whatever format they're expected to be on a particular platform.
Constructors
| FileOption String String | |
| Option String |
useUnicodeSyntax :: DynFlags -> Bool #
An internal helper to check whether to use unicode syntax for output.
Note: You should very likely be using unicodeSyntax instead
of this function.
useStarIsType :: DynFlags -> Bool #
shouldUseColor :: DynFlags -> Bool #
hasPprDebug :: DynFlags -> Bool #
hasNoDebugOutput :: DynFlags -> Bool #
Contains not only a collection of GeneralFlags but also a plethora of
information relating to the compilation of a single file or GHC session
Constructors
| DynFlags | |
Fields
| |
Constructors
Instances
| Enum DumpFlag | |
| Eq DumpFlag | |
| Show DumpFlag | |
data GeneralFlag #
Enumerates the simple on-or-off dynamic flags
Constructors
Instances
| Enum GeneralFlag | |
Defined in DynFlags Methods succ :: GeneralFlag -> GeneralFlag # pred :: GeneralFlag -> GeneralFlag # toEnum :: Int -> GeneralFlag # fromEnum :: GeneralFlag -> Int # enumFrom :: GeneralFlag -> [GeneralFlag] # enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag] # | |
| Eq GeneralFlag | |
Defined in DynFlags | |
| Show GeneralFlag | |
Defined in DynFlags Methods showsPrec :: Int -> GeneralFlag -> ShowS # show :: GeneralFlag -> String # showList :: [GeneralFlag] -> ShowS # | |
gfinally :: ExceptionMonad m => m a -> m b -> m a #
gcatch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m a #
gbracket :: ExceptionMonad m => m a -> (a -> m b) -> (a -> m c) -> m c #
data FileSettings #
Paths to various files and directories used by GHC, including those that provide more settings.
type ForeignHValue = ForeignRef HValue #
data IntegerLibrary #
Constructors
| IntegerGMP | |
| IntegerSimple |
Instances
| Eq IntegerLibrary | |
Defined in GHC.Platform Methods (==) :: IntegerLibrary -> IntegerLibrary -> Bool # (/=) :: IntegerLibrary -> IntegerLibrary -> Bool # | |
| Read IntegerLibrary | |
Defined in GHC.Platform Methods readsPrec :: Int -> ReadS IntegerLibrary # readList :: ReadS [IntegerLibrary] # | |
| Show IntegerLibrary | |
Defined in GHC.Platform Methods showsPrec :: Int -> IntegerLibrary -> ShowS # show :: IntegerLibrary -> String # showList :: [IntegerLibrary] -> ShowS # | |
data PlatformMisc #
Platform-specific settings formerly hard-coded in Config.hs.
These should probably be all be triaged whether they can be computed from
other settings or belong in another another place (like Platform above).
Constructors
| PlatformMisc | |
Fields
| |
data ForeignSrcLang #
Foreign formats supported by GHC via TH
Constructors
| LangC | C |
| LangCxx | C++ |
| LangObjc | Objective C |
| LangObjcxx | Objective C++ |
| LangAsm | Assembly language (.s) |
| RawObject | Object (.o) |
Instances
coreModule :: DesugaredMod m => m -> ModGuts #
tyConRealArity :: TyCon -> Int Source #
- NOTE:tyConRealArity
The semantics of tyConArity changed between GHC 8.6.5 and GHC 8.10, mostly due to the
Visible Dependent Quantification (VDQ). As a result, given the following:
data family EntityField record :: * -> *
Calling tyConArity on this would yield 2 for 8.6.5 but 1 an 8.10, so we try to backport
the old behaviour in 8.10 by "looking" at the Kind of the input TyCon and trying to recursively
split the type apart with either splitFunTy_maybe or splitForAllTy_maybe.
- NOTE:isEvVarType
For GHC < 8.10.1 isPredTy is effectively the same as the new isEvVarType, which covers the cases
for coercion types and "normal" type coercions. The 8.6.5 version of isPredTy had a special case to
handle a TyConApp in the case of type equality (i.e. ~ ) which was removed in the implementation
for 8.10.1, which essentially calls tcIsConstraintKind straight away.
dataConExTyVars :: DataCon -> [TyVar] Source #