| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC
Contents
- Initialisation
- GHC Monad
- Flags and settings
- Logging
- Targets
- Loading/compiling the program
- Inspecting the module structure of the program
- Inspecting modules
- Querying the environment
- Printing
- Interactive evaluation
- Abstract syntax elements
- Exceptions
- Token stream manipulations
- Pure interface to the parser
- API Annotations
- Miscellaneous
Synopsis
- defaultErrorHandler :: ExceptionMonad m => FatalMessager -> FlushOut -> m a -> m a
- defaultCleanupHandler :: ExceptionMonad m => DynFlags -> m a -> m a
- prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a
- withSignalHandlers :: ExceptionMonad m => m a -> m a
- withCleanupSession :: GhcMonad m => m a -> m a
- data Ghc a
- data GhcT m a
- class (Functor m, ExceptionMonad m, HasDynFlags m, HasLogger m) => GhcMonad m where- getSession :: m HscEnv
- setSession :: HscEnv -> m ()
 
- data HscEnv
- runGhc :: Maybe FilePath -> Ghc a -> IO a
- runGhcT :: ExceptionMonad m => Maybe FilePath -> GhcT m a -> m a
- initGhcMonad :: GhcMonad m => Maybe FilePath -> m ()
- printException :: GhcMonad m => SourceError -> m ()
- handleSourceError :: MonadCatch m => (SourceError -> m a) -> m a -> m a
- needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
- data DynFlags = DynFlags {- ghcMode :: GhcMode
- ghcLink :: GhcLink
- backend :: !Backend
- ghcNameVersion :: !GhcNameVersion
- fileSettings :: !FileSettings
- targetPlatform :: Platform
- toolSettings :: !ToolSettings
- platformMisc :: !PlatformMisc
- rawSettings :: [(String, String)]
- 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]
- mainModuleNameIs :: ModuleName
- mainFunIs :: Maybe String
- reductionDepth :: IntWithInf
- solverIterations :: IntWithInf
- homeUnitId_ :: UnitId
- homeUnitInstanceOf_ :: Maybe UnitId
- homeUnitInstantiations_ :: [(ModuleName, Module)]
- targetWays_ :: Ways
- 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
- dynamicTooFailed :: IORef Bool
- dynObjectSuf_ :: String
- dynHiSuf_ :: String
- outputFile_ :: Maybe String
- dynOutputFile_ :: Maybe String
- outputHi :: Maybe String
- dynOutputHi :: Maybe String
- dynLibLoader :: DynLibLoader
- dynamicNow :: !Bool
- 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]
- depMakefile :: FilePath
- depIncludePkgDeps :: Bool
- depIncludeCppDeps :: Bool
- depExcludeMods :: [ModuleName]
- depSuffixes :: [String]
- packageDBFlags :: [PackageDBFlag]
- ignorePackageFlags :: [IgnorePackageFlag]
- packageFlags :: [PackageFlag]
- pluginPackageFlags :: [PackageFlag]
- trustFlags :: [TrustFlag]
- packageEnv :: Maybe 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
- deriveViaOnLoc :: SrcSpan
- overlapInstLoc :: SrcSpan
- incoherentOnLoc :: SrcSpan
- pkgTrustOnLoc :: SrcSpan
- warnSafeOnLoc :: SrcSpan
- warnUnsafeOnLoc :: SrcSpan
- trustworthyOnLoc :: SrcSpan
- extensions :: [OnOff Extension]
- extensionFlags :: EnumSet Extension
- unfoldingOpts :: !UnfoldingOpts
- maxWorkerArgs :: Int
- ghciHistSize :: Int
- 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
- callerCcFilters :: [CallerCcFilter]
- 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 :: Word
- uniqueIncrement :: Int
- cfgWeights :: Weights
 
- data GeneralFlag- = Opt_DumpToFile
- | Opt_D_faststring_stats
- | Opt_D_dump_minimal_imports
- | Opt_DoCoreLinting
- | Opt_DoLinearCoreLinting
- | Opt_DoStgLinting
- | Opt_DoCmmLinting
- | Opt_DoAsmLinting
- | Opt_DoAnnotationLinting
- | Opt_DoBoundsChecking
- | Opt_NoLlvmMangler
- | Opt_FastLlvm
- | Opt_NoTypeableBinds
- | Opt_DistinctConstructorTables
- | Opt_InfoTableMap
- | 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_InlineGenerics
- | Opt_InlineGenericsAggressively
- | 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_CmmStaticPred
- | 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_Ticky
- | Opt_Ticky_Allocd
- | Opt_Ticky_LNE
- | Opt_Ticky_Dyn_Thunk
- | Opt_RPath
- | Opt_RelativeDynlibPaths
- | Opt_CompactUnwind
- | Opt_Hpc
- | Opt_FamAppCache
- | Opt_ExternalInterpreter
- | Opt_OptimalApplicativeDo
- | Opt_VersionMacros
- | Opt_WholeArchiveHsLibs
- | Opt_SingleLibFolder
- | Opt_ExposeInternalSymbols
- | Opt_KeepCAFs
- | Opt_KeepGoing
- | Opt_ByteCode
- | Opt_LinkRts
- | 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
 
- data Severity
- data Backend- = NCG
- | LLVM
- | ViaC
- | Interpreter
- | NoBackend
 
- gopt :: GeneralFlag -> DynFlags -> Bool
- data GhcMode
- data GhcLink
- parseDynamicFlags :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- parseTargetFiles :: DynFlags -> [String] -> (DynFlags, [(String, Maybe Phase)], [String])
- getSessionDynFlags :: GhcMonad m => m DynFlags
- setSessionDynFlags :: GhcMonad m => DynFlags -> m ()
- getProgramDynFlags :: GhcMonad m => m DynFlags
- setProgramDynFlags :: GhcMonad m => DynFlags -> m Bool
- getInteractiveDynFlags :: GhcMonad m => m DynFlags
- setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
- interpretPackageEnv :: Logger -> DynFlags -> IO DynFlags
- data Logger
- getLogger :: HasLogger m => m Logger
- pushLogHook :: (LogAction -> LogAction) -> Logger -> Logger
- popLogHook :: Logger -> Logger
- pushLogHookM :: GhcMonad m => (LogAction -> LogAction) -> m ()
- popLogHookM :: GhcMonad m => m ()
- modifyLogger :: GhcMonad m => (Logger -> Logger) -> m ()
- putMsgM :: GhcMonad m => SDoc -> m ()
- putLogMsgM :: GhcMonad m => WarnReason -> Severity -> SrcSpan -> SDoc -> m ()
- data Target = Target {- targetId :: !TargetId
- targetAllowObjCode :: !Bool
- targetContents :: !(Maybe (InputFileBuffer, UTCTime))
 
- data TargetId- = TargetModule !ModuleName
- | TargetFile !FilePath !(Maybe Phase)
 
- data Phase
- setTargets :: GhcMonad m => [Target] -> m ()
- getTargets :: GhcMonad m => m [Target]
- addTarget :: GhcMonad m => Target -> m ()
- removeTarget :: GhcMonad m => TargetId -> m ()
- guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target
- depanal :: GhcMonad m => [ModuleName] -> Bool -> m ModuleGraph
- depanalE :: GhcMonad m => [ModuleName] -> Bool -> m (ErrorMessages, ModuleGraph)
- load :: GhcMonad m => LoadHowMuch -> m SuccessFlag
- data LoadHowMuch
- data InteractiveImport
- data SuccessFlag
- succeeded :: SuccessFlag -> Bool
- failed :: SuccessFlag -> Bool
- defaultWarnErrLogger :: WarnErrLogger
- type WarnErrLogger = forall m. GhcMonad m => Maybe SourceError -> m ()
- workingDirectoryChanged :: GhcMonad m => m ()
- parseModule :: GhcMonad m => ModSummary -> m ParsedModule
- typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule
- desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule
- loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod
- data ParsedModule = ParsedModule {}
- data TypecheckedModule = TypecheckedModule {}
- data DesugaredModule = DesugaredModule {}
- type TypecheckedSource = LHsBinds GhcTc
- type ParsedSource = Located HsModule
- type RenamedSource = (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString)
- class ParsedMod m => TypecheckedMod m
- class ParsedMod m
- moduleInfo :: TypecheckedMod m => m -> ModuleInfo
- renamedSource :: TypecheckedMod m => m -> Maybe RenamedSource
- typecheckedSource :: TypecheckedMod m => m -> TypecheckedSource
- parsedSource :: ParsedMod m => m -> ParsedSource
- coreModule :: DesugaredMod m => m -> ModGuts
- data CoreModule = CoreModule {- cm_module :: !Module
- cm_types :: !TypeEnv
- cm_binds :: CoreProgram
- cm_safe :: SafeHaskellMode
 
- compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule
- compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule
- data ModuleGraph
- emptyMG :: ModuleGraph
- mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
- mkModuleGraph :: [ExtendedModSummary] -> ModuleGraph
- mgModSummaries :: ModuleGraph -> [ModSummary]
- mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
- 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
 
- ms_mod_name :: ModSummary -> ModuleName
- data ModLocation = ModLocation {}
- getModSummary :: GhcMonad m => ModuleName -> m ModSummary
- getModuleGraph :: GhcMonad m => m ModuleGraph
- isLoaded :: GhcMonad m => ModuleName -> m Bool
- topSortModuleGraph :: Bool -> ModuleGraph -> Maybe ModuleName -> [SCC ModuleGraphNode]
- data ModuleInfo
- getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo)
- modInfoTyThings :: ModuleInfo -> [TyThing]
- modInfoTopLevelScope :: ModuleInfo -> Maybe [Name]
- modInfoExports :: ModuleInfo -> [Name]
- modInfoExportsWithSelectors :: ModuleInfo -> [Name]
- modInfoInstances :: ModuleInfo -> [ClsInst]
- modInfoIsExportedName :: ModuleInfo -> Name -> Bool
- modInfoLookupName :: GhcMonad m => ModuleInfo -> Name -> m (Maybe TyThing)
- modInfoIface :: ModuleInfo -> Maybe ModIface
- modInfoRdrEnv :: ModuleInfo -> Maybe GlobalRdrEnv
- modInfoSafe :: ModuleInfo -> SafeHaskellMode
- lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing)
- findGlobalAnns :: (GhcMonad m, Typeable a) => ([Word8] -> a) -> AnnTarget Name -> m [a]
- mkPrintUnqualifiedForModule :: GhcMonad m => ModuleInfo -> m (Maybe PrintUnqualified)
- type ModIface = ModIface_ 'ModIfaceFinal
- 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_matches :: [IfaceCompleteMatch]
- mi_doc_hdr :: Maybe HsDocString
- mi_decl_docs :: DeclDocMap
- mi_arg_docs :: ArgDocMap
- mi_final_exts :: !(IfaceBackendExts phase)
- mi_ext_fields :: ExtensibleFields
 
