Safe Haskell | None |
---|---|
Language | Haskell2010 |
- Initialisation
- GHC Monad
- Flags and settings
- 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 :: Type -> Type) a
- class (Functor m, ExceptionMonad m, HasDynFlags m) => GhcMonad (m :: Type -> Type) 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
- hscTarget :: HscTarget
- ghcNameVersion :: !GhcNameVersion
- fileSettings :: !FileSettings
- targetPlatform :: Platform
- toolSettings :: !ToolSettings
- platformMisc :: !PlatformMisc
- platformConstants :: PlatformConstants
- 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]
- mainModIs :: Module
- mainFunIs :: Maybe String
- reductionDepth :: IntWithInf
- solverIterations :: IntWithInf
- homeUnitId :: UnitId
- homeUnitInstanceOfId :: Maybe IndefUnitId
- homeUnitInstantiations :: [(ModuleName, Module)]
- ways :: Set Way
- splitInfo :: Maybe (String, Int)
- objectDir :: Maybe String
- dylibInstallName :: Maybe String
- hiDir :: Maybe String
- hieDir :: Maybe String
- stubDir :: Maybe String
- dumpDir :: Maybe String
- objectSuf :: String
- hcSuf :: String
- hiSuf :: String
- hieSuf :: String
- canGenerateDynamicToo :: IORef Bool
- dynObjectSuf :: String
- dynHiSuf :: String
- outputFile :: Maybe String
- dynOutputFile :: Maybe String
- outputHi :: Maybe String
- dynLibLoader :: DynLibLoader
- dumpPrefix :: Maybe FilePath
- dumpPrefixForce :: Maybe FilePath
- ldInputs :: [Option]
- includePaths :: IncludeSpecs
- libraryPaths :: [String]
- frameworkPaths :: [String]
- cmdlineFrameworks :: [String]
- rtsOpts :: Maybe String
- rtsOptsEnabled :: RtsOptsEnabled
- rtsOptsSuggestions :: Bool
- hpcDir :: String
- pluginModNames :: [ModuleName]
- pluginModNameOpts :: [(ModuleName, String)]
- frontendPluginOpts :: [String]
- cachedPlugins :: [LoadedPlugin]
- staticPlugins :: [StaticPlugin]
- hooks :: Hooks
- depMakefile :: FilePath
- depIncludePkgDeps :: Bool
- depIncludeCppDeps :: Bool
- depExcludeMods :: [ModuleName]
- depSuffixes :: [String]
- packageDBFlags :: [PackageDBFlag]
- ignorePackageFlags :: [IgnorePackageFlag]
- packageFlags :: [PackageFlag]
- pluginPackageFlags :: [PackageFlag]
- trustFlags :: [TrustFlag]
- packageEnv :: Maybe FilePath
- unitDatabases :: Maybe [UnitDatabase UnitId]
- unitState :: UnitState
- filesToClean :: IORef FilesToClean
- dirsToClean :: IORef (Map FilePath FilePath)
- nextTempSuffix :: IORef Int
- generatedDumps :: IORef (Set FilePath)
- dumpFlags :: EnumSet DumpFlag
- generalFlags :: EnumSet GeneralFlag
- warningFlags :: EnumSet WarningFlag
- fatalWarningFlags :: EnumSet WarningFlag
- language :: Maybe Language
- safeHaskell :: SafeHaskellMode
- safeInfer :: Bool
- safeInferred :: Bool
- thOnLoc :: SrcSpan
- newDerivOnLoc :: SrcSpan
- overlapInstLoc :: SrcSpan
- incoherentOnLoc :: SrcSpan
- pkgTrustOnLoc :: SrcSpan
- warnSafeOnLoc :: SrcSpan
- warnUnsafeOnLoc :: SrcSpan
- trustworthyOnLoc :: SrcSpan
- extensions :: [OnOff Extension]
- extensionFlags :: EnumSet Extension
- ufCreationThreshold :: Int
- ufUseThreshold :: Int
- ufFunAppDiscount :: Int
- ufDictDiscount :: Int
- ufDearOp :: Int
- ufVeryAggressive :: Bool
- maxWorkerArgs :: Int
- ghciHistSize :: Int
- log_action :: LogAction
- dump_action :: DumpAction
- trace_action :: TraceAction
- flushOut :: FlushOut
- flushErr :: FlushErr
- ghcVersionFile :: Maybe FilePath
- haddockOptions :: Maybe String
- ghciScripts :: [String]
- pprUserLength :: Int
- pprCols :: Int
- useUnicode :: Bool
- useColor :: OverridingBool
- canUseColor :: Bool
- colScheme :: Scheme
- profAuto :: ProfAuto
- interactivePrint :: Maybe String
- nextWrapperNum :: IORef (ModuleEnv Int)
- sseVersion :: Maybe SseVersion
- bmiVersion :: Maybe BmiVersion
- avx :: Bool
- avx2 :: Bool
- avx512cd :: Bool
- avx512er :: Bool
- avx512f :: Bool
- avx512pf :: Bool
- rtldInfo :: IORef (Maybe LinkerInfo)
- rtccInfo :: IORef (Maybe CompilerInfo)
- maxInlineAllocSize :: Int
- maxInlineMemcpyInsns :: Int
- maxInlineMemsetInsns :: Int
- reverseErrors :: Bool
- maxErrors :: Maybe Int
- initialUnique :: Int
- uniqueIncrement :: Int
- cfgWeightInfo :: CfgWeights
- data 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_NoLlvmMangler
- | Opt_FastLlvm
- | Opt_NoTypeableBinds
- | Opt_WarnIsError
- | Opt_ShowWarnGroups
- | Opt_HideSourcePaths
- | Opt_PrintExplicitForalls
- | Opt_PrintExplicitKinds
- | Opt_PrintExplicitCoercions
- | Opt_PrintExplicitRuntimeReps
- | Opt_PrintEqualityRelations
- | Opt_PrintAxiomIncomps
- | Opt_PrintUnicodeSyntax
- | Opt_PrintExpandedSynonyms
- | Opt_PrintPotentialInstances
- | Opt_PrintTypecheckerElaboration
- | Opt_CallArity
- | Opt_Exitification
- | Opt_Strictness
- | Opt_LateDmdAnal
- | Opt_KillAbsence
- | Opt_KillOneShot
- | Opt_FullLaziness
- | Opt_FloatIn
- | Opt_LateSpecialise
- | Opt_Specialise
- | Opt_SpecialiseAggressively
- | Opt_CrossModuleSpecialise
- | Opt_StaticArgumentTransformation
- | Opt_CSE
- | Opt_StgCSE
- | Opt_StgLiftLams
- | Opt_LiberateCase
- | Opt_SpecConstr
- | Opt_SpecConstrKeen
- | Opt_DoLambdaEtaExpansion
- | Opt_IgnoreAsserts
- | Opt_DoEtaReduction
- | Opt_CaseMerge
- | Opt_CaseFolding
- | Opt_UnboxStrictFields
- | Opt_UnboxSmallStrictFields
- | Opt_DictsCheap
- | Opt_EnableRewriteRules
- | Opt_EnableThSpliceWarnings
- | Opt_RegsGraph
- | Opt_RegsIterative
- | Opt_PedanticBottoms
- | Opt_LlvmTBAA
- | Opt_LlvmFillUndefWithGarbage
- | Opt_IrrefutableTuples
- | Opt_CmmSink
- | Opt_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_Hpc
- | Opt_FlatCache
- | Opt_ExternalInterpreter
- | Opt_OptimalApplicativeDo
- | Opt_VersionMacros
- | Opt_WholeArchiveHsLibs
- | Opt_SingleLibFolder
- | Opt_KeepCAFs
- | Opt_KeepGoing
- | Opt_ByteCodeIfUnboxed
- | 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 HscTarget
- gopt :: GeneralFlag -> DynFlags -> Bool
- data GhcMode
- data GhcLink
- defaultObjectTarget :: DynFlags -> HscTarget
- parseDynamicFlags :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- getSessionDynFlags :: GhcMonad m => m DynFlags
- setSessionDynFlags :: GhcMonad m => DynFlags -> m ()
- getProgramDynFlags :: GhcMonad m => m DynFlags
- setProgramDynFlags :: GhcMonad m => DynFlags -> m Bool
- setLogAction :: GhcMonad m => LogAction -> m ()
- getInteractiveDynFlags :: GhcMonad m => m DynFlags
- setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
- interpretPackageEnv :: DynFlags -> IO DynFlags
- data Target = Target {
- targetId :: TargetId
- targetAllowObjCode :: Bool
- targetContents :: Maybe (InputFileBuffer, UTCTime)
- data TargetId
- 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
- = IIDecl (ImportDecl GhcPs)
- | IIModule ModuleName
- data SuccessFlag
- succeeded :: SuccessFlag -> Bool
- failed :: SuccessFlag -> Bool
- defaultWarnErrLogger :: WarnErrLogger
- type WarnErrLogger = forall (m :: Type -> Type). 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 {
- tm_parsed_module :: ParsedModule
- tm_renamed_source :: Maybe RenamedSource
- tm_typechecked_source :: TypecheckedSource
- tm_checked_module_info :: ModuleInfo
- tm_internals_ :: (TcGblEnv, ModDetails)
- data DesugaredModule = DesugaredModule {
- dm_typechecked_module :: TypecheckedModule
- dm_core_module :: ModGuts
- 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 {}
- compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule
- compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule
- data ModuleGraph
- emptyMG :: ModuleGraph
- mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
- mkModuleGraph :: [ModSummary] -> 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 ModSummary]
- 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_sigs :: [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 -> 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, 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, Map Int HsDocString))
- data GetDocsFailure
- runTcInteractive :: HscEnv -> TcRn a -> IO (Messages, Maybe a)
- isStmt :: ParserFlags -> String -> Bool
- hasImport :: ParserFlags -> String -> Bool
- isImport :: ParserFlags -> String -> Bool
- isDecl :: ParserFlags -> 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 {
- modBreaks_flags :: ForeignRef BreakArray
- modBreaks_locs :: !(Array BreakIndex SrcSpan)
- modBreaks_vars :: !(Array BreakIndex [OccName])
- modBreaks_decls :: !(Array BreakIndex [String])
- modBreaks_ccs :: !(Array BreakIndex (RemotePtr CostCentre))
- modBreaks_breakInfo :: IntMap CgBreakInfo
- type BreakIndex = Int
- data BreakInfo
- back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- 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
- splitForAllTys :: 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
- data FixityDirection
- defaultFixity :: Fixity
- maxPrecedence :: Int
- negateFixity :: Fixity
- compareFixity :: Fixity -> Fixity -> (Bool, Bool)
- data LexicalFixity
- data SrcLoc
- = RealSrcLoc !RealSrcLoc !(Maybe BufPos)
- | UnhelpfulLoc FastString
- data RealSrcLoc
- mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
- noSrcLoc :: SrcLoc
- srcLocFile :: RealSrcLoc -> FastString
- srcLocLine :: RealSrcLoc -> Int
- srcLocCol :: RealSrcLoc -> Int
- data SrcSpan
- = RealSrcSpan !RealSrcSpan !(Maybe BufSpan)
- | UnhelpfulSpan !UnhelpfulSpanReason
- 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
- = Signal Int
- | UsageError String
- | CmdLineError String
- | Panic String
- | PprPanic String SDoc
- | Sorry String
- | PprSorry String SDoc
- | InstallationError String
- | ProgramError String
- | PprProgramError String SDoc
- showGhcException :: GhcException -> ShowS
- 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 ApiAnns = ApiAnns {}
- data AnnKeywordId
- = AnnAnyclass
- | AnnAs
- | AnnAt
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnClass
- | AnnClose
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | AnnCloseS
- | AnnColon
- | AnnComma
- | AnnCommaTuple
- | AnnDarrow
- | AnnDarrowU
- | AnnData
- | AnnDcolon
- | AnnDcolonU
- | AnnDefault
- | AnnDeriving
- | AnnDo
- | AnnDot
- | AnnDotdot
- | AnnElse
- | AnnEqual
- | AnnExport
- | AnnFamily
- | AnnForall
- | AnnForallU
- | AnnForeign
- | AnnFunId
- | AnnGroup
- | AnnHeader
- | AnnHiding
- | AnnIf
- | AnnImport
- | AnnIn
- | AnnInfix
- | AnnInstance
- | AnnLam
- | AnnLarrow
- | AnnLarrowU
- | AnnLet
- | AnnLollyU
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnPercentOne
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenS
- | AnnDollar
- | AnnDollarDollar
- | AnnPackageName
- | AnnPattern
- | AnnPercent
- | 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 AnnotationComment
- type ApiAnnKey = (RealSrcSpan, AnnKeywordId)
- getAnnotation :: ApiAnns -> RealSrcSpan -> AnnKeywordId -> [RealSrcSpan]
- getAndRemoveAnnotation :: ApiAnns -> RealSrcSpan -> AnnKeywordId -> ([RealSrcSpan], ApiAnns)
- getAnnotationComments :: ApiAnns -> RealSrcSpan -> [RealLocated AnnotationComment]
- getAndRemoveAnnotationComments :: ApiAnns -> RealSrcSpan -> ([RealLocated AnnotationComment], ApiAnns)
- unicodeAnn :: AnnKeywordId -> AnnKeywordId
- cyclicModuleErr :: [ModSummary] -> 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 #
withSignalHandlers :: ExceptionMonad m => m a -> m a #
withCleanupSession :: GhcMonad m => m a -> m a Source #
GHC Monad
Instances
Monad Ghc | |
Functor Ghc | |
MonadFix Ghc | |
Defined in GHC.Driver.Monad | |
Applicative Ghc | |
MonadIO Ghc | |
Defined in GHC.Driver.Monad | |
MonadThrow Ghc | |
Defined in GHC.Driver.Monad | |
MonadCatch Ghc | |
MonadMask Ghc | |
HasDynFlags Ghc | |
Defined in GHC.Driver.Monad getDynFlags :: Ghc DynFlags # | |
GhcMonad Ghc | |
Defined in GHC.Driver.Monad getSession :: Ghc HscEnv # setSession :: HscEnv -> Ghc () # |
data GhcT (m :: Type -> Type) a #
Instances
Monad m => Monad (GhcT m) | |
Functor m => Functor (GhcT m) | |
Applicative m => Applicative (GhcT m) | |
MonadIO m => MonadIO (GhcT m) | |
Defined in GHC.Driver.Monad | |
MonadThrow m => MonadThrow (GhcT m) | |
Defined in GHC.Driver.Monad | |
MonadCatch m => MonadCatch (GhcT m) | |
MonadMask m => MonadMask (GhcT m) | |
MonadIO m => HasDynFlags (GhcT m) | |
Defined in GHC.Driver.Monad getDynFlags :: GhcT m DynFlags # | |
ExceptionMonad m => GhcMonad (GhcT m) | |
Defined in GHC.Driver.Monad getSession :: GhcT m HscEnv # setSession :: HscEnv -> GhcT m () # |
class (Functor m, ExceptionMonad m, HasDynFlags m) => GhcMonad (m :: Type -> Type) where #
getSession :: m HscEnv #
setSession :: HscEnv -> m () #
Instances
GhcMonad Ghc | |
Defined in GHC.Driver.Monad getSession :: Ghc HscEnv # setSession :: HscEnv -> Ghc () # | |
ExceptionMonad m => GhcMonad (GhcT m) | |
Defined in GHC.Driver.Monad getSession :: GhcT m HscEnv # setSession :: HscEnv -> GhcT m () # |
:: 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.
:: 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 () #
handleSourceError :: MonadCatch m => (SourceError -> m a) -> m a -> m a #
Flags and settings
data GeneralFlag #
Instances
Enum GeneralFlag | |
Defined in GHC.Driver.Flags succ :: GeneralFlag -> GeneralFlag # pred :: GeneralFlag -> GeneralFlag # toEnum :: Int -> GeneralFlag # fromEnum :: GeneralFlag -> Int # enumFrom :: GeneralFlag -> [GeneralFlag] # enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag] # | |
Eq GeneralFlag | |
Defined in GHC.Driver.Flags (==) :: GeneralFlag -> GeneralFlag -> Bool # (/=) :: GeneralFlag -> GeneralFlag -> Bool # | |
Show GeneralFlag | |
Defined in GHC.Driver.Flags showsPrec :: Int -> GeneralFlag -> ShowS # show :: GeneralFlag -> String # showList :: [GeneralFlag] -> ShowS # |
gopt :: GeneralFlag -> DynFlags -> Bool #
parseDynamicFlags :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn]) Source #
getSessionDynFlags :: GhcMonad m => m DynFlags #
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).
Returns a list of new packages that may need to be linked in using
the dynamic linker (see linkPackages
) as a result of new package
flags. If you are not doing linking or doing static linking, you
can ignore the list of packages returned.
setLogAction :: GhcMonad m => LogAction -> m () Source #
Set the action taken when the compiler produces a message. This
can also be accomplished using setProgramDynFlags
, but using
setLogAction
avoids invalidating the cached module graph.
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.
Note: this cannot be used for changes to packages. Use
setSessionDynFlags
, or setProgramDynFlags
and then copy the
unitState
into the interactive DynFlags
.
interpretPackageEnv :: 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
Targets
Target | |
|
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
:: 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.
:: 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 target (see hscTarget
) compiling
and loading may result in files being created on disk.
Calls the defaultWarnErrLogger
after each compiling each module, whether
successful or not.
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.
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 #
IIDecl (ImportDecl GhcPs) | |
IIModule ModuleName |
Instances
Outputable InteractiveImport | |
Defined in GHC.Driver.Types ppr :: InteractiveImport -> SDoc pprPrec :: Rational -> InteractiveImport -> SDoc |
data SuccessFlag #
Instances
Outputable SuccessFlag | |
Defined in GHC.Types.Basic ppr :: SuccessFlag -> SDoc pprPrec :: Rational -> SuccessFlag -> SDoc |
succeeded :: SuccessFlag -> Bool #
failed :: SuccessFlag -> Bool #
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 hscTarget
, 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.
Instances
ParsedMod ParsedModule Source # | |
Defined in GHC |
data TypecheckedModule Source #
The result of successful typechecking. It also contains the parser result.
TypecheckedModule | |
|
Instances
TypecheckedMod TypecheckedModule Source # | |
Defined in GHC renamedSource :: TypecheckedModule -> Maybe RenamedSource Source # typecheckedSource :: TypecheckedModule -> TypecheckedSource Source # moduleInfo :: TypecheckedModule -> ModuleInfo Source # tm_internals :: TypecheckedModule -> (TcGblEnv, ModDetails) | |
ParsedMod 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.
DesugaredModule | |
|
Instances
TypecheckedMod DesugaredModule Source # | |
Defined in GHC renamedSource :: DesugaredModule -> Maybe RenamedSource Source # typecheckedSource :: DesugaredModule -> TypecheckedSource Source # moduleInfo :: DesugaredModule -> ModuleInfo Source # tm_internals :: DesugaredModule -> (TcGblEnv, ModDetails) | |
ParsedMod DesugaredModule Source # | |
Defined in GHC |
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 #
renamedSource, typecheckedSource, moduleInfo, tm_internals
Instances
TypecheckedMod DesugaredModule Source # | |
Defined in GHC renamedSource :: DesugaredModule -> Maybe RenamedSource Source # typecheckedSource :: DesugaredModule -> TypecheckedSource Source # moduleInfo :: DesugaredModule -> ModuleInfo Source # tm_internals :: DesugaredModule -> (TcGblEnv, ModDetails) | |
TypecheckedMod TypecheckedModule Source # | |
Defined in GHC renamedSource :: TypecheckedModule -> Maybe RenamedSource Source # typecheckedSource :: TypecheckedModule -> TypecheckedSource Source # moduleInfo :: TypecheckedModule -> ModuleInfo Source # tm_internals :: TypecheckedModule -> (TcGblEnv, ModDetails) |
modSummary, parsedSource
Instances
ParsedMod DesugaredModule Source # | |
Defined in GHC | |
ParsedMod TypecheckedModule Source # | |
Defined in GHC | |
ParsedMod ParsedModule Source # | |
Defined in GHC |
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.
Instances
Outputable CoreModule Source # | |
Defined in GHC ppr :: CoreModule -> SDoc pprPrec :: Rational -> CoreModule -> SDoc |
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 #
emptyMG :: ModuleGraph #
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph #
mkModuleGraph :: [ModSummary] -> ModuleGraph #
mgModSummaries :: ModuleGraph -> [ModSummary] #
mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary #
data ModSummary #
ModSummary | |
|
Instances
Outputable ModSummary | |
Defined in GHC.Driver.Types ppr :: ModSummary -> SDoc pprPrec :: Rational -> ModSummary -> SDoc |
ms_mod_name :: ModSummary -> ModuleName #
data ModLocation #
ModLocation | |
|
Instances
Show ModLocation | |
Defined in GHC.Unit.Module.Location showsPrec :: Int -> ModLocation -> ShowS # show :: ModLocation -> String # showList :: [ModLocation] -> ShowS # | |
Outputable ModLocation | |
Defined in GHC.Unit.Module.Location ppr :: ModLocation -> SDoc pprPrec :: Rational -> ModLocation -> SDoc |
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.
:: Bool | Drop hi-boot nodes? (see below) |
-> ModuleGraph | |
-> Maybe ModuleName | Root module name. If |
-> [SCC ModSummary] |
Topological sort of the module graph
Calculate SCCs of the module graph, possibly dropping the hi-boot nodes The resulting list of strongly-connected-components is in topologically sorted order, starting with the module(s) at the bottom of the dependency graph (ie compile them first) and ending with the ones at the top.
Drop hi-boot nodes (first boolean arg)?
False
: treat the hi-boot summaries as nodes of the graph, so the graph must be acyclicTrue
: eliminate the hi-boot nodes, and instead pretend the a source-import of Foo is an import of Foo The resulting graph has no hi-boot nodes, but can be cyclic
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 #
modInfoRdrEnv :: ModuleInfo -> Maybe GlobalRdrEnv 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) #
ModIface | |
|
data SafeHaskellMode #
Instances
Eq SafeHaskellMode | |
Defined in GHC.Driver.Session (==) :: SafeHaskellMode -> SafeHaskellMode -> Bool # (/=) :: SafeHaskellMode -> SafeHaskellMode -> Bool # | |
Show SafeHaskellMode | |
Defined in GHC.Driver.Session showsPrec :: Int -> SafeHaskellMode -> ShowS # show :: SafeHaskellMode -> String # showList :: [SafeHaskellMode] -> ShowS # | |
Outputable SafeHaskellMode | |
Defined in GHC.Driver.Session ppr :: SafeHaskellMode -> SDoc pprPrec :: Rational -> SafeHaskellMode -> SDoc |
Querying the environment
Printing
data PrintUnqualified #
Interactive evaluation
Executing statements
:: 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 #
execOptions :: ExecOptions Source #
default ExecOptions
data ExecResult #
resumeExec :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> 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 RdrName
s in scope in the current interactive
context, excluding any that are internally-generated.
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 #
:: GhcMonad m | |
=> [Module] | visible modules. An orphan instance will be returned if it is visible from at least one module in the list. |
-> Maybe [Module] | modules to load. If this is not specified, we load modules for everything that is in scope unqualified. |
-> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) |
Retrieve all type and family instances in the environment, indexed
by Name
. Each name's lists will contain every instance in which that name
is mentioned in the instance head.
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]
TM_Inst | Instantiate the type fully (:type) |
TM_NoInst | Do not instantiate the type (:type +v) |
TM_Default | Default the type eagerly (:type +d) |
Looking up a Name
parseName :: GhcMonad m => String -> m [Name] Source #
Parses a string as an identifier, and returns the list of Name
s 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.
compileParsedExpr :: GhcMonad m => LHsExpr GhcPs -> m HValue Source #
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 #
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, Map Int HsDocString)) Source #
data GetDocsFailure Source #
Failure modes for getDocs
.
NameHasNoModule Name |
|
NoDocsInIface Module Bool |
|
InteractiveName | The |
Instances
Outputable GetDocsFailure Source # | |
Defined in GHC.Runtime.Eval ppr :: GetDocsFailure -> SDoc pprPrec :: Rational -> GetDocsFailure -> SDoc |
Other
hasImport :: ParserFlags -> String -> Bool Source #
Returns True
if passed string has an import declaration.
isImport :: ParserFlags -> String -> Bool Source #
Returns True
if passed string is an import declaration.
isDecl :: ParserFlags -> String -> Bool Source #
Returns True
if passed string is a declaration but not a splice.
The debugger
Resume | |
|
getHistoryModule :: History -> Module Source #
abandonAll :: GhcMonad m => m Bool Source #
getResumeContext :: GhcMonad m => m [Resume] Source #
ModBreaks | |
|
type BreakIndex = Int #
Abstract syntax elements
Units
Modules
mkModule :: u -> ModuleName -> GenModule u #
moduleName :: GenModule unit -> ModuleName #
moduleUnit :: GenModule unit -> unit #
data ModuleName #
Instances
mkModuleName :: String -> ModuleName #
moduleNameString :: ModuleName -> String #
Names
Instances
Eq Name | |
Data Name | |
Defined in GHC.Types.Name gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # dataTypeOf :: Name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) # gmapT :: (forall b. Data b => b -> b) -> Name -> Name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
Ord Name | |
NFData Name | |
Defined in GHC.Types.Name | |
Uniquable Name | |
Defined in GHC.Types.Name | |
NamedThing Name | |
Defined in GHC.Types.Name | |
HasOccName Name | |
Defined in GHC.Types.Name | |
Binary Name | |
OutputableBndr Name | |
Defined in GHC.Types.Name pprBndr :: BindingSite -> Name -> SDoc pprPrefixOcc :: Name -> SDoc pprInfixOcc :: Name -> SDoc bndrIsJoin_maybe :: Name -> Maybe Int | |
Outputable Name | |
isExternalName :: Name -> Bool #
nameModule :: HasDebugCallStack => Name -> Module #
pprParenSymName :: NamedThing a => a -> SDoc Source #
print a NamedThing
, adding parentheses if the name is an operator.
nameSrcSpan :: Name -> SrcSpan #
class NamedThing a where #
Instances
NamedThing Name | |
Defined in GHC.Types.Name | |
NamedThing TyThing | |
Defined in GHC.Core.TyCo.Rep | |
NamedThing Var | |
Defined in GHC.Types.Var | |
NamedThing TyCon | |
Defined in GHC.Core.TyCon | |
NamedThing Class | |
Defined in GHC.Core.Class | |
NamedThing DataCon | |
Defined in GHC.Core.DataCon | |
NamedThing ConLike | |
Defined in GHC.Core.ConLike | |
NamedThing PatSyn | |
Defined in GHC.Core.PatSyn | |
NamedThing IfaceDecl | |
Defined in GHC.Iface.Syntax | |
NamedThing ClsInst | |
Defined in GHC.Core.InstEnv | |
NamedThing FamInst | |
Defined in GHC.Core.FamInstEnv | |
NamedThing HoleFitCandidate | |
Defined in GHC.Tc.Errors.Hole.FitTypes | |
NamedThing IfaceClassOp | |
Defined in GHC.Iface.Syntax | |
NamedThing IfaceConDecl | |
Defined in GHC.Iface.Syntax | |
NamedThing e => NamedThing (Located e) | |
Defined in GHC.Types.Name | |
NamedThing (CoAxiom br) | |
Defined in GHC.Core.Coercion.Axiom | |
NamedThing tv => NamedThing (VarBndr tv flag) | |
Defined in GHC.Types.Var | |
NamedThing (HsTyVarBndr flag GhcRn) | |
Defined in GHC.Hs.Type |
Instances
Eq RdrName | |
Data RdrName | |
Defined in GHC.Types.Name.Reader gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RdrName -> c RdrName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RdrName # toConstr :: RdrName -> Constr # dataTypeOf :: RdrName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RdrName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName) # gmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r # gmapQ :: (forall d. Data d => d -> u) -> RdrName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RdrName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName # | |
Ord RdrName | |
HasOccName RdrName | |
Defined in GHC.Types.Name.Reader | |
OutputableBndr RdrName | |
Defined in GHC.Types.Name.Reader pprBndr :: BindingSite -> RdrName -> SDoc pprPrefixOcc :: RdrName -> SDoc pprInfixOcc :: RdrName -> SDoc bndrIsJoin_maybe :: RdrName -> Maybe Int | |
Outputable RdrName | |
DisambInfixOp RdrName | |
Defined in GHC.Parser.PostProcess mkHsVarOpPV :: Located RdrName -> PV (Located RdrName) mkHsConOpPV :: Located RdrName -> PV (Located RdrName) mkHsInfixHolePV :: SrcSpan -> PV (Located RdrName) |
Identifiers
isImplicitId :: Id -> Bool #
isDeadBinder :: Id -> Bool #
isExportedId :: Var -> Bool #
isGlobalId :: Var -> Bool #
isRecordSelector :: Id -> Bool #
isPrimOpId :: Id -> Bool #
isClassOpId_maybe :: Id -> Maybe Class #
isDataConWorkId :: Id -> Bool #
isDeadEndId :: Var -> Bool #
isDictonaryId :: Id -> Bool Source #
recordSelectorTyCon :: Id -> RecSelParent #
Type constructors
Instances
Eq TyCon | |
Data TyCon | |
Defined in GHC.Core.TyCon gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyCon -> c TyCon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyCon # dataTypeOf :: TyCon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyCon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCon) # gmapT :: (forall b. Data b => b -> b) -> TyCon -> TyCon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyCon -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyCon -> r # gmapQ :: (forall d. Data d => d -> u) -> TyCon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyCon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon # | |
Uniquable TyCon | |
Defined in GHC.Core.TyCon | |
NamedThing TyCon | |
Defined in GHC.Core.TyCon | |
Outputable 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 #
Type variables
alphaTyVars :: [TyVar] #
Data constructors
Instances
Eq DataCon | |
Data DataCon | |
Defined in GHC.Core.DataCon gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataCon -> c DataCon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataCon # toConstr :: DataCon -> Constr # dataTypeOf :: DataCon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataCon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataCon) # gmapT :: (forall b. Data b => b -> b) -> DataCon -> DataCon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r # gmapQ :: (forall d. Data d => d -> u) -> DataCon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataCon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon # | |
Uniquable DataCon | |
Defined in GHC.Core.DataCon | |
NamedThing DataCon | |
Defined in GHC.Core.DataCon | |
OutputableBndr DataCon | |
Defined in GHC.Core.DataCon pprBndr :: BindingSite -> DataCon -> SDoc pprPrefixOcc :: DataCon -> SDoc pprInfixOcc :: DataCon -> SDoc bndrIsJoin_maybe :: DataCon -> Maybe Int | |
Outputable DataCon | |
dataConType :: DataCon -> Type Source #
dataConTyCon :: DataCon -> TyCon #
dataConFieldLabels :: DataCon -> [FieldLabel] #
dataConIsInfix :: DataCon -> Bool #
isVanillaDataCon :: DataCon -> Bool #
dataConWrapperType :: DataCon -> Type #
dataConSrcBangs :: DataCon -> [HsSrcBang] #
data StrictnessMark #
Instances
Outputable StrictnessMark | |
Defined in GHC.Core.DataCon ppr :: StrictnessMark -> SDoc pprPrec :: Rational -> StrictnessMark -> SDoc |
isMarkedStrict :: StrictnessMark -> Bool #
Classes
Instances
Eq Class | |
Data Class | |
Defined in GHC.Core.Class gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Class -> c Class # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Class # dataTypeOf :: Class -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Class) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Class) # gmapT :: (forall b. Data b => b -> b) -> Class -> Class # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r # gmapQ :: (forall d. Data d => d -> u) -> Class -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Class -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Class -> m Class # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class # | |
Uniquable Class | |
Defined in GHC.Core.Class | |
NamedThing Class | |
Defined in GHC.Core.Class | |
Outputable Class | |
classMethods :: Class -> [Id] #
classSCTheta :: Class -> [PredType] #
classTvsFds :: Class -> ([TyVar], [FunDep TyVar]) #
pprFundeps :: Outputable a => [FunDep a] -> SDoc #
Instances
Instances
Data ClsInst | |
Defined in GHC.Core.InstEnv gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInst -> c ClsInst # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClsInst # toConstr :: ClsInst -> Constr # dataTypeOf :: ClsInst -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClsInst) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClsInst) # gmapT :: (forall b. Data b => b -> b) -> ClsInst -> ClsInst # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r # gmapQ :: (forall d. Data d => d -> u) -> ClsInst -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInst -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # | |
NamedThing ClsInst | |
Defined in GHC.Core.InstEnv | |
Outputable ClsInst | |
instanceDFunId :: ClsInst -> DFunId #
pprInstance :: ClsInst -> SDoc #
pprInstanceHdr :: ClsInst -> SDoc #
pprFamInst :: FamInst -> SDoc Source #
Pretty-prints a FamInst
(type/data family instance) with its defining location.
Instances
NamedThing FamInst | |
Defined in GHC.Core.FamInstEnv | |
Outputable FamInst | |
Types and Kinds
Instances
Data Type | |
Defined in GHC.Core.TyCo.Rep gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type # dataTypeOf :: Type -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Type) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) # gmapT :: (forall b. Data b => b -> b) -> Type -> Type # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # | |
Outputable Type | |
Eq (DeBruijn Type) | |
splitForAllTys :: Type -> ([TyCoVar], Type) #
funResultTy :: Type -> Type #
pprParendType :: Type -> SDoc #
pprTypeApp :: TyCon -> [Type] -> SDoc #
pprForAll :: [TyCoVarBinder] -> SDoc #
pprThetaArrowTy :: ThetaType -> SDoc #
Entities
Instances
NamedThing TyThing | |
Defined in GHC.Core.TyCo.Rep | |
Outputable TyThing | |
Syntax
Fixities
data FixityDirection #
Instances
Eq FixityDirection | |
Defined in GHC.Types.Basic (==) :: FixityDirection -> FixityDirection -> Bool # (/=) :: FixityDirection -> FixityDirection -> Bool # | |
Data FixityDirection | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixityDirection -> c FixityDirection # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FixityDirection # toConstr :: FixityDirection -> Constr # dataTypeOf :: FixityDirection -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FixityDirection) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FixityDirection) # gmapT :: (forall b. Data b => b -> b) -> FixityDirection -> FixityDirection # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r # gmapQ :: (forall d. Data d => d -> u) -> FixityDirection -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FixityDirection -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # | |
Binary FixityDirection | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> FixityDirection -> IO () put :: BinHandle -> FixityDirection -> IO (Bin FixityDirection) get :: BinHandle -> IO FixityDirection | |
Outputable FixityDirection | |
Defined in GHC.Types.Basic ppr :: FixityDirection -> SDoc pprPrec :: Rational -> FixityDirection -> SDoc |
defaultFixity :: Fixity #
maxPrecedence :: Int #
negateFixity :: Fixity #
compareFixity :: Fixity -> Fixity -> (Bool, Bool) #
data LexicalFixity #
Instances
Eq LexicalFixity | |
Defined in GHC.Types.Basic (==) :: LexicalFixity -> LexicalFixity -> Bool # (/=) :: LexicalFixity -> LexicalFixity -> Bool # | |
Data LexicalFixity | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LexicalFixity # toConstr :: LexicalFixity -> Constr # dataTypeOf :: LexicalFixity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LexicalFixity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LexicalFixity) # gmapT :: (forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r # gmapQ :: (forall d. Data d => d -> u) -> LexicalFixity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # | |
Outputable LexicalFixity | |
Defined in GHC.Types.Basic ppr :: LexicalFixity -> SDoc pprPrec :: Rational -> LexicalFixity -> SDoc |
Source locations
RealSrcLoc !RealSrcLoc !(Maybe BufPos) | |
UnhelpfulLoc FastString |
data RealSrcLoc #
Instances
Eq RealSrcLoc | |
Defined in GHC.Types.SrcLoc (==) :: RealSrcLoc -> RealSrcLoc -> Bool # (/=) :: RealSrcLoc -> RealSrcLoc -> Bool # | |
Ord RealSrcLoc | |
Defined in GHC.Types.SrcLoc compare :: RealSrcLoc -> RealSrcLoc -> Ordering # (<) :: RealSrcLoc -> RealSrcLoc -> Bool # (<=) :: RealSrcLoc -> RealSrcLoc -> Bool # (>) :: RealSrcLoc -> RealSrcLoc -> Bool # (>=) :: RealSrcLoc -> RealSrcLoc -> Bool # max :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # min :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # | |
Show RealSrcLoc | |
Defined in GHC.Types.SrcLoc showsPrec :: Int -> RealSrcLoc -> ShowS # show :: RealSrcLoc -> String # showList :: [RealSrcLoc] -> ShowS # | |
Outputable RealSrcLoc | |
Defined in GHC.Types.SrcLoc ppr :: RealSrcLoc -> SDoc pprPrec :: Rational -> RealSrcLoc -> SDoc |
srcLocFile :: RealSrcLoc -> FastString #
srcLocLine :: RealSrcLoc -> Int #
srcLocCol :: RealSrcLoc -> Int #
RealSrcSpan !RealSrcSpan !(Maybe BufSpan) | |
UnhelpfulSpan !UnhelpfulSpanReason |
Instances
Eq SrcSpan | |
Data SrcSpan | |
Defined in GHC.Types.SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcSpan -> c SrcSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcSpan # toConstr :: SrcSpan -> Constr # dataTypeOf :: SrcSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcSpan) # gmapT :: (forall b. Data b => b -> b) -> SrcSpan -> SrcSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # | |
Show SrcSpan | |
NFData SrcSpan | |
Defined in GHC.Types.SrcLoc | |
Binary SrcSpan | |
Outputable SrcSpan | |
ToJson SrcSpan | |
Defined in GHC.Types.SrcLoc | |
NamedThing e => NamedThing (Located e) | |
Defined in GHC.Types.Name | |
Binary a => Binary (Located a) | |
data RealSrcSpan #
Instances
srcLocSpan :: SrcLoc -> SrcSpan #
isGoodSrcSpan :: SrcSpan -> Bool #
srcSpanStart :: SrcSpan -> SrcLoc #
srcSpanEnd :: SrcSpan -> SrcLoc #
srcSpanFile :: RealSrcSpan -> FastString #
srcSpanStartLine :: RealSrcSpan -> Int #
srcSpanEndLine :: RealSrcSpan -> Int #
srcSpanStartCol :: RealSrcSpan -> Int #
srcSpanEndCol :: RealSrcSpan -> Int #
Located
data GenLocated l e #
L l e |
Instances
Functor (GenLocated l) | |
Defined in GHC.Types.SrcLoc fmap :: (a -> b) -> GenLocated l a -> GenLocated l b # (<$) :: a -> GenLocated l b -> GenLocated l a # | |
Foldable (GenLocated l) | |
Defined in GHC.Types.SrcLoc fold :: Monoid m => GenLocated l m -> m # foldMap :: Monoid m => (a -> m) -> GenLocated l a -> m # foldMap' :: Monoid m => (a -> m) -> GenLocated l a -> m # foldr :: (a -> b -> b) -> b -> GenLocated l a -> b # foldr' :: (a -> b -> b) -> b -> GenLocated l a -> b # foldl :: (b -> a -> b) -> b -> GenLocated l a -> b # foldl' :: (b -> a -> b) -> b -> GenLocated l a -> b # foldr1 :: (a -> a -> a) -> GenLocated l a -> a # foldl1 :: (a -> a -> a) -> GenLocated l a -> a # toList :: GenLocated l a -> [a] # null :: GenLocated l a -> Bool # length :: GenLocated l a -> Int # elem :: Eq a => a -> GenLocated l a -> Bool # maximum :: Ord a => GenLocated l a -> a # minimum :: Ord a => GenLocated l a -> a # sum :: Num a => GenLocated l a -> a # product :: Num a => GenLocated l a -> a # | |
Traversable (GenLocated l) | |
Defined in GHC.Types.SrcLoc traverse :: Applicative f => (a -> f b) -> GenLocated l a -> f (GenLocated l b) # sequenceA :: Applicative f => GenLocated l (f a) -> f (GenLocated l a) # mapM :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b) # sequence :: Monad m => GenLocated l (m a) -> m (GenLocated l a) # | |
NamedThing e => NamedThing (Located e) | |
Defined in GHC.Types.Name | |
Binary a => Binary (Located a) | |
(Eq l, Eq e) => Eq (GenLocated l e) | |
Defined in GHC.Types.SrcLoc (==) :: GenLocated l e -> GenLocated l e -> Bool # (/=) :: GenLocated l e -> GenLocated l e -> Bool # | |
(Data l, Data e) => Data (GenLocated l e) | |
Defined in GHC.Types.SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenLocated l e) # toConstr :: GenLocated l e -> Constr # dataTypeOf :: GenLocated l e -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e)) # dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (GenLocated l e)) # gmapT :: (forall b. Data b => b -> b) -> GenLocated l e -> GenLocated l e # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r # gmapQ :: (forall d. Data d => d -> u) -> GenLocated l e -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # | |
(Ord l, Ord e) => Ord (GenLocated l e) | |
Defined in GHC.Types.SrcLoc compare :: GenLocated l e -> GenLocated l e -> Ordering # (<) :: GenLocated l e -> GenLocated l e -> Bool # (<=) :: GenLocated l e -> GenLocated l e -> Bool # (>) :: GenLocated l e -> GenLocated l e -> Bool # (>=) :: GenLocated l e -> GenLocated l e -> Bool # max :: GenLocated l e -> GenLocated l e -> GenLocated l e # min :: GenLocated l e -> GenLocated l e -> GenLocated l e # | |
(Outputable l, Outputable e) => Outputable (GenLocated l e) | |
Defined in GHC.Types.SrcLoc ppr :: GenLocated l e -> SDoc pprPrec :: Rational -> GenLocated l e -> SDoc |
type Located = GenLocated SrcSpan #
type RealLocated = GenLocated RealSrcSpan #
Constructing Located
mkGeneralLocated :: String -> e -> Located e #
Deconstructing Located
getLoc :: GenLocated l e -> l #
unLoc :: GenLocated l e -> e #
getRealSrcSpan :: RealLocated a -> RealSrcSpan #
unRealSrcSpan :: RealLocated a -> a #
Combining and comparing Located values
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 #
leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering #
leftmost_largest :: SrcSpan -> SrcSpan -> Ordering #
rightmost_smallest :: SrcSpan -> SrcSpan -> Ordering #
isSubspanOf :: SrcSpan -> SrcSpan -> Bool #
Exceptions
data GhcException #
Signal Int | |
UsageError String | |
CmdLineError String | |
Panic String | |
PprPanic String SDoc | |
Sorry String | |
PprSorry String SDoc | |
InstallationError String | |
ProgramError String | |
PprProgramError String SDoc |
Instances
Show GhcException | |
Defined in GHC.Utils.Panic showsPrec :: Int -> GhcException -> ShowS # show :: GhcException -> String # showList :: [GhcException] -> ShowS # | |
Exception GhcException | |
Defined in GHC.Utils.Panic |
showGhcException :: GhcException -> ShowS #
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
:: 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 #
Instances
data AnnotationComment #
AnnDocCommentNext String | |
AnnDocCommentPrev String | |
AnnDocCommentNamed String | |
AnnDocSection Int String | |
AnnDocOptions String | |
AnnLineComment String | |
AnnBlockComment String |
Instances
type ApiAnnKey = (RealSrcSpan, AnnKeywordId) #
getAnnotation :: ApiAnns -> RealSrcSpan -> AnnKeywordId -> [RealSrcSpan] #
getAndRemoveAnnotation :: ApiAnns -> RealSrcSpan -> AnnKeywordId -> ([RealSrcSpan], ApiAnns) #
getAndRemoveAnnotationComments :: ApiAnns -> RealSrcSpan -> ([RealLocated AnnotationComment], ApiAnns) #
unicodeAnn :: AnnKeywordId -> AnnKeywordId #
Miscellaneous
cyclicModuleErr :: [ModSummary] -> SDoc Source #