- data SafeHaskellMode
- data PrintUnqualified
- alwaysQualify :: PrintUnqualified
- execStmt :: GhcMonad m => String -> ExecOptions -> m ExecResult
- execStmt' :: GhcMonad m => GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult
- data ExecOptions = ExecOptions {}
- execOptions :: ExecOptions
- data ExecResult- = ExecComplete { }
- | ExecBreak { - breakNames :: [Name]
- breakInfo :: Maybe BreakInfo
 
 
- resumeExec :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m ExecResult
- runDecls :: GhcMonad m => String -> m [Name]
- runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name]
- runParsedDecls :: GhcMonad m => [LHsDecl GhcPs] -> m [Name]
- parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs)
- setContext :: GhcMonad m => [InteractiveImport] -> m ()
- getContext :: GhcMonad m => m [InteractiveImport]
- setGHCiMonad :: GhcMonad m => String -> m ()
- getGHCiMonad :: GhcMonad m => m Name
- getBindings :: GhcMonad m => m [TyThing]
- getInsts :: GhcMonad m => m ([ClsInst], [FamInst])
- getPrintUnqual :: GhcMonad m => m PrintUnqualified
- findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module
- lookupModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module
- isModuleTrusted :: GhcMonad m => Module -> m Bool
- moduleTrustReqs :: GhcMonad m => Module -> m (Bool, Set UnitId)
- getNamesInScope :: GhcMonad m => m [Name]
- getRdrNamesInScope :: GhcMonad m => m [RdrName]
- getGRE :: GhcMonad m => m GlobalRdrEnv
- moduleIsInterpreted :: GhcMonad m => Module -> m Bool
- getInfo :: GhcMonad m => Bool -> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
- showModule :: GhcMonad m => ModSummary -> m String
- moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool
- getNameToInstancesIndex :: GhcMonad m => [Module] -> Maybe [Module] -> m (Messages DecoratedSDoc, Maybe (NameEnv ([ClsInst], [FamInst])))
- exprType :: GhcMonad m => TcRnExprMode -> String -> m Type
- data TcRnExprMode
- typeKind :: GhcMonad m => Bool -> String -> m (Type, Kind)
- parseName :: GhcMonad m => String -> m [Name]
- lookupName :: GhcMonad m => Name -> m (Maybe TyThing)
- data HValue
- parseExpr :: GhcMonad m => String -> m (LHsExpr GhcPs)
- compileParsedExpr :: GhcMonad m => LHsExpr GhcPs -> m HValue
- compileExpr :: GhcMonad m => String -> m HValue
- dynCompileExpr :: GhcMonad m => String -> m Dynamic
- type ForeignHValue = ForeignRef HValue
- compileExprRemote :: GhcMonad m => String -> m ForeignHValue
- compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue
- getDocs :: GhcMonad m => Name -> m (Either GetDocsFailure (Maybe HsDocString, IntMap HsDocString))
- data GetDocsFailure
- runTcInteractive :: HscEnv -> TcRn a -> IO (Messages DecoratedSDoc, Maybe a)
- isStmt :: ParserOpts -> String -> Bool
- hasImport :: ParserOpts -> String -> Bool
- isImport :: ParserOpts -> String -> Bool
- isDecl :: ParserOpts -> String -> Bool
- data SingleStep
- 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
- getHistorySpan :: GhcMonad m => History -> m SrcSpan
- getHistoryModule :: History -> Module
- abandon :: GhcMonad m => m Bool
- abandonAll :: GhcMonad m => m Bool
- getResumeContext :: GhcMonad m => m [Resume]
- obtainTermFromId :: GhcMonad m => Int -> Bool -> Id -> m Term
- obtainTermFromVal :: GhcMonad m => Int -> Bool -> Type -> a -> m Term
- reconstructType :: HscEnv -> Int -> Id -> IO (Maybe Type)
- modInfoModBreaks :: ModuleInfo -> ModBreaks
- data ModBreaks = ModBreaks {}
- type BreakIndex = Int
- data BreakInfo = BreakInfo {}
- back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- setupBreakpoint :: GhcMonad m => HscEnv -> BreakInfo -> Int -> m ()
- type Unit = GenUnit UnitId
- type Module = GenModule Unit
- mkModule :: u -> ModuleName -> GenModule u
- pprModule :: Module -> SDoc
- moduleName :: GenModule unit -> ModuleName
- moduleUnit :: GenModule unit -> unit
- data ModuleName
- mkModuleName :: String -> ModuleName
- moduleNameString :: ModuleName -> String
- data Name
- isExternalName :: Name -> Bool
- nameModule :: HasDebugCallStack => Name -> Module
- pprParenSymName :: NamedThing a => a -> SDoc
- nameSrcSpan :: Name -> SrcSpan
- class NamedThing a where- getOccName :: a -> OccName
- getName :: a -> Name
 
- data RdrName
- type Id = Var
- idType :: Id -> Kind
- isImplicitId :: Id -> Bool
- isDeadBinder :: Id -> Bool
- isExportedId :: Var -> Bool
- isLocalId :: Var -> Bool
- isGlobalId :: Var -> Bool
- isRecordSelector :: Id -> Bool
- isPrimOpId :: Id -> Bool
- isFCallId :: Id -> Bool
- isClassOpId_maybe :: Id -> Maybe Class
- isDataConWorkId :: Id -> Bool
- idDataCon :: Id -> DataCon
- isDeadEndId :: Var -> Bool
- isDictonaryId :: Id -> Bool
- recordSelectorTyCon :: Id -> RecSelParent
- data TyCon
- tyConTyVars :: TyCon -> [TyVar]
- tyConDataCons :: TyCon -> [DataCon]
- tyConArity :: TyCon -> Arity
- isClassTyCon :: TyCon -> Bool
- isTypeSynonymTyCon :: TyCon -> Bool
- isTypeFamilyTyCon :: TyCon -> Bool
- isNewTyCon :: TyCon -> Bool
- isPrimTyCon :: TyCon -> Bool
- isFunTyCon :: TyCon -> Bool
- isFamilyTyCon :: TyCon -> Bool
- isOpenFamilyTyCon :: TyCon -> Bool
- isOpenTypeFamilyTyCon :: TyCon -> Bool
- tyConClass_maybe :: TyCon -> Maybe Class
- synTyConRhs_maybe :: TyCon -> Maybe Type
- synTyConDefn_maybe :: TyCon -> Maybe ([TyVar], Type)
- tyConKind :: TyCon -> Kind
- type TyVar = Var
- alphaTyVars :: [TyVar]
- data DataCon
- dataConType :: DataCon -> Type
- dataConTyCon :: DataCon -> TyCon
- dataConFieldLabels :: DataCon -> [FieldLabel]
- dataConIsInfix :: DataCon -> Bool
- isVanillaDataCon :: DataCon -> Bool
- dataConWrapperType :: DataCon -> Type
- dataConSrcBangs :: DataCon -> [HsSrcBang]
- data StrictnessMark
- isMarkedStrict :: StrictnessMark -> Bool
- data Class
- classMethods :: Class -> [Id]
- classSCTheta :: Class -> [PredType]
- classTvsFds :: Class -> ([TyVar], [FunDep TyVar])
- classATs :: Class -> [TyCon]
- pprFundeps :: Outputable a => [FunDep a] -> SDoc
- data ClsInst
- instanceDFunId :: ClsInst -> DFunId
- pprInstance :: ClsInst -> SDoc
- pprInstanceHdr :: ClsInst -> SDoc
- pprFamInst :: FamInst -> SDoc
- data FamInst
- data Type
- splitForAllTyCoVars :: Type -> ([TyCoVar], Type)
- funResultTy :: Type -> Type
- pprParendType :: Type -> SDoc
- pprTypeApp :: TyCon -> [Type] -> SDoc
- type Kind = Type
- type PredType = Type
- type ThetaType = [PredType]
- pprForAll :: [TyCoVarBinder] -> SDoc
- pprThetaArrowTy :: ThetaType -> SDoc
- parseInstanceHead :: GhcMonad m => String -> m Type
- getInstancesForType :: GhcMonad m => Type -> m [ClsInst]
- data TyThing
- module GHC.Hs
- data FixityDirection
- defaultFixity :: Fixity
- maxPrecedence :: Int
- negateFixity :: Fixity
- compareFixity :: Fixity -> Fixity -> (Bool, Bool)
- data LexicalFixity
- data SrcLoc
- data RealSrcLoc
- mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
- noSrcLoc :: SrcLoc
- srcLocFile :: RealSrcLoc -> FastString
- srcLocLine :: RealSrcLoc -> Int
- srcLocCol :: RealSrcLoc -> Int
- data SrcSpan
- data RealSrcSpan
- mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
- srcLocSpan :: SrcLoc -> SrcSpan
- isGoodSrcSpan :: SrcSpan -> Bool
- noSrcSpan :: SrcSpan
- srcSpanStart :: SrcSpan -> SrcLoc
- srcSpanEnd :: SrcSpan -> SrcLoc
- srcSpanFile :: RealSrcSpan -> FastString
- srcSpanStartLine :: RealSrcSpan -> Int
- srcSpanEndLine :: RealSrcSpan -> Int
- srcSpanStartCol :: RealSrcSpan -> Int
- srcSpanEndCol :: RealSrcSpan -> Int
- data GenLocated l e = L l e
- type Located = GenLocated SrcSpan
- type RealLocated = GenLocated RealSrcSpan
- noLoc :: e -> Located e
- mkGeneralLocated :: String -> e -> Located e
- getLoc :: GenLocated l e -> l
- unLoc :: GenLocated l e -> e
- getRealSrcSpan :: RealLocated a -> RealSrcSpan
- unRealSrcSpan :: RealLocated a -> a
- eqLocated :: Eq a => GenLocated l a -> GenLocated l a -> Bool
- cmpLocated :: Ord a => GenLocated l a -> GenLocated l a -> Ordering
- combineLocs :: Located a -> Located b -> SrcSpan
- addCLoc :: Located a -> Located b -> c -> Located c
- leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering
- leftmost_largest :: SrcSpan -> SrcSpan -> Ordering
- rightmost_smallest :: SrcSpan -> SrcSpan -> Ordering
- spans :: SrcSpan -> (Int, Int) -> Bool
- isSubspanOf :: SrcSpan -> SrcSpan -> Bool
- data GhcException
- showGhcException :: SDocContext -> GhcException -> ShowS
- newtype GhcApiError = GhcApiError String
- data Token
- getTokenStream :: GhcMonad m => Module -> m [Located Token]
- getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)]
- showRichTokenStream :: [(Located Token, String)] -> String
- addSourceToTokens :: RealSrcLoc -> StringBuffer -> [Located Token] -> [(Located Token, String)]
- parser :: String -> DynFlags -> FilePath -> (WarningMessages, Either ErrorMessages (Located HsModule))
- data AnnKeywordId- = AnnAnyclass
- | AnnAs
- | AnnAt
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnClass
- | AnnClose
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | AnnClosePH
- | 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
- | AnnLollyU
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenS
- | AnnOpenPH
- | AnnDollar
- | AnnDollarDollar
- | AnnPackageName
- | AnnPattern
- | AnnPercent
- | AnnPercentOne
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRarrowU
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnSignature
- | AnnStatic
- | AnnStock
- | AnnThen
- | AnnThTyQuote
- | AnnTilde
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnVia
- | AnnWhere
- | Annlarrowtail
- | AnnlarrowtailU
- | Annrarrowtail
- | AnnrarrowtailU
- | AnnLarrowtail
- | AnnLarrowtailU
- | AnnRarrowtail
- | AnnRarrowtailU
 
- data EpaComment = EpaComment {}
- cyclicModuleErr :: [ModuleGraphNode] -> SDoc
Initialisation
defaultErrorHandler :: ExceptionMonad m => FatalMessager -> FlushOut -> m a -> m a Source #
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.
defaultCleanupHandler :: ExceptionMonad m => DynFlags -> m a -> m a Source #
Deprecated: Cleanup is now done by runGhc/runGhcT
This function is no longer necessary, cleanup is now done by runGhc/runGhcT.
prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a Source #
withSignalHandlers :: ExceptionMonad m => m a -> m a Source #
Temporarily install standard signal handlers for catching ^C, which just throw an exception in the current thread.
withCleanupSession :: GhcMonad m => m a -> m a Source #
GHC Monad
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.
Instances
| MonadFix Ghc Source # | |
| MonadIO Ghc Source # | |
| Applicative Ghc Source # | |
| Functor Ghc Source # | |
| Monad Ghc Source # | |
| MonadCatch Ghc Source # | |
| MonadMask Ghc Source # | |
| MonadThrow Ghc Source # | |
| GhcMonad Ghc Source # | |
| Defined in GHC.Driver.Monad | |
| HasDynFlags Ghc Source # | |
| Defined in GHC.Driver.Monad Methods | |
| HasLogger Ghc Source # | |
A monad transformer to add GHC specific features to another monad.
Note that the wrapped monad must support IO and handling of exceptions.
Instances
| MonadIO m => MonadIO (GhcT m) Source # | |
| Applicative m => Applicative (GhcT m) Source # | |
| Functor m => Functor (GhcT m) Source # | |
| Monad m => Monad (GhcT m) Source # | |
| MonadCatch m => MonadCatch (GhcT m) Source # | |
| MonadMask m => MonadMask (GhcT m) Source # | |
| Defined in GHC.Driver.Monad | |
| MonadThrow m => MonadThrow (GhcT m) Source # | |
| ExceptionMonad m => GhcMonad (GhcT m) Source # | |
| Defined in GHC.Driver.Monad | |
| MonadIO m => HasDynFlags (GhcT m) Source # | |
| Defined in GHC.Driver.Monad Methods getDynFlags :: GhcT m DynFlags Source # | |
| MonadIO m => HasLogger (GhcT m) Source # | |
class (Functor m, ExceptionMonad m, HasDynFlags m, HasLogger m) => GhcMonad m where Source #
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.
Instances
| GhcMonad Ghc Source # | |
| Defined in GHC.Driver.Monad | |
| ExceptionMonad m => GhcMonad (GhcT m) Source # | |
| Defined in GHC.Driver.Monad | |
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.
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.
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.
initGhcMonad :: GhcMonad m => Maybe FilePath -> m () Source #
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.
printException :: GhcMonad m => SourceError -> m () Source #
Print the error message and all warnings. Useful inside exception handlers. Clears warnings after printing.
Arguments
| :: MonadCatch 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.
needsTemplateHaskellOrQQ :: ModuleGraph -> Bool Source #
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.
Flags and settings
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 
 | |
data GeneralFlag Source #
Enumerates the simple on-or-off dynamic flags
Constructors
Instances
| Enum GeneralFlag Source # | |
| Defined in GHC.Driver.Flags Methods succ :: GeneralFlag -> GeneralFlag Source # pred :: GeneralFlag -> GeneralFlag Source # toEnum :: Int -> GeneralFlag Source # fromEnum :: GeneralFlag -> Int Source # enumFrom :: GeneralFlag -> [GeneralFlag] Source # enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag] Source # enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag] Source # enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag] Source # | |
| Show GeneralFlag Source # | |
| Defined in GHC.Driver.Flags | |
| Eq GeneralFlag Source # | |
| Defined in GHC.Driver.Flags | |
Constructors
| SevOutput | |
| SevFatal | |
| SevInteractive | |
| SevDump | Log message intended for compiler developers No file/line/column stuff | 
| SevInfo | Log messages intended for end users. No file/line/column stuff. | 
| SevWarning | |
| SevError | SevWarning and SevError are used for warnings and errors o The message has a file/line/column heading, plus "warning:" or "error:", added by mkLocMessags o Output is intended for end users | 
Code generation backends.
GHC supports several code generation backends serving different purposes (producing machine code, producing ByteCode for the interpreter) and supporting different platforms.
Constructors
| NCG | Native code generator backend. Compiles Cmm code into textual assembler, then relies on an external assembler toolchain to produce machine code. Only supports a few platforms (X86, PowerPC, SPARC). See GHC.CmmToAsm. | 
| LLVM | LLVM backend. Compiles Cmm code into LLVM textual IR, then relies on LLVM toolchain to produce machine code. It relies on LLVM support for the calling convention used by the NCG backend to produce code objects ABI compatible with it (see "cc 10" or "ghccc" calling convention in https://llvm.org/docs/LangRef.html#calling-conventions). Support a few platforms (X86, AArch64, s390x, ARM). See GHC.CmmToLlvm | 
| ViaC | Via-C backend. Compiles Cmm code into C code, then relies on a C compiler to produce machine code. It produces code objects that are *not* ABI compatible with those produced by NCG and LLVM backends. Produced code is expected to be less efficient than the one produced by NCG and LLVM backends because STG registers are not pinned into real registers. On the other hand, it supports more target platforms (those having a valid C toolchain). See GHC.CmmToC | 
| Interpreter | ByteCode interpreter. Produce ByteCode objects (BCO, see GHC.ByteCode) that can be interpreted. It is used by GHCi. Currently some extensions are not supported (foreign primops). | 
| NoBackend | No code generated. Use this to disable code generation. It is particularly useful when GHC is used as a library for other purpose than generating code (e.g. to generate documentation with Haddock) or when the user requested it (via -fno-code) for some reason. | 
gopt :: GeneralFlag -> DynFlags -> Bool Source #
Test whether a GeneralFlag is set
Note that dynamicNow (i.e., dynamic objects built with `-dynamic-too`)
 always implicitly enables Opt_PIC, Opt_ExternalDynamicRefs, and disables
 Opt_SplitSections.
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 GHC.Unit.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 | 
parseDynamicFlags :: MonadIO m => Logger -> DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn]) Source #
parseTargetFiles :: DynFlags -> [String] -> (DynFlags, [(String, Maybe Phase)], [String]) Source #
Parse command line arguments that look like files.
 First normalises its arguments and then splits them into source files
 and object files.
 A source file can be turned into a Target via guessTarget
getSessionDynFlags :: GhcMonad m => m DynFlags Source #
Grabs the DynFlags from the Session
setSessionDynFlags :: GhcMonad m => DynFlags -> m () Source #
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).
getInteractiveDynFlags :: GhcMonad m => m DynFlags Source #
Get the DynFlags used to evaluate interactive expressions.
setInteractiveDynFlags :: GhcMonad m => DynFlags -> m () Source #
Set the DynFlags used to evaluate interactive expressions.
 Also initialise (load) plugins.
Note: this cannot be used for changes to packages.  Use
 setSessionDynFlags, or setProgramDynFlags and then copy the
 unitState into the interactive DynFlags.
interpretPackageEnv :: Logger -> DynFlags -> IO DynFlags Source #
Find the package environment (if one exists)
We interpret the package environment as a set of package flags; to be specific, if we find a package environment file like
clear-package-db global-package-db package-db blah/package.conf.d package-id id1 package-id id2
we interpret this as
[ -hide-all-packages , -clear-package-db , -global-package-db , -package-db blah/package.conf.d , -package-id id1 , -package-id id2 ]
There's also an older syntax alias for package-id, which is just an unadorned package id
id1 id2
Logging
popLogHook :: Logger -> Logger Source #
Pop a log hook
popLogHookM :: GhcMonad m => m () Source #
Pop a log hook from the stack
putLogMsgM :: GhcMonad m => WarnReason -> Severity -> SrcSpan -> SDoc -> m () Source #
Put a log message
Targets
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 
 | |
Instances
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. | 
setTargets :: GhcMonad m => [Target] -> m () Source #
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.
getTargets :: GhcMonad m => m [Target] Source #
Returns the current set of targets
removeTarget :: GhcMonad m => TargetId -> m () Source #
Remove a target
guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target Source #
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
Loading/compiling the program
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.
 In case of errors, just throw them.
Arguments
| :: GhcMonad m | |
| => [ModuleName] | excluded modules | 
| -> Bool | allow duplicate roots | 
| -> m (ErrorMessages, ModuleGraph) | 
Perform dependency analysis like in depanal.
 In case of errors, the errors and an empty module graph are returned.
load :: GhcMonad m => LoadHowMuch -> m SuccessFlag Source #
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 backend (see backend field) compiling
 and loading may result in files being created on disk.
Calls the defaultWarnErrLogger after each compiling each module, whether
 successful or not.
If errors are encountered during dependency analysis, the module depanalE
 returns together with the errors an empty ModuleGraph.
 After processing this empty ModuleGraph, the errors of depanalE are thrown.
 All other errors are reported using the defaultWarnErrLogger.
data LoadHowMuch Source #
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. | 
data InteractiveImport Source #
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 Source # | |
| Defined in GHC.Runtime.Context Methods ppr :: InteractiveImport -> SDoc Source # | |
data SuccessFlag Source #
Instances
| Outputable SuccessFlag Source # | |
| Defined in GHC.Types.Basic Methods ppr :: SuccessFlag -> SDoc Source # | |
succeeded :: SuccessFlag -> Bool Source #
failed :: SuccessFlag -> Bool Source #
type WarnErrLogger = forall m. GhcMonad m => Maybe SourceError -> m () Source #
A function called to log warnings and errors.
workingDirectoryChanged :: GhcMonad m => m () Source #
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).
parseModule :: GhcMonad m => ModSummary -> m ParsedModule Source #
Parse a module.
Throws a SourceError on parse error.
typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule Source #
Typecheck and rename a parsed module.
Throws a SourceError if either fails.
desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule Source #
Desugar a typechecked module.
loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod Source #
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
 DynFlags's backend, may also include code generation.
This function will always cause recompilation and will always overwrite previous compilation results (potentially files on disk).
data ParsedModule Source #
The result of successful parsing.
Constructors
| ParsedModule | |
| Fields | |
Instances
| ParsedMod ParsedModule Source # | |
| Defined in GHC Methods modSummary :: ParsedModule -> ModSummary | |
data TypecheckedModule Source #
The result of successful typechecking. It also contains the parser result.
Constructors
| TypecheckedModule | |
Instances
| ParsedMod TypecheckedModule Source # | |
| Defined in GHC Methods | |
| TypecheckedMod TypecheckedModule Source # | |
| Defined in GHC | |
data DesugaredModule Source #
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 Source # | |
| Defined in GHC Methods | |
| TypecheckedMod DesugaredModule Source # | |
| Defined in GHC Methods renamedSource :: DesugaredModule -> Maybe RenamedSource Source # typecheckedSource :: DesugaredModule -> TypecheckedSource Source # moduleInfo :: DesugaredModule -> ModuleInfo Source # tm_internals :: DesugaredModule -> (TcGblEnv, ModDetails) | |
type TypecheckedSource = LHsBinds GhcTc Source #
type ParsedSource = Located HsModule Source #
type RenamedSource = (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString) Source #
class ParsedMod m => TypecheckedMod m Source #
Minimal complete definition
renamedSource, typecheckedSource, moduleInfo, tm_internals
Instances
| TypecheckedMod DesugaredModule Source # | |
| Defined in GHC Methods renamedSource :: DesugaredModule -> Maybe RenamedSource Source # typecheckedSource :: DesugaredModule -> TypecheckedSource Source # moduleInfo :: DesugaredModule -> ModuleInfo Source # tm_internals :: DesugaredModule -> (TcGblEnv, ModDetails) | |
| TypecheckedMod TypecheckedModule Source # | |
| Defined in GHC | |
Minimal complete definition
modSummary, parsedSource
Instances
| ParsedMod DesugaredModule Source # | |
| Defined in GHC Methods | |
| ParsedMod ParsedModule Source # | |
| Defined in GHC Methods modSummary :: ParsedModule -> ModSummary | |
| ParsedMod TypecheckedModule Source # | |
| Defined in GHC Methods | |
moduleInfo :: TypecheckedMod m => m -> ModuleInfo Source #
renamedSource :: TypecheckedMod m => m -> Maybe RenamedSource Source #
typecheckedSource :: TypecheckedMod m => m -> TypecheckedSource Source #
parsedSource :: ParsedMod m => m -> ParsedSource Source #
coreModule :: DesugaredMod m => m -> ModGuts Source #
Compiling to Core
data CoreModule Source #
A CoreModule consists of just the fields of a ModGuts that are needed for
 the compileToCoreModule interface.
Constructors
| CoreModule | |
| Fields 
 | |
Instances
compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule Source #
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.
compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule Source #
Like compileToCoreModule, but invokes the simplifier, so as to return simplified and tidied Core.
Inspecting the module structure of the program
data ModuleGraph Source #
A 'ModuleGraph' contains all the nodes from the home package (only). See
 'ModuleGraphNode' for information about the nodes.
Modules need to be compiled. hs-boots need to be typechecked before the associated "real" module so modules with {-# SOURCE #-} imports can be built. Instantiations also need to be typechecked to ensure that the module fits the signature. Substantiation typechecking is roughly comparable to the check that the module and its hs-boot agree.
The graph is not necessarily stored in topologically-sorted order.  Use
 topSortModuleGraph and flattenSCC to achieve this.
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph Source #
Map a function f over all the ModSummaries.
 To preserve invariants f can't change the isBoot status.
mgModSummaries :: ModuleGraph -> [ModSummary] Source #
mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary Source #
Look up a ModSummary in the ModuleGraph
data ModSummary Source #
Data for a module node in a ModuleGraph. Module nodes of the module graph
 are one of:
- A regular Haskell source module
- A hi-boot source module
Constructors
| ModSummary | |
| Fields 
 | |
Instances
| Outputable ModSummary Source # | |
| Defined in GHC.Unit.Module.ModSummary Methods ppr :: ModSummary -> SDoc Source # | |
ms_mod_name :: ModSummary -> ModuleName Source #
data ModLocation Source #
Module Location
Where a module lives on the file system: the actual locations of the .hs, .hi and .o files, if we have them.
For a module in another unit, the ml_hs_file and ml_obj_file components of ModLocation are undefined.
The locations specified by a ModLocation may or may not correspond to actual files yet: for example, even if the object file doesn't exist, the ModLocation still contains the path to where the object file will reside if/when it is created.
Constructors
| ModLocation | |
| Fields 
 | |
Instances
| Show ModLocation Source # | |
| Defined in GHC.Unit.Module.Location | |
| Outputable ModLocation Source # | |
| Defined in GHC.Unit.Module.Location Methods ppr :: ModLocation -> SDoc Source # | |
getModSummary :: GhcMonad m => ModuleName -> m ModSummary Source #
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.
getModuleGraph :: GhcMonad m => m ModuleGraph Source #
Get the module dependency graph.
Arguments
| :: Bool | Drop hi-boot nodes? (see below) | 
| -> ModuleGraph | |
| -> Maybe ModuleName | Root module name.  If  | 
| -> [SCC ModuleGraphNode] | 
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 acyclic
- True: 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
Inspecting modules
data ModuleInfo Source #
Container for information about a Module.
getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo) Source #
Request information about a loaded Module
modInfoTyThings :: ModuleInfo -> [TyThing] Source #
The list of top-level entities defined in a module
modInfoTopLevelScope :: ModuleInfo -> Maybe [Name] Source #
modInfoExports :: ModuleInfo -> [Name] Source #
modInfoExportsWithSelectors :: ModuleInfo -> [Name] Source #
modInfoInstances :: ModuleInfo -> [ClsInst] Source #
Returns the instances defined by the specified module. Warning: currently unimplemented for package modules.
modInfoIsExportedName :: ModuleInfo -> Name -> Bool Source #
modInfoLookupName :: GhcMonad m => ModuleInfo -> Name -> m (Maybe TyThing) Source #
modInfoIface :: ModuleInfo -> Maybe ModIface Source #
modInfoSafe :: ModuleInfo -> SafeHaskellMode Source #
Retrieve module safe haskell mode
lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing) Source #
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.
mkPrintUnqualifiedForModule :: GhcMonad m => ModuleInfo -> m (Maybe PrintUnqualified) Source #
data ModIface_ (phase :: ModIfacePhase) Source #
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 
 | |
Instances
| Binary ModIface Source # | |
| (NFData (IfaceBackendExts phase), NFData (IfaceDeclExts phase)) => NFData (ModIface_ phase) Source # | |
| Defined in GHC.Unit.Module.ModIface | |
data SafeHaskellMode Source #
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
| Show SafeHaskellMode Source # | |
| Defined in GHC.Types.SafeHaskell | |
| Outputable SafeHaskellMode Source # | |
| Defined in GHC.Types.SafeHaskell Methods ppr :: SafeHaskellMode -> SDoc Source # | |
| Eq SafeHaskellMode Source # | |
| Defined in GHC.Types.SafeHaskell Methods (==) :: SafeHaskellMode -> SafeHaskellMode -> Bool # (/=) :: SafeHaskellMode -> SafeHaskellMode -> Bool # | |
Querying the environment
Printing
data PrintUnqualified Source #
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.
Interactive evaluation
Executing statements
Arguments
| :: GhcMonad m | |
| => String | a statement (bind or expression) | 
| -> ExecOptions | |
| -> m ExecResult | 
Run a statement in the current interactive context.
execStmt' :: GhcMonad m => GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult Source #
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).
data ExecOptions Source #
Constructors
| ExecOptions | |
| Fields 
 | |
execOptions :: ExecOptions Source #
default ExecOptions
data ExecResult Source #
Constructors
| ExecComplete | |
| Fields | |
| ExecBreak | |
| Fields 
 | |
resumeExec :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m ExecResult Source #
Adding new declarations
runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name] Source #
Run some declarations and return any user-visible names that were brought into scope.
runParsedDecls :: GhcMonad m => [LHsDecl GhcPs] -> m [Name] Source #
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).
Get/set the current context
parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) Source #
setContext :: GhcMonad m => [InteractiveImport] -> m () Source #
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.)
getContext :: GhcMonad m => m [InteractiveImport] Source #
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.
setGHCiMonad :: GhcMonad m => String -> m () Source #
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.
getGHCiMonad :: GhcMonad m => m Name Source #
Get the monad GHCi lifts user statements into.
Inspecting the current context
getBindings :: GhcMonad m => m [TyThing] Source #
Return the bindings for the current interactive session.
getInsts :: GhcMonad m => m ([ClsInst], [FamInst]) Source #
Return the instances for the current interactive session.
getPrintUnqual :: GhcMonad m => m PrintUnqualified Source #
findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module Source #
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.
lookupModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module Source #
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.
isModuleTrusted :: GhcMonad m => Module -> m Bool Source #
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.
moduleTrustReqs :: GhcMonad m => Module -> m (Bool, Set UnitId) Source #
Return if a module is trusted and the pkgs it depends on to be trusted.
getNamesInScope :: GhcMonad m => m [Name] Source #
Returns all names in scope in the current interactive context
getRdrNamesInScope :: GhcMonad m => m [RdrName] Source #
Returns all RdrNames in scope in the current interactive
 context, excluding any that are internally-generated.
getGRE :: GhcMonad m => m GlobalRdrEnv Source #
get the GlobalRdrEnv for a session
moduleIsInterpreted :: GhcMonad m => Module -> m Bool Source #
Returns True if the specified module is interpreted, and hence has
 its full top-level scope available.
getInfo :: GhcMonad m => Bool -> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)) Source #
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)
showModule :: GhcMonad m => ModSummary -> m String Source #
moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool Source #
getNameToInstancesIndex Source #
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 DecoratedSDoc, 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.
Inspecting types and kinds
exprType :: GhcMonad m => TcRnExprMode -> String -> m Type Source #
Get the type of an expression
 Returns the type as described by TcRnExprMode
data TcRnExprMode Source #
How should we infer a type? See Note [TcRnExprMode]
Constructors
| TM_Inst | Instantiate inferred quantifiers only (:type) | 
| TM_Default | Instantiate all quantifiers, and do eager defaulting (:type +d) | 
Looking up a Name
parseName :: GhcMonad m => String -> m [Name] Source #
Parses a string as an identifier, and returns the list of Names that
 the identifier can refer to in the current interactive context.
Compiling expressions
parseExpr :: GhcMonad m => String -> m (LHsExpr GhcPs) Source #
Parse an expression, the parsed expression can be further processed and passed to compileParsedExpr.
compileExpr :: GhcMonad m => String -> m HValue Source #
Compile an expression, run it, and deliver the resulting HValue.
dynCompileExpr :: GhcMonad m => String -> m Dynamic Source #
Compile an expression, run it and return the result as a Dynamic.
type ForeignHValue = ForeignRef HValue Source #
compileExprRemote :: GhcMonad m => String -> m ForeignHValue Source #
Compile an expression, run it, and deliver the resulting HValue.
compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue Source #
Compile a parsed expression (before renaming), run it, and deliver the resulting HValue.
Docs
getDocs :: GhcMonad m => Name -> m (Either GetDocsFailure (Maybe HsDocString, IntMap HsDocString)) Source #
data GetDocsFailure Source #
Failure modes for getDocs.
Constructors
| NameHasNoModule Name | 
 | 
| NoDocsInIface | This is probably because the module was loaded without  | 
| InteractiveName | The  | 
Instances
| Outputable GetDocsFailure Source # | |
| Defined in GHC.Runtime.Eval Methods ppr :: GetDocsFailure -> SDoc Source # | |
Other
runTcInteractive :: HscEnv -> TcRn a -> IO (Messages DecoratedSDoc, Maybe a) Source #
hasImport :: ParserOpts -> String -> Bool Source #
Returns True if passed string has an import declaration.
isImport :: ParserOpts -> String -> Bool Source #
Returns True if passed string is an import declaration.
isDecl :: ParserOpts -> String -> Bool Source #
Returns True if passed string is a declaration but not a splice.
The debugger
data SingleStep Source #
Constructors
| RunToCompletion | |
| SingleStep | |
| RunAndLogSteps | 
Constructors
| Resume | |
| Fields 
 | |
getHistoryModule :: History -> Module Source #
abandonAll :: GhcMonad m => m Bool Source #
getResumeContext :: GhcMonad m => m [Resume] Source #
All the information about the breakpoints for a module
Constructors
| ModBreaks | |
| Fields 
 | |
type BreakIndex = Int Source #
Breakpoint index
Constructors
| BreakInfo | |
| Fields | |
Abstract syntax elements
Units
Modules
mkModule :: u -> ModuleName -> GenModule u Source #
moduleName :: GenModule unit -> ModuleName Source #
Module name (e.g. A.B.C)
moduleUnit :: GenModule unit -> unit Source #
Unit the module belongs to
data ModuleName Source #
A ModuleName is essentially a simple string, e.g. Data.List.
Instances
mkModuleName :: String -> ModuleName Source #
moduleNameString :: ModuleName -> String Source #
Names
A unique, unambiguous name for something, containing information about where that thing originated.
Instances
| Data Name Source # | |
| Defined in GHC.Types.Name Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name Source # toConstr :: Name -> Constr Source # dataTypeOf :: Name -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) Source # gmapT :: (forall b. Data b => b -> b) -> Name -> Name Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name Source # | |
| NFData Name Source # | |
| Defined in GHC.Types.Name | |
| NamedThing Name Source # | |
| HasOccName Name Source # | |
| Uniquable Name Source # | |
| Binary Name Source # | Assumes that the  | 
| Outputable Name Source # | |
| OutputableBndr Name Source # | |
| Defined in GHC.Types.Name | |
| Eq Name Source # | |
| Ord Name Source # | Caution: This instance is implemented via  See  | 
| type Anno Name Source # | |
| Defined in GHC.Hs.Extension | |
| type Anno (LocatedN Name) Source # | |
| Defined in GHC.Hs.Binds | |
| type Anno [LocatedN Name] Source # | |
| Defined in GHC.Hs.Binds | |
isExternalName :: Name -> Bool Source #
nameModule :: HasDebugCallStack => Name -> Module Source #
pprParenSymName :: NamedThing a => a -> SDoc Source #
print a NamedThing, adding parentheses if the name is an operator.
nameSrcSpan :: Name -> SrcSpan Source #
class NamedThing a where Source #
A class allowing convenient access to the Name of various datatypes
Minimal complete definition
Instances
| NamedThing Class Source # | |
| NamedThing ConLike Source # | |
| NamedThing DataCon Source # | |
| NamedThing FamInst Source # | |
| NamedThing ClsInst Source # | |
| NamedThing PatSyn Source # | |
| NamedThing TyCon Source # | |
| NamedThing IfaceClassOp Source # | |
| Defined in GHC.Iface.Syntax | |
| NamedThing IfaceConDecl Source # | |
| Defined in GHC.Iface.Syntax | |
| NamedThing IfaceDecl Source # | |
| NamedThing HoleFitCandidate Source # | |
| Defined in GHC.Tc.Errors.Hole.FitTypes Methods getOccName :: HoleFitCandidate -> OccName Source # getName :: HoleFitCandidate -> Name Source # | |
| NamedThing Name Source # | |
| NamedThing TyThing Source # | |
| NamedThing Var Source # | |
| NamedThing (CoAxiom br) Source # | |
| NamedThing e => NamedThing (Located e) Source # | |
| NamedThing (Located a) => NamedThing (LocatedAn an a) Source # | |
| NamedThing tv => NamedThing (VarBndr tv flag) Source # | |
| NamedThing (HsTyVarBndr flag GhcRn) Source # | |
| Defined in GHC.Hs.Type Methods getOccName :: HsTyVarBndr flag GhcRn -> OccName Source # | |
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- '`',- AnnVal- AnnTilde,
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  | 
Instances
| Data RdrName Source # | |
| Defined in GHC.Types.Name.Reader Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RdrName -> c RdrName Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RdrName Source # toConstr :: RdrName -> Constr Source # dataTypeOf :: RdrName -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RdrName) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName) Source # gmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RdrName -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RdrName -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName Source # | |
| DisambInfixOp RdrName Source # | |
| Defined in GHC.Parser.PostProcess | |
| HasOccName RdrName Source # | |
| Outputable RdrName Source # | |
| OutputableBndr RdrName Source # | |
| Defined in GHC.Types.Name.Reader | |
| Eq RdrName Source # | |
| Ord RdrName Source # | |
| Defined in GHC.Types.Name.Reader | |
| type Anno RdrName Source # | |
| Defined in GHC.Hs.Extension | |
| type Anno (LocatedN RdrName) Source # | |
| Defined in GHC.Hs.Binds | |
| type Anno [LocatedN RdrName] Source # | |
| Defined in GHC.Hs.Binds | |
Identifiers
isImplicitId :: Id -> Bool Source #
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.
isDeadBinder :: Id -> Bool Source #
isExportedId :: Var -> Bool Source #
isExportedIdVar means "don't throw this away"
isGlobalId :: Var -> Bool Source #
isRecordSelector :: Id -> Bool Source #
isPrimOpId :: Id -> Bool Source #
isDataConWorkId :: Id -> Bool Source #
idDataCon :: Id -> DataCon Source #
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
isDeadEndId :: Var -> Bool Source #
Returns true if an application to n args diverges or throws an exception See Note [Dead ends] in GHC.Types.Demand.
isDictonaryId :: Id -> Bool Source #
recordSelectorTyCon :: Id -> RecSelParent Source #
Type constructors
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
| Data TyCon Source # | |
| Defined in GHC.Core.TyCon Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyCon -> c TyCon Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyCon Source # toConstr :: TyCon -> Constr Source # dataTypeOf :: TyCon -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyCon) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCon) Source # gmapT :: (forall b. Data b => b -> b) -> TyCon -> TyCon Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyCon -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyCon -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TyCon -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyCon -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon Source # | |
| NamedThing TyCon Source # | |
| Uniquable TyCon Source # | |
| Outputable TyCon Source # | |
| Eq TyCon Source # | |
tyConTyVars :: TyCon -> [TyVar] Source #
TyVar binders
tyConDataCons :: TyCon -> [DataCon] Source #
As tyConDataCons_maybe, but returns the empty list of constructors if no
 constructors could be found
tyConArity :: TyCon -> Arity Source #
Arity
isTypeSynonymTyCon :: TyCon -> Bool Source #
Is this a TyCon representing a regular H98 type synonym (type)?
isTypeFamilyTyCon :: TyCon -> Bool Source #
Is this a synonym TyCon that can have may have further instances appear?
isPrimTyCon :: TyCon -> Bool Source #
Does this TyCon represent something that cannot be defined in Haskell?
isFunTyCon :: TyCon -> Bool Source #
isFamilyTyCon :: TyCon -> Bool Source #
Is this a TyCon, synonym or otherwise, that defines a family?
isOpenFamilyTyCon :: TyCon -> Bool Source #
Is this a TyCon, synonym or otherwise, that defines a family with
 instances?
isOpenTypeFamilyTyCon :: TyCon -> Bool Source #
Is this an open type family TyCon?
tyConClass_maybe :: TyCon -> Maybe Class Source #
If this TyCon is that for a class instance, return the class it is for.
 Otherwise returns Nothing
synTyConRhs_maybe :: TyCon -> Maybe Type Source #
Extract the information pertaining to the right hand side of a type synonym
 (type) declaration.
synTyConDefn_maybe :: TyCon -> Maybe ([TyVar], Type) Source #
Extract the TyVars bound by a vanilla type synonym
 and the corresponding (unsubstituted) right hand side.
Type variables
alphaTyVars :: [TyVar] Source #
Data constructors
A data constructor
Instances
| Data DataCon Source # | |
| Defined in GHC.Core.DataCon Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataCon -> c DataCon Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataCon Source # toConstr :: DataCon -> Constr Source # dataTypeOf :: DataCon -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataCon) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataCon) Source # gmapT :: (forall b. Data b => b -> b) -> DataCon -> DataCon Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DataCon -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataCon -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon Source # | |
| NamedThing DataCon Source # | |
| Uniquable DataCon Source # | |
| Outputable DataCon Source # | |
| OutputableBndr DataCon Source # | |
| Defined in GHC.Core.DataCon | |
| Eq DataCon Source # | |
dataConType :: DataCon -> Type Source #
dataConTyCon :: DataCon -> TyCon Source #
The type constructor that we are building via this data constructor
dataConFieldLabels :: DataCon -> [FieldLabel] Source #
The labels for the fields of this particular DataCon
isVanillaDataCon :: DataCon -> Bool Source #
Vanilla DataCons are those that are nice boring Haskell 98 constructors
dataConWrapperType :: DataCon -> Type Source #
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.
dataConSrcBangs :: DataCon -> [HsSrcBang] Source #
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
data StrictnessMark Source #
Constructors
| MarkedStrict | |
| NotMarkedStrict | 
Instances
| Outputable StrictnessMark Source # | |
| Defined in GHC.Core.DataCon Methods ppr :: StrictnessMark -> SDoc Source # | |
isMarkedStrict :: StrictnessMark -> Bool Source #
Classes
Instances
| Data Class Source # | |
| Defined in GHC.Core.Class Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Class -> c Class Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Class Source # toConstr :: Class -> Constr Source # dataTypeOf :: Class -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Class) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Class) Source # gmapT :: (forall b. Data b => b -> b) -> Class -> Class Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Class -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Class -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Class -> m Class Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class Source # | |
| NamedThing Class Source # | |
| Uniquable Class Source # | |
| Outputable Class Source # | |
| Eq Class Source # | |
classMethods :: Class -> [Id] Source #
classSCTheta :: Class -> [PredType] Source #
pprFundeps :: Outputable a => [FunDep a] -> SDoc Source #
Instances
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.
Instances
| Data ClsInst Source # | |
| Defined in GHC.Core.InstEnv Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInst -> c ClsInst Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClsInst Source # toConstr :: ClsInst -> Constr Source # dataTypeOf :: ClsInst -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClsInst) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClsInst) Source # gmapT :: (forall b. Data b => b -> b) -> ClsInst -> ClsInst Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ClsInst -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInst -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst Source # | |
| NamedThing ClsInst Source # | |
| Outputable ClsInst Source # | |
instanceDFunId :: ClsInst -> DFunId Source #
pprInstance :: ClsInst -> SDoc Source #
pprInstanceHdr :: ClsInst -> SDoc Source #
pprFamInst :: FamInst -> SDoc Source #
Pretty-prints a FamInst (type/data family instance) with its defining location.
Instances
Types and Kinds
Instances
| Data Type Source # | |
| Defined in GHC.Core.TyCo.Rep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type Source # toConstr :: Type -> Constr Source # dataTypeOf :: Type -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Type) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) Source # gmapT :: (forall b. Data b => b -> b) -> Type -> Type Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type Source # | |
| Outputable Type Source # | |
| Eq (DeBruijn Type) Source # | |
splitForAllTyCoVars :: Type -> ([TyCoVar], Type) Source #
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.
funResultTy :: Type -> Type Source #
Extract the function result type and panic if that is not possible
pprParendType :: Type -> SDoc Source #
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"
pprForAll :: [TyCoVarBinder] -> SDoc Source #
pprThetaArrowTy :: ThetaType -> SDoc Source #
Entities
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 GHC.Tc.Utils.Env for how to retrieve
 a TyThing given a Name.
Instances
Syntax
module GHC.Hs
Fixities
data FixityDirection Source #
Instances
maxPrecedence :: Int Source #
data LexicalFixity Source #
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
| Data LexicalFixity Source # | |
| Defined in GHC.Types.Fixity Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LexicalFixity Source # toConstr :: LexicalFixity -> Constr Source # dataTypeOf :: LexicalFixity -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LexicalFixity) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LexicalFixity) Source # gmapT :: (forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LexicalFixity -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity Source # | |
| Outputable LexicalFixity Source # | |
| Defined in GHC.Types.Fixity Methods ppr :: LexicalFixity -> SDoc Source # | |
| Eq LexicalFixity Source # | |
| Defined in GHC.Types.Fixity Methods (==) :: LexicalFixity -> LexicalFixity -> Bool # (/=) :: LexicalFixity -> LexicalFixity -> Bool # | |
Source locations
Source Location
Constructors
| RealSrcLoc !RealSrcLoc !(Maybe BufPos) | |
| UnhelpfulLoc FastString | 
data RealSrcLoc Source #
Real Source Location
Represents a single point within a file
Instances
| Show RealSrcLoc Source # | |
| Defined in GHC.Types.SrcLoc | |
| Outputable RealSrcLoc Source # | |
| Defined in GHC.Types.SrcLoc Methods ppr :: RealSrcLoc -> SDoc Source # | |
| Eq RealSrcLoc Source # | |
| Defined in GHC.Types.SrcLoc | |
| Ord RealSrcLoc Source # | |
| Defined in GHC.Types.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 # | |
srcLocFile :: RealSrcLoc -> FastString Source #
Gives the filename of the SrcLoc
srcLocLine :: RealSrcLoc -> Int Source #
Raises an error when used on a "bad" SrcLoc
Source Span
A SrcSpan identifies either a specific portion of a text file
 or a human-readable description of a location.
Constructors
| RealSrcSpan !RealSrcSpan !(Maybe BufSpan) | |
| UnhelpfulSpan !UnhelpfulSpanReason | 
Instances
data RealSrcSpan Source #
A SrcSpan 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
isGoodSrcSpan :: SrcSpan -> Bool Source #
Test if a SrcSpan is "good", i.e. has precise location information
srcSpanStart :: SrcSpan -> SrcLoc Source #
srcSpanEnd :: SrcSpan -> SrcLoc Source #
srcSpanFile :: RealSrcSpan -> FastString Source #
srcSpanStartLine :: RealSrcSpan -> Int Source #
srcSpanEndLine :: RealSrcSpan -> Int Source #
srcSpanStartCol :: RealSrcSpan -> Int Source #
srcSpanEndCol :: RealSrcSpan -> Int Source #
Located
data GenLocated l e Source #
We attach SrcSpans to lots of things, so let's have a datatype for it.
Constructors
| L l e | 
Instances
type Located = GenLocated SrcSpan Source #
type RealLocated = GenLocated RealSrcSpan Source #
Constructing Located
mkGeneralLocated :: String -> e -> Located e Source #
Deconstructing Located
getLoc :: GenLocated l e -> l Source #
unLoc :: GenLocated l e -> e Source #
getRealSrcSpan :: RealLocated a -> RealSrcSpan Source #
unRealSrcSpan :: RealLocated a -> a Source #
Combining and comparing Located values
eqLocated :: Eq a => GenLocated l a -> GenLocated l a -> Bool Source #
Tests whether the two located things are equal
cmpLocated :: Ord a => GenLocated l a -> GenLocated l a -> Ordering Source #
Tests the ordering of the two located things
addCLoc :: Located a -> Located b -> c -> Located c Source #
Combine locations from two Located things and add them to a third thing
spans :: SrcSpan -> (Int, Int) -> Bool Source #
Determines whether a span encloses a given line and column index
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
Exceptions
data GhcException Source #
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
| Exception GhcException Source # | |
| Defined in GHC.Utils.Panic Methods toException :: GhcException -> SomeException Source # fromException :: SomeException -> Maybe GhcException Source # | |
| Show GhcException Source # | |
| Defined in GHC.Utils.Panic | |
showGhcException :: SDocContext -> GhcException -> ShowS Source #
Append a description of the given exception to this string.
newtype GhcApiError Source #
An error thrown if the GHC API is used in an incorrect fashion.
Constructors
| GhcApiError String | 
Instances
| Exception GhcApiError Source # | |
| Defined in GHC Methods toException :: GhcApiError -> SomeException Source # fromException :: SomeException -> Maybe GhcApiError Source # displayException :: GhcApiError -> String Source # | |
| Show GhcApiError Source # | |
Token stream manipulations
getTokenStream :: GhcMonad m => Module -> m [Located Token] Source #
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.
getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)] Source #
Give even more information on the source than getTokenStream
 This function allows reconstructing the source completely with
 showRichTokenStream.
showRichTokenStream :: [(Located Token, String)] -> String Source #
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)] Source #
Given a source location and a StringBuffer corresponding to this location, return a rich token stream with the source associated to the tokens.
Pure interface to the parser
Arguments
| :: String | Haskell module source text (full Unicode is supported) | 
| -> DynFlags | the flags | 
| -> FilePath | the filename (for source locations) | 
| -> (WarningMessages, Either ErrorMessages (Located HsModule)) | 
A pure interface to the module parser.
API Annotations
data AnnKeywordId Source #
Exact print 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 otherwise captured in the AST.
The wiki page describing this feature is https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations https://gitlab.haskell.org/ghc/ghc/-/wikis/implementing-trees-that-grow/in-tree-api-annotations
Note: in general the names of these are taken from the corresponding token, unless otherwise noted See note [exact print annotations] above for details of the usage
Constructors
| AnnAnyclass | |
| AnnAs | |
| AnnAt | |
| AnnBang | 
 | 
| AnnBackquote | '`' | 
| AnnBy | |
| AnnCase | case or lambda case | 
| AnnClass | |
| AnnClose | '#)' or '#-}' etc | 
| AnnCloseB | '|)' | 
| AnnCloseBU | '|)', unicode variant | 
| AnnCloseC | '}' | 
| AnnCloseQ | '|]' | 
| AnnCloseQU | '|]', unicode variant | 
| AnnCloseP | ')' | 
| AnnClosePH | '#)' | 
| AnnCloseS | ']' | 
| AnnColon | |
| AnnComma | as a list separator | 
| AnnCommaTuple | in a RdrName for a tuple | 
| AnnDarrow | '=>' | 
| AnnDarrowU | '=>', unicode variant | 
| AnnData | |
| AnnDcolon | '::' | 
| AnnDcolonU | '::', unicode variant | 
| AnnDefault | |
| AnnDeriving | |
| AnnDo | |
| AnnDot | |
| AnnDotdot | '..' | 
| AnnElse | |
| AnnEqual | |
| AnnExport | |
| AnnFamily | |
| AnnForall | |
| AnnForallU | Unicode variant | 
| AnnForeign | |
| AnnFunId | for function name in matches where there are multiple equations for the function. | 
| AnnGroup | |
| AnnHeader | for CType | 
| AnnHiding | |
| AnnIf | |
| AnnImport | |
| AnnIn | |
| AnnInfix | 'infix' or 'infixl' or 'infixr' | 
| AnnInstance | |
| AnnLam | |
| AnnLarrow | '<-' | 
| AnnLarrowU | '<-', unicode variant | 
| AnnLet | |
| AnnLollyU | The  | 
| AnnMdo | |
| AnnMinus | |
| AnnModule | |
| AnnNewtype | |
| AnnName | where a name loses its location in the AST, this carries it | 
| AnnOf | |
| AnnOpen | '{-# DEPRECATED' etc. Opening of pragmas where
 the capitalisation of the string can be changed by
 the user. The actual text used is stored in a
  | 
| AnnOpenB | '(|' | 
| AnnOpenBU | '(|', unicode variant | 
| AnnOpenC | '{' | 
| AnnOpenE | '[e|' or '[e||' | 
| AnnOpenEQ | '[|' | 
| AnnOpenEQU | '[|', unicode variant | 
| AnnOpenP | '(' | 
| AnnOpenS | '[' | 
| AnnOpenPH | '(#' | 
| AnnDollar | prefix  | 
| AnnDollarDollar | prefix  | 
| AnnPackageName | |
| AnnPattern | |
| AnnPercent | 
 | 
| AnnPercentOne | '%1' -- for HsLinearArrow | 
| AnnProc | |
| AnnQualified | |
| AnnRarrow | 
 | 
| AnnRarrowU | 
 | 
| AnnRec | |
| AnnRole | |
| AnnSafe | |
| AnnSemi | ';' | 
| AnnSimpleQuote | ''' | 
| AnnSignature | |
| AnnStatic | 
 | 
| AnnStock | |
| AnnThen | |
| AnnThTyQuote | double ''' | 
| AnnTilde | 
 | 
| AnnType | |
| AnnUnit | 
 | 
| AnnUsing | |
| AnnVal | e.g. INTEGER | 
| AnnValStr | String value, will need quotes when output | 
| AnnVbar | '|' | 
| AnnVia | 
 | 
| AnnWhere | |
| Annlarrowtail | 
 | 
| AnnlarrowtailU | 
 | 
| Annrarrowtail | 
 | 
| AnnrarrowtailU | 
 | 
| AnnLarrowtail | 
 | 
| AnnLarrowtailU | 
 | 
| AnnRarrowtail | 
 | 
| AnnRarrowtailU | 
 | 
Instances
data EpaComment Source #
Constructors
| EpaComment | |
| Fields 
 | |
Instances
Miscellaneous
cyclicModuleErr :: [ModuleGraphNode] -> SDoc Source #