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, MonadIO m) => m a -> m a
- withCleanupSession :: GhcMonad m => m a -> m a
- data Ghc a
- data GhcT (m :: Type -> Type) a
- class (Functor m, MonadIO 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 ()
- gcatch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m a
- gbracket :: ExceptionMonad m => m a -> (a -> m b) -> (a -> m c) -> m c
- gfinally :: ExceptionMonad m => m a -> m b -> m a
- printException :: GhcMonad m => SourceError -> m ()
- handleSourceError :: ExceptionMonad m => (SourceError -> m a) -> m a -> m a
- needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
- data DynFlags = DynFlags {
- ghcMode :: GhcMode
- ghcLink :: GhcLink
- hscTarget :: HscTarget
- settings :: Settings
- integerLibrary :: IntegerLibrary
- llvmTargets :: LlvmTargets
- llvmPasses :: LlvmPasses
- verbosity :: Int
- optLevel :: Int
- debugLevel :: Int
- simplPhases :: Int
- maxSimplIterations :: Int
- maxPmCheckIterations :: 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
- simplTickFactor :: Int
- specConstrThreshold :: Maybe Int
- specConstrCount :: Maybe Int
- specConstrRecursive :: Int
- liberateCaseThreshold :: Maybe Int
- floatLamArgs :: Maybe Int
- liftLamsRecArgs :: Maybe Int
- liftLamsNonRecArgs :: Maybe Int
- liftLamsKnown :: Bool
- cmmProcAlignment :: Maybe Int
- historySize :: Int
- importPaths :: [FilePath]
- mainModIs :: Module
- mainFunIs :: Maybe String
- reductionDepth :: IntWithInf
- solverIterations :: IntWithInf
- thisInstalledUnitId :: InstalledUnitId
- thisComponentId_ :: Maybe ComponentId
- thisUnitIdInsts_ :: Maybe [(ModuleName, Module)]
- ways :: [Way]
- buildTag :: String
- splitInfo :: Maybe (String, Int)
- objectDir :: Maybe String
- dylibInstallName :: Maybe String
- hiDir :: Maybe String
- hieDir :: Maybe String
- stubDir :: Maybe String
- dumpDir :: Maybe String
- objectSuf :: String
- hcSuf :: String
- hiSuf :: String
- hieSuf :: String
- canGenerateDynamicToo :: IORef Bool
- dynObjectSuf :: String
- dynHiSuf :: String
- outputFile :: Maybe String
- dynOutputFile :: Maybe String
- outputHi :: Maybe String
- dynLibLoader :: DynLibLoader
- dumpPrefix :: Maybe FilePath
- dumpPrefixForce :: Maybe FilePath
- ldInputs :: [Option]
- includePaths :: IncludeSpecs
- libraryPaths :: [String]
- frameworkPaths :: [String]
- cmdlineFrameworks :: [String]
- rtsOpts :: Maybe String
- rtsOptsEnabled :: RtsOptsEnabled
- rtsOptsSuggestions :: Bool
- hpcDir :: String
- pluginModNames :: [ModuleName]
- pluginModNameOpts :: [(ModuleName, String)]
- frontendPluginOpts :: [String]
- cachedPlugins :: [LoadedPlugin]
- staticPlugins :: [StaticPlugin]
- hooks :: Hooks
- depMakefile :: FilePath
- depIncludePkgDeps :: Bool
- depExcludeMods :: [ModuleName]
- depSuffixes :: [String]
- packageDBFlags :: [PackageDBFlag]
- ignorePackageFlags :: [IgnorePackageFlag]
- packageFlags :: [PackageFlag]
- pluginPackageFlags :: [PackageFlag]
- trustFlags :: [TrustFlag]
- packageEnv :: Maybe FilePath
- pkgDatabase :: Maybe [(FilePath, [PackageConfig])]
- pkgState :: PackageState
- filesToClean :: IORef FilesToClean
- dirsToClean :: IORef (Map FilePath FilePath)
- nextTempSuffix :: IORef Int
- generatedDumps :: IORef (Set FilePath)
- dumpFlags :: EnumSet DumpFlag
- generalFlags :: EnumSet GeneralFlag
- warningFlags :: EnumSet WarningFlag
- fatalWarningFlags :: EnumSet WarningFlag
- language :: Maybe Language
- safeHaskell :: SafeHaskellMode
- safeInfer :: Bool
- safeInferred :: Bool
- thOnLoc :: SrcSpan
- newDerivOnLoc :: SrcSpan
- overlapInstLoc :: SrcSpan
- incoherentOnLoc :: SrcSpan
- pkgTrustOnLoc :: SrcSpan
- warnSafeOnLoc :: SrcSpan
- warnUnsafeOnLoc :: SrcSpan
- trustworthyOnLoc :: SrcSpan
- extensions :: [OnOff Extension]
- extensionFlags :: EnumSet Extension
- ufCreationThreshold :: Int
- ufUseThreshold :: Int
- ufFunAppDiscount :: Int
- ufDictDiscount :: Int
- ufKeenessFactor :: Float
- ufDearOp :: Int
- ufVeryAggressive :: Bool
- maxWorkerArgs :: Int
- ghciHistSize :: Int
- log_action :: LogAction
- flushOut :: FlushOut
- flushErr :: FlushErr
- ghcVersionFile :: Maybe FilePath
- haddockOptions :: Maybe String
- ghciScripts :: [String]
- pprUserLength :: Int
- pprCols :: Int
- useUnicode :: Bool
- useColor :: OverridingBool
- canUseColor :: Bool
- colScheme :: Scheme
- profAuto :: ProfAuto
- interactivePrint :: Maybe String
- nextWrapperNum :: IORef (ModuleEnv Int)
- sseVersion :: Maybe SseVersion
- bmiVersion :: Maybe BmiVersion
- avx :: Bool
- avx2 :: Bool
- avx512cd :: Bool
- avx512er :: Bool
- avx512f :: Bool
- avx512pf :: Bool
- rtldInfo :: IORef (Maybe LinkerInfo)
- rtccInfo :: IORef (Maybe CompilerInfo)
- maxInlineAllocSize :: Int
- maxInlineMemcpyInsns :: Int
- maxInlineMemsetInsns :: Int
- reverseErrors :: Bool
- maxErrors :: Maybe Int
- initialUnique :: Int
- uniqueIncrement :: Int
- cfgWeightInfo :: CfgWeights
- data GeneralFlag
- = Opt_DumpToFile
- | Opt_D_faststring_stats
- | Opt_D_dump_minimal_imports
- | Opt_DoCoreLinting
- | Opt_DoStgLinting
- | Opt_DoCmmLinting
- | Opt_DoAsmLinting
- | Opt_DoAnnotationLinting
- | Opt_NoLlvmMangler
- | Opt_FastLlvm
- | Opt_WarnIsError
- | Opt_ShowWarnGroups
- | Opt_HideSourcePaths
- | Opt_PrintExplicitForalls
- | Opt_PrintExplicitKinds
- | Opt_PrintExplicitCoercions
- | Opt_PrintExplicitRuntimeReps
- | Opt_PrintEqualityRelations
- | 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_RegsGraph
- | Opt_RegsIterative
- | Opt_PedanticBottoms
- | Opt_LlvmTBAA
- | Opt_LlvmFillUndefWithGarbage
- | Opt_IrrefutableTuples
- | Opt_CmmSink
- | Opt_CmmElimCommonBlocks
- | Opt_AsmShortcutting
- | Opt_OmitYields
- | Opt_FunToThunk
- | Opt_DictsStrict
- | Opt_DmdTxDictSel
- | Opt_Loopification
- | Opt_CfgBlocklayout
- | Opt_WeightlessBlocklayout
- | Opt_CprAnal
- | Opt_WorkerWrapper
- | Opt_SolveConstantDicts
- | Opt_AlignmentSanitisation
- | Opt_CatchBottoms
- | Opt_NumConstantFolding
- | Opt_SimplPreInlining
- | Opt_IgnoreInterfacePragmas
- | Opt_OmitInterfacePragmas
- | Opt_ExposeAllUnfoldings
- | Opt_WriteInterface
- | Opt_WriteHie
- | Opt_AutoSccsOnIndividualCafs
- | Opt_ProfCountEntries
- | Opt_Pp
- | Opt_ForceRecomp
- | Opt_IgnoreOptimChanges
- | Opt_IgnoreHpcChanges
- | Opt_ExcessPrecision
- | Opt_EagerBlackHoling
- | Opt_NoHsMain
- | Opt_SplitObjs
- | Opt_SplitSections
- | Opt_StgStats
- | Opt_HideAllPackages
- | Opt_HideAllPluginPackages
- | Opt_PrintBindResult
- | Opt_Haddock
- | Opt_HaddockOptions
- | Opt_BreakOnException
- | Opt_BreakOnError
- | Opt_PrintEvldWithShow
- | Opt_PrintBindContents
- | Opt_GenManifest
- | Opt_EmbedManifest
- | Opt_SharedImplib
- | Opt_BuildingCabalPackage
- | Opt_IgnoreDotGhci
- | Opt_GhciSandbox
- | Opt_GhciHistory
- | Opt_GhciLeakCheck
- | Opt_ValidateHie
- | Opt_LocalGhciHistory
- | Opt_NoIt
- | Opt_HelpfulErrors
- | Opt_DeferTypeErrors
- | Opt_DeferTypedHoles
- | Opt_DeferOutOfScopeVariables
- | Opt_PIC
- | Opt_PIE
- | Opt_PICExecutable
- | Opt_ExternalDynamicRefs
- | Opt_SccProfilingOn
- | Opt_Ticky
- | Opt_Ticky_Allocd
- | Opt_Ticky_LNE
- | Opt_Ticky_Dyn_Thunk
- | Opt_RPath
- | Opt_RelativeDynlibPaths
- | Opt_Hpc
- | Opt_FlatCache
- | Opt_ExternalInterpreter
- | Opt_OptimalApplicativeDo
- | Opt_VersionMacros
- | Opt_WholeArchiveHsLibs
- | Opt_SingleLibFolder
- | Opt_KeepCAFs
- | Opt_ErrorSpans
- | 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_G_NoStateHack
- | Opt_G_NoOptCoercion
- data Severity
- data HscTarget
- gopt :: GeneralFlag -> DynFlags -> Bool
- data GhcMode
- data GhcLink
- defaultObjectTarget :: Platform -> HscTarget
- parseDynamicFlags :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- getSessionDynFlags :: GhcMonad m => m DynFlags
- setSessionDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId]
- getProgramDynFlags :: GhcMonad m => m DynFlags
- setProgramDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId]
- setLogAction :: GhcMonad m => LogAction -> m ()
- getInteractiveDynFlags :: GhcMonad m => m DynFlags
- setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
- data Target = Target {}
- 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
- load :: GhcMonad m => LoadHowMuch -> m SuccessFlag
- data LoadHowMuch
- data InteractiveImport
- 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 {}
- data DesugaredModule = DesugaredModule {}
- type TypecheckedSource = LHsBinds GhcTc
- type ParsedSource = Located (HsModule GhcPs)
- 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 :: [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
- 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)
- data ModIface = ModIface {
- mi_module :: !Module
- mi_sig_of :: !(Maybe Module)
- mi_iface_hash :: !Fingerprint
- mi_mod_hash :: !Fingerprint
- mi_flag_hash :: !Fingerprint
- mi_opt_hash :: !Fingerprint
- mi_hpc_hash :: !Fingerprint
- mi_plugin_hash :: !Fingerprint
- mi_orphan :: !WhetherHasOrphans
- mi_finsts :: !WhetherHasFamInst
- mi_hsc_src :: !HscSource
- mi_deps :: Dependencies
- mi_usages :: [Usage]
- mi_exports :: ![IfaceExport]
- mi_exp_hash :: !Fingerprint
- mi_used_th :: !Bool
- mi_fixities :: [(OccName, Fixity)]
- mi_warns :: Warnings
- mi_anns :: [IfaceAnnotation]
- mi_decls :: [(Fingerprint, IfaceDecl)]
- mi_globals :: !(Maybe GlobalRdrEnv)
- mi_insts :: [IfaceClsInst]
- mi_fam_insts :: [IfaceFamInst]
- mi_rules :: [IfaceRule]
- mi_orphan_hash :: !Fingerprint
- mi_warn_fn :: OccName -> Maybe WarningTxt
- mi_fix_fn :: OccName -> Maybe Fixity
- mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint)
- 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
- 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 InstalledUnitId)
- 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 :: DynFlags -> String -> Bool
- hasImport :: DynFlags -> String -> Bool
- isImport :: DynFlags -> String -> Bool
- isDecl :: DynFlags -> 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
- back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- data UnitId
- data Module
- mkModule :: UnitId -> ModuleName -> Module
- pprModule :: Module -> SDoc
- moduleName :: Module -> ModuleName
- moduleUnitId :: Module -> UnitId
- 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
- isBottomingId :: 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
- dataConSig :: DataCon -> ([TyCoVar], ThetaType, [Type], Type)
- dataConType :: DataCon -> Type
- dataConTyCon :: DataCon -> TyCon
- dataConFieldLabels :: DataCon -> [FieldLabel]
- dataConIsInfix :: DataCon -> Bool
- isVanillaDataCon :: DataCon -> Bool
- dataConUserType :: 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
- data TyThing
- module HsSyn
- 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
- noLoc :: HasSrcSpan a => SrcSpanLess a -> a
- mkGeneralLocated :: HasSrcSpan e => String -> SrcSpanLess e -> e
- getLoc :: HasSrcSpan a => a -> SrcSpan
- unLoc :: HasSrcSpan a => a -> SrcSpanLess a
- getRealSrcSpan :: RealLocated a -> RealSrcSpan
- unRealSrcSpan :: RealLocated a -> a
- class HasSrcSpan a where
- composeSrcSpan :: Located (SrcSpanLess a) -> a
- decomposeSrcSpan :: a -> Located (SrcSpanLess a)
- type family SrcSpanLess a :: Type
- dL :: HasSrcSpan a => a -> Located (SrcSpanLess a)
- cL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
- eqLocated :: (HasSrcSpan a, Eq (SrcSpanLess a)) => a -> a -> Bool
- cmpLocated :: (HasSrcSpan a, Ord (SrcSpanLess a)) => a -> a -> Ordering
- combineLocs :: (HasSrcSpan a, HasSrcSpan b) => a -> b -> SrcSpan
- addCLoc :: (HasSrcSpan a, HasSrcSpan b, HasSrcSpan c) => a -> b -> SrcSpanLess c -> c
- leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering
- leftmost_largest :: SrcSpan -> SrcSpan -> Ordering
- rightmost :: SrcSpan -> SrcSpan -> Ordering
- spans :: SrcSpan -> (Int, Int) -> Bool
- isSubspanOf :: SrcSpan -> SrcSpan -> Bool
- data GhcException
- 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 GhcPs)))
- type ApiAnns = (Map ApiAnnKey [SrcSpan], Map SrcSpan [Located AnnotationComment])
- data AnnKeywordId
- = AnnAnyclass
- | AnnAs
- | AnnAt
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnClass
- | AnnClose
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | AnnCloseS
- | AnnColon
- | AnnComma
- | AnnCommaTuple
- | AnnDarrow
- | AnnDarrowU
- | AnnData
- | AnnDcolon
- | AnnDcolonU
- | AnnDefault
- | AnnDeriving
- | AnnDo
- | AnnDot
- | AnnDotdot
- | AnnElse
- | AnnEqual
- | AnnExport
- | AnnFamily
- | AnnForall
- | AnnForallU
- | AnnForeign
- | AnnFunId
- | AnnGroup
- | AnnHeader
- | AnnHiding
- | AnnIf
- | AnnImport
- | AnnIn
- | AnnInfix
- | AnnInstance
- | AnnLam
- | AnnLarrow
- | AnnLarrowU
- | AnnLet
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenPE
- | AnnOpenPTE
- | AnnOpenS
- | AnnPackageName
- | AnnPattern
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRarrowU
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnSignature
- | AnnStatic
- | AnnStock
- | AnnThen
- | AnnThIdSplice
- | AnnThIdTySplice
- | AnnThTyQuote
- | AnnTilde
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnVia
- | AnnWhere
- | Annlarrowtail
- | AnnlarrowtailU
- | Annrarrowtail
- | AnnrarrowtailU
- | AnnLarrowtail
- | AnnLarrowtailU
- | AnnRarrowtail
- | AnnRarrowtailU
- | AnnEofPos
- data AnnotationComment
- getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan]
- getAndRemoveAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> ([SrcSpan], ApiAnns)
- getAnnotationComments :: ApiAnns -> SrcSpan -> [Located AnnotationComment]
- getAndRemoveAnnotationComments :: ApiAnns -> SrcSpan -> ([Located 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, MonadIO m) => m a -> m a #
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
Monad Ghc | |
Functor Ghc | |
MonadFix Ghc | |
Applicative Ghc | |
MonadIO Ghc | |
GhcMonad Ghc | |
Defined in GhcMonad getSession :: Ghc HscEnv # setSession :: HscEnv -> Ghc () # | |
HasDynFlags Ghc | |
Defined in GhcMonad getDynFlags :: Ghc DynFlags # | |
ExceptionMonad Ghc | |
data GhcT (m :: Type -> Type) a #
A monad transformer to add GHC specific features to another monad.
Note that the wrapped monad must support IO and handling of exceptions.
Instances
Monad m => Monad (GhcT m) | |
Functor m => Functor (GhcT m) | |
Applicative m => Applicative (GhcT m) | |
MonadIO m => MonadIO (GhcT m) | |
ExceptionMonad m => GhcMonad (GhcT m) | |
Defined in GhcMonad getSession :: GhcT m HscEnv # setSession :: HscEnv -> GhcT m () # | |
MonadIO m => HasDynFlags (GhcT m) | |
Defined in GhcMonad getDynFlags :: GhcT m DynFlags # | |
ExceptionMonad m => ExceptionMonad (GhcT m) | |
class (Functor m, MonadIO m, ExceptionMonad m, HasDynFlags m) => GhcMonad (m :: Type -> Type) where #
A monad that has all the features needed by GHC API calls.
In short, a GHC monad
- allows embedding of IO actions,
- can log warnings,
- allows handling of (extensible) exceptions, and
- maintains a current session.
If you do not use Ghc
or GhcT
, make sure to call initGhcMonad
before any call to the GHC API functions can occur.
getSession :: m HscEnv #
setSession :: HscEnv -> m () #
Instances
GhcMonad Ghc | |
Defined in GhcMonad getSession :: Ghc HscEnv # setSession :: HscEnv -> Ghc () # | |
ExceptionMonad m => GhcMonad (GhcT m) | |
Defined in GhcMonad getSession :: GhcT m HscEnv # setSession :: HscEnv -> GhcT m () # |
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--. 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.
:: 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.
gcatch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m a #
gbracket :: ExceptionMonad m => m a -> (a -> m b) -> (a -> m c) -> m c #
gfinally :: ExceptionMonad m => m a -> m b -> m a #
printException :: GhcMonad m => SourceError -> m () #
Print the error message and all warnings. Useful inside exception handlers. Clears warnings after printing.
:: ExceptionMonad m | |
=> (SourceError -> m a) | exception handler |
-> m a | action to perform |
-> m a |
Perform the given action and call the exception handler if the action
throws a SourceError
. See SourceError
for more information.
needsTemplateHaskellOrQQ :: ModuleGraph -> Bool #
Determines whether a set of modules requires Template Haskell or Quasi Quotes
Note that if the session's DynFlags
enabled Template Haskell when
depanal
was called, then each module in the returned module graph will
have Template Haskell enabled whether it is actually needed or not.
Flags and settings
Contains not only a collection of GeneralFlag
s but also a plethora of
information relating to the compilation of a single file or GHC session
DynFlags | |
|
data GeneralFlag #
Enumerates the simple on-or-off dynamic flags
Instances
Enum GeneralFlag | |
Defined in DynFlags succ :: GeneralFlag -> GeneralFlag # pred :: GeneralFlag -> GeneralFlag # toEnum :: Int -> GeneralFlag # fromEnum :: GeneralFlag -> Int # enumFrom :: GeneralFlag -> [GeneralFlag] # enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag] # | |
Eq GeneralFlag | |
Defined in DynFlags (==) :: GeneralFlag -> GeneralFlag -> Bool # (/=) :: GeneralFlag -> GeneralFlag -> Bool # | |
Show GeneralFlag | |
Defined in DynFlags showsPrec :: Int -> GeneralFlag -> ShowS # show :: GeneralFlag -> String # showList :: [GeneralFlag] -> ShowS # |
SevOutput | |
SevFatal | |
SevInteractive | |
SevDump | Log message intended for compiler developers No filelinecolumn stuff |
SevInfo | Log messages intended for end users. No filelinecolumn stuff. |
SevWarning | |
SevError | SevWarning and SevError are used for warnings and errors o The message has a filelinecolumn heading, plus "warning:" or "error:", added by mkLocMessags o Output is intended for end users |
The target code type of the compilation (if any).
Whenever you change the target, also make sure to set ghcLink
to
something sensible.
HscNothing
can be used to avoid generating any output, however, note
that:
- If a program uses Template Haskell the typechecker may need to run code from an imported module. To facilitate this, code generation is enabled for modules imported by modules that use template haskell. See Note [-fno-code mode].
HscC | Generate C code. |
HscAsm | Generate assembly using the native code generator. |
HscLlvm | Generate assembly using the llvm code generator. |
HscInterpreted | Generate bytecode. (Requires |
HscNothing | Don't generate any code. See notes above. |
gopt :: GeneralFlag -> DynFlags -> Bool #
Test whether a GeneralFlag
is set
The GhcMode
tells us whether we're doing multi-module
compilation (controlled via the GHC API) or one-shot
(single-module) compilation. This makes a difference primarily to
the Finder: in one-shot mode we look for interface files for
imported modules, but in multi-module mode we look for source files
in order to check whether they need to be recompiled.
CompManager |
|
OneShot | ghc -c Foo.hs |
MkDepend |
|
What to do in the link step, if there is one.
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 |
defaultObjectTarget :: Platform -> HscTarget #
The HscTarget
value corresponding to the default way to create
object files on the current platform.
parseDynamicFlags :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn]) Source #
getSessionDynFlags :: GhcMonad m => m DynFlags #
Grabs the DynFlags from the Session
setSessionDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId] 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.
setProgramDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId] Source #
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
pkgState
into the interactive DynFlags
.
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).
Target | |
|
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
:: 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.
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.
Throw a SourceError
if errors are encountered before the actual
compilation starts (e.g., during dependency analysis). All other errors
are reported using the defaultWarnErrLogger
.
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) | Bring the exports of a particular module (filtered by an import decl) into scope |
IIModule ModuleName | Bring into scope the entire top-level envt of of this module, including the things imported into it. |
Instances
Outputable InteractiveImport | |
Defined in HscTypes ppr :: InteractiveImport -> SDoc # pprPrec :: Rational -> InteractiveImport -> SDoc # |
data SuccessFlag #
Instances
Outputable SuccessFlag | |
Defined in BasicTypes ppr :: SuccessFlag -> SDoc # pprPrec :: Rational -> SuccessFlag -> SDoc # |
succeeded :: SuccessFlag -> Bool #
failed :: SuccessFlag -> Bool #
type WarnErrLogger = forall (m :: Type -> Type). GhcMonad m => Maybe SourceError -> m () #
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
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.
Instances
TypecheckedMod TypecheckedModule Source # | |
Defined in GHC | |
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.
Instances
TypecheckedMod DesugaredModule Source # | |
Defined in GHC | |
ParsedMod DesugaredModule Source # | |
Defined in GHC |
type TypecheckedSource = LHsBinds GhcTc 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 | |
TypecheckedMod TypecheckedModule Source # | |
Defined in GHC |
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.
CoreModule | |
|
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 #
A ModuleGraph contains all the nodes from the home package (only). There will be a node for each source module, plus a node for each hi-boot module.
The graph is not necessarily stored in topologically-sorted order. Use
topSortModuleGraph
and flattenSCC
to achieve this.
emptyMG :: ModuleGraph #
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph #
Map a function f
over all the ModSummaries
.
To preserve invariants f
can't change the isBoot status.
mkModuleGraph :: [ModSummary] -> ModuleGraph #
mgModSummaries :: ModuleGraph -> [ModSummary] #
mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary #
Look up a ModSummary in the ModuleGraph
data ModSummary #
A single node in a ModuleGraph
. The nodes of the module graph
are one of:
- A regular Haskell source module
- A hi-boot source module
ModSummary | |
|
Instances
Outputable ModSummary | |
Defined in HscTypes ppr :: ModSummary -> SDoc # pprPrec :: Rational -> ModSummary -> SDoc # |
ms_mod_name :: ModSummary -> ModuleName #
data ModLocation #
Module Location
Where a module lives on the file system: the actual locations of the .hs, .hi and .o files, if we have them
ModLocation | |
|
Instances
Show ModLocation | |
Defined in Module showsPrec :: Int -> ModLocation -> ShowS # show :: ModLocation -> String # showList :: [ModLocation] -> ShowS # | |
Outputable ModLocation | |
Defined in Module 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 #
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 #
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
.
ModIface | |
|
data SafeHaskellMode #
The various Safe Haskell modes
Instances
Eq SafeHaskellMode | |
Defined in DynFlags (==) :: SafeHaskellMode -> SafeHaskellMode -> Bool # (/=) :: SafeHaskellMode -> SafeHaskellMode -> Bool # | |
Show SafeHaskellMode | |
Defined in DynFlags showsPrec :: Int -> SafeHaskellMode -> ShowS # show :: SafeHaskellMode -> String # showList :: [SafeHaskellMode] -> ShowS # | |
Outputable SafeHaskellMode | |
Defined in DynFlags ppr :: SafeHaskellMode -> SDoc # pprPrec :: Rational -> SafeHaskellMode -> SDoc # |
Querying the environment
Printing
data PrintUnqualified #
When printing code that contains original names, we need to map the
original names back to something the user understands. This is the
purpose of the triple of functions that gets passed around
when rendering SDoc
.
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 :: 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 InstalledUnitId) 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.
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 Trac #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.
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 InteractiveEval ppr :: GetDocsFailure -> SDoc # pprPrec :: Rational -> GetDocsFailure -> SDoc # |
Other
hasImport :: DynFlags -> String -> Bool Source #
Returns True
if passed string has an import declaration.
isImport :: DynFlags -> String -> Bool Source #
Returns True
if passed string is an import declaration.
isDecl :: DynFlags -> 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 #
All the information about the breakpoints for a module
ModBreaks | |
|
type BreakIndex = Int #
Breakpoint index
Abstract syntax elements
Packages
A unit identifier identifies a (possibly partially) instantiated
library. It is primarily used as part of Module
, which in turn
is used in Name
, which is used to give names to entities when
typechecking.
There are two possible forms for a UnitId
. It can be a
DefiniteUnitId
, in which case we just have a string that uniquely
identifies some fully compiled, installed library we have on disk.
However, when we are typechecking a library with missing holes,
we may need to instantiate a library on the fly (in which case
we don't have any on-disk representation.) In that case, you
have an IndefiniteUnitId
, which explicitly records the
instantiation, so that we can substitute over it.
Instances
Modules
A Module is a pair of a UnitId
and a ModuleName
.
Module variables (i.e. H
) which can be instantiated to a
specific module at some later point in time are represented
with moduleUnitId
set to holeUnitId
(this allows us to
avoid having to make moduleUnitId
a partial operation.)
Instances
mkModule :: UnitId -> ModuleName -> Module #
moduleName :: Module -> ModuleName #
moduleUnitId :: Module -> UnitId #
data ModuleName #
A ModuleName is essentially a simple string, e.g. Data.List
.
Instances
mkModuleName :: String -> ModuleName #
moduleNameString :: ModuleName -> String #
Names
A unique, unambiguous name for something, containing information about where that thing originated.
Instances
Eq Name | |
Data Name | |
Defined in 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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
Ord Name | Caution: This instance is implemented via See |
NFData Name | |
NamedThing Name | |
HasOccName Name | |
Binary Name | Assumes that the |
Uniquable Name | |
HasSrcSpan Name | |
Defined in Name composeSrcSpan :: Located (SrcSpanLess Name) -> Name # decomposeSrcSpan :: Name -> Located (SrcSpanLess Name) # | |
Outputable Name | |
OutputableBndr Name | |
Defined in Name pprBndr :: BindingSite -> Name -> SDoc # pprPrefixOcc :: Name -> SDoc # pprInfixOcc :: Name -> SDoc # bndrIsJoin_maybe :: Name -> Maybe Int # | |
type SrcSpanLess Name | |
Defined in 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 #
A class allowing convenient access to the Name
of various datatypes
Instances
NamedThing ClsInst | |
NamedThing FamInst | |
Defined in FamInstEnv | |
NamedThing IfaceDecl | |
NamedThing IfaceClassOp | |
Defined in IfaceSyn getOccName :: IfaceClassOp -> OccName # getName :: IfaceClassOp -> Name # | |
NamedThing IfaceConDecl | |
Defined in IfaceSyn getOccName :: IfaceConDecl -> OccName # getName :: IfaceConDecl -> Name # | |
NamedThing Class | |
NamedThing ConLike | |
NamedThing DataCon | |
NamedThing PatSyn | |
NamedThing Var | |
NamedThing TyThing | |
NamedThing TyCon | |
NamedThing Name | |
NamedThing (CoAxiom br) | |
NamedThing e => NamedThing (Located e) | |
NamedThing tv => NamedThing (VarBndr tv flag) | |
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
,
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
Eq RdrName | |
Data RdrName | |
Defined in RdrName 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 :: (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 | |
Outputable RdrName | |
OutputableBndr RdrName | |
Defined in RdrName pprBndr :: BindingSite -> RdrName -> SDoc # pprPrefixOcc :: RdrName -> SDoc # pprInfixOcc :: RdrName -> SDoc # bndrIsJoin_maybe :: RdrName -> Maybe Int # |
Identifiers
isImplicitId :: Id -> Bool #
isImplicitId
tells whether an Id
s info is implied by other
declarations, so we don't need to put its signature in an interface
file, even if it's mentioned in some other interface unfolding.
isDeadBinder :: Id -> Bool #
isExportedId :: Var -> Bool #
isExportedIdVar
means "don't throw this away"
isGlobalId :: Var -> Bool #
isRecordSelector :: Id -> Bool #
isPrimOpId :: Id -> Bool #
isClassOpId_maybe :: Id -> Maybe Class #
isDataConWorkId :: Id -> Bool #
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
isBottomingId :: Var -> Bool #
Returns true if an application to n args would diverge
isDictonaryId :: Id -> Bool Source #
recordSelectorTyCon :: Id -> RecSelParent #
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
Eq TyCon | |
Data TyCon | |
Defined in 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 :: (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 # | |
NamedThing TyCon | |
Uniquable TyCon | |
Outputable TyCon | |
tyConTyVars :: TyCon -> [TyVar] #
TyVar binders
tyConDataCons :: TyCon -> [DataCon] #
As tyConDataCons_maybe
, but returns the empty list of constructors if no
constructors could be found
tyConArity :: TyCon -> Arity #
Arity
isClassTyCon :: TyCon -> Bool #
Is this TyCon
that for a class instance?
isTypeSynonymTyCon :: TyCon -> Bool #
Is this a TyCon
representing a regular H98 type synonym (type
)?
isTypeFamilyTyCon :: TyCon -> Bool #
Is this a synonym TyCon
that can have may have further instances appear?
isNewTyCon :: TyCon -> Bool #
Is this TyCon
that for a newtype
isPrimTyCon :: TyCon -> Bool #
Does this TyCon
represent something that cannot be defined in Haskell?
isFunTyCon :: TyCon -> Bool #
isFamilyTyCon :: TyCon -> Bool #
Is this a TyCon
, synonym or otherwise, that defines a family?
isOpenFamilyTyCon :: TyCon -> Bool #
Is this a TyCon
, synonym or otherwise, that defines a family with
instances?
isOpenTypeFamilyTyCon :: TyCon -> Bool #
Is this an open type family TyCon?
tyConClass_maybe :: TyCon -> Maybe Class #
If this TyCon
is that for a class instance, return the class it is for.
Otherwise returns Nothing
synTyConRhs_maybe :: TyCon -> Maybe Type #
Extract the information pertaining to the right hand side of a type synonym
(type
) declaration.
synTyConDefn_maybe :: TyCon -> Maybe ([TyVar], Type) #
Extract the TyVar
s bound by a vanilla type synonym
and the corresponding (unsubstituted) right hand side.
Type variables
alphaTyVars :: [TyVar] #
Data constructors
A data constructor
Instances
Eq DataCon | |
Data DataCon | |
Defined in 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 :: (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 # | |
NamedThing DataCon | |
Uniquable DataCon | |
Outputable DataCon | |
OutputableBndr DataCon | |
Defined in DataCon pprBndr :: BindingSite -> DataCon -> SDoc # pprPrefixOcc :: DataCon -> SDoc # pprInfixOcc :: DataCon -> SDoc # bndrIsJoin_maybe :: DataCon -> Maybe Int # |
dataConSig :: DataCon -> ([TyCoVar], ThetaType, [Type], Type) #
The "signature" of the DataCon
returns, in order:
1) The result of dataConUnivAndExTyCoVars
,
2) All the ThetaType
s relating to the DataCon
(coercion, dictionary,
implicit parameter - whatever), including dependent GADT equalities.
Dependent GADT equalities are *also* listed in return value (1), so be
careful!
3) The type arguments to the constructor
4) The original result type of the DataCon
dataConType :: DataCon -> Type Source #
dataConTyCon :: DataCon -> TyCon #
The type constructor that we are building via this data constructor
dataConFieldLabels :: DataCon -> [FieldLabel] #
The labels for the fields of this particular DataCon
dataConIsInfix :: DataCon -> Bool #
Should the DataCon
be presented infix?
isVanillaDataCon :: DataCon -> Bool #
Vanilla DataCon
s are those that are nice boring Haskell 98 constructors
dataConUserType :: DataCon -> Type #
The user-declared type of the data constructor in the nice-to-read form:
T :: forall a b. a -> b -> T [a]
rather than:
T :: forall a c. forall b. (c~[a]) => a -> b -> T c
The type variables are quantified in the order that the user wrote them.
See Note [DataCon user type variable binders]
.
NB: If the constructor is part of a data instance, the result type mentions the family tycon, not the internal one.
dataConSrcBangs :: DataCon -> [HsSrcBang] #
Strictness/unpack annotations, from user; or, for imported
DataCons, from the interface file
The list is in one-to-one correspondence with the arity of the DataCon
data StrictnessMark #
Instances
Outputable StrictnessMark | |
Defined in DataCon ppr :: StrictnessMark -> SDoc # pprPrec :: Rational -> StrictnessMark -> SDoc # |
isMarkedStrict :: StrictnessMark -> Bool #
Classes
Instances
Eq Class | |
Data Class | |
Defined in 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 :: (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 # | |
NamedThing Class | |
Uniquable Class | |
Outputable Class | |
classMethods :: Class -> [Id] #
classSCTheta :: Class -> [PredType] #
pprFundeps :: Outputable a => [FunDep a] -> SDoc #
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 | |
Defined in 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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r # gmapQ :: (forall d. Data d => d -> u) -> ClsInst -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInst -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # | |
NamedThing ClsInst | |
Outputable ClsInst | |
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 FamInstEnv | |
Outputable FamInst | |
Types and Kinds
Instances
Data Type | |
Defined in TyCoRep 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 :: (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) #
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 #
Extract the function result type and panic if that is not possible
pprParendType :: Type -> SDoc #
pprTypeApp :: TyCon -> [Type] -> SDoc #
A type of the form p
of kind Constraint
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 #
pprThetaArrowTy :: ThetaType -> SDoc #
Entities
Syntax
module HsSyn
Fixities
data FixityDirection #
Instances
defaultFixity :: Fixity #
maxPrecedence :: Int #
negateFixity :: Fixity #
data LexicalFixity #
Captures the fixity of declarations as they are parsed. This is not necessarily the same as the fixity declaration, as the normal fixity may be overridden using parens or backticks.
Instances
Eq LexicalFixity | |
Defined in BasicTypes (==) :: LexicalFixity -> LexicalFixity -> Bool # (/=) :: LexicalFixity -> LexicalFixity -> Bool # | |
Data LexicalFixity | |
Defined in BasicTypes 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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r # gmapQ :: (forall d. Data d => d -> u) -> LexicalFixity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # | |
Outputable LexicalFixity | |
Defined in BasicTypes ppr :: LexicalFixity -> SDoc # pprPrec :: Rational -> LexicalFixity -> SDoc # |
Source locations
data RealSrcLoc #
Real Source Location
Represents a single point within a file
Instances
Eq RealSrcLoc | |
Defined in SrcLoc (==) :: RealSrcLoc -> RealSrcLoc -> Bool # (/=) :: RealSrcLoc -> RealSrcLoc -> Bool # | |
Ord RealSrcLoc | |
Defined in 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 SrcLoc showsPrec :: Int -> RealSrcLoc -> ShowS # show :: RealSrcLoc -> String # showList :: [RealSrcLoc] -> ShowS # | |
Outputable RealSrcLoc | |
Defined in SrcLoc ppr :: RealSrcLoc -> SDoc # pprPrec :: Rational -> RealSrcLoc -> SDoc # |
Built-in "bad" RealSrcLoc
values for particular locations
srcLocFile :: RealSrcLoc -> FastString #
Gives the filename of the RealSrcLoc
srcLocLine :: RealSrcLoc -> Int #
Raises an error when used on a "bad" RealSrcLoc
srcLocCol :: RealSrcLoc -> Int #
Raises an error when used on a "bad" RealSrcLoc
Source Span
A SrcSpan
identifies either a specific portion of a text file
or a human-readable description of a location.
Instances
Eq SrcSpan | |
Data SrcSpan | |
Defined in 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 :: (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 # | |
Ord SrcSpan | |
Show SrcSpan | |
NFData SrcSpan | |
Binary SrcSpan | |
ToJson SrcSpan | |
Outputable SrcSpan | |
NamedThing e => NamedThing (Located e) | |
Binary a => Binary (Located a) | |
HasSrcSpan (Located a) | |
Defined in SrcLoc composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) # |
data RealSrcSpan #
A RealSrcSpan
delimits a portion of a text file. It could be represented
by a pair of (line,column) coordinates, but in fact we optimise
slightly by using more compact representations for single-line and
zero-length spans, both of which are quite common.
The end position is defined to be the column after the end of the span. That is, a span of (1,1)-(1,2) is one character long, and a span of (1,1)-(1,1) is zero characters long.
Real Source Span
Instances
srcLocSpan :: SrcLoc -> SrcSpan #
Create a SrcSpan
corresponding to a single point
isGoodSrcSpan :: SrcSpan -> Bool #
Test if a SrcSpan
is "good", i.e. has precise location information
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 #
We attach SrcSpans to lots of things, so let's have a datatype for it.
L l e |
Instances
Functor (GenLocated l) | |
Defined in SrcLoc fmap :: (a -> b) -> GenLocated l a -> GenLocated l b # (<$) :: a -> GenLocated l b -> GenLocated l a # | |
Foldable (GenLocated l) | |
Defined in SrcLoc fold :: Monoid m => GenLocated l m -> m # foldMap :: Monoid m => (a -> m) -> GenLocated l a -> m # foldr :: (a -> b -> b) -> b -> GenLocated l a -> b # foldr' :: (a -> b -> b) -> b -> GenLocated l a -> b # foldl :: (b -> a -> b) -> b -> GenLocated l a -> b # foldl' :: (b -> a -> b) -> b -> GenLocated l a -> b # foldr1 :: (a -> a -> a) -> GenLocated l a -> a # foldl1 :: (a -> a -> a) -> GenLocated l a -> a # toList :: GenLocated l a -> [a] # null :: GenLocated l a -> Bool # length :: GenLocated l a -> Int # elem :: Eq a => a -> GenLocated l a -> Bool # maximum :: Ord a => GenLocated l a -> a # minimum :: Ord a => GenLocated l a -> a # sum :: Num a => GenLocated l a -> a # product :: Num a => GenLocated l a -> a # | |
Traversable (GenLocated l) | |
Defined in SrcLoc 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) | |
Binary a => Binary (Located a) | |
HasSrcSpan (Located a) | |
Defined in SrcLoc composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) # | |
(Eq l, Eq e) => Eq (GenLocated l e) | |
Defined in SrcLoc (==) :: GenLocated l e -> GenLocated l e -> Bool # (/=) :: GenLocated l e -> GenLocated l e -> Bool # | |
(Data l, Data e) => Data (GenLocated l e) | |
Defined in SrcLoc 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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r # gmapQ :: (forall d. Data d => d -> u) -> GenLocated l e -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # | |
(Ord l, Ord e) => Ord (GenLocated l e) | |
Defined in SrcLoc compare :: GenLocated l e -> GenLocated l e -> Ordering # (<) :: GenLocated l e -> GenLocated l e -> Bool # (<=) :: GenLocated l e -> GenLocated l e -> Bool # (>) :: GenLocated l e -> GenLocated l e -> Bool # (>=) :: GenLocated l e -> GenLocated l e -> Bool # max :: GenLocated l e -> GenLocated l e -> GenLocated l e # min :: GenLocated l e -> GenLocated l e -> GenLocated l e # | |
(Outputable l, Outputable e) => Outputable (GenLocated l e) | |
Defined in SrcLoc ppr :: GenLocated l e -> SDoc # pprPrec :: Rational -> GenLocated l e -> SDoc # | |
type SrcSpanLess (GenLocated l e) | |
Defined in SrcLoc |
type Located = GenLocated SrcSpan #
Constructing Located
noLoc :: HasSrcSpan a => SrcSpanLess a -> a #
mkGeneralLocated :: HasSrcSpan e => String -> SrcSpanLess e -> e #
Deconstructing Located
getLoc :: HasSrcSpan a => a -> SrcSpan #
unLoc :: HasSrcSpan a => a -> SrcSpanLess a #
getRealSrcSpan :: RealLocated a -> RealSrcSpan #
unRealSrcSpan :: RealLocated a -> a #
HasSrcSpan
class HasSrcSpan a where #
A typeclass to set/get SrcSpans
composeSrcSpan :: Located (SrcSpanLess a) -> a #
Composes a SrcSpan
decoration with an undecorated syntactic
entity to form its decorated variant
decomposeSrcSpan :: a -> Located (SrcSpanLess a) #
Decomposes a decorated syntactic entity into its SrcSpan
decoration and its undecorated variant
Instances
HasSrcSpan Name | |
Defined in Name composeSrcSpan :: Located (SrcSpanLess Name) -> Name # decomposeSrcSpan :: Name -> Located (SrcSpanLess Name) # | |
HasSrcSpan (LPat (GhcPass p)) | |
Defined in HsPat composeSrcSpan :: Located (SrcSpanLess (LPat (GhcPass p))) -> LPat (GhcPass p) # decomposeSrcSpan :: LPat (GhcPass p) -> Located (SrcSpanLess (LPat (GhcPass p))) # | |
HasSrcSpan (Located a) | |
Defined in SrcLoc composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) # |
type family SrcSpanLess a :: Type #
Determines the type of undecorated syntactic entities
For most syntactic entities E
, where source location spans are
introduced by a wrapper construtor of the same syntactic entity,
we have `SrcSpanLess E = E`.
However, some syntactic entities have a different type compared to
a syntactic entity `e :: E` may have the type `Located E` when
decorated by wrapping it with `L sp e` for a source span sp
.
Instances
type SrcSpanLess Name | |
Defined in Name | |
type SrcSpanLess (LPat (GhcPass p)) | |
type SrcSpanLess (GenLocated l e) | |
Defined in SrcLoc |
dL :: HasSrcSpan a => a -> Located (SrcSpanLess a) #
An abbreviated form of decomposeSrcSpan, mainly to be used in ViewPatterns
cL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a #
An abbreviated form of composeSrcSpan,
mainly to replace the hardcoded L
Combining and comparing Located values
eqLocated :: (HasSrcSpan a, Eq (SrcSpanLess a)) => a -> a -> Bool #
Tests whether the two located things are equal
cmpLocated :: (HasSrcSpan a, Ord (SrcSpanLess a)) => a -> a -> Ordering #
Tests the ordering of the two located things
combineLocs :: (HasSrcSpan a, HasSrcSpan b) => a -> b -> SrcSpan #
addCLoc :: (HasSrcSpan a, HasSrcSpan b, HasSrcSpan c) => a -> b -> SrcSpanLess c -> c #
Combine locations from two Located
things and add them to a third thing
spans :: SrcSpan -> (Int, Int) -> Bool #
Determines whether a span encloses a given line and column index
Determines whether a span is enclosed by another one
Exceptions
data GhcException #
GHC's own exception type error messages all take the form:
location: error
If the location is on the command line, or in GHC itself, then location="ghc". All of the error types below correspond to a location of "ghc", except for ProgramError (where the string is assumed to contain a location already, so we don't print one).
Signal Int | Some other fatal signal (SIGHUP,SIGTERM) |
UsageError String | Prints the short usage msg after the error |
CmdLineError String | A problem with the command line arguments, but don't print usage. |
Panic String | The |
PprPanic String SDoc | |
Sorry String | The user tickled something that's known not to work yet, but we're not counting it as a bug. |
PprSorry String SDoc | |
InstallationError String | An installation problem. |
ProgramError String | An error in the user's code, probably. |
PprProgramError String SDoc |
Instances
Show GhcException | |
Defined in Panic showsPrec :: Int -> GhcException -> ShowS # show :: GhcException -> String # showList :: [GhcException] -> ShowS # | |
Exception GhcException | |
Defined in Panic |
showGhcException :: GhcException -> ShowS #
Append a description of the given exception to this string.
Note that this uses unsafeGlobalDynFlags
, which may have some
uninitialized fields if invoked before initGhcMonad
has been called.
If the error message to be printed includes a pretty-printer document
which forces one of these fields this call may bottom.
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 GhcPs))) |
A pure interface to the module parser.
API Annotations
data AnnKeywordId #
API Annotations exist so that tools can perform source to source conversions of Haskell code. They are used to keep track of the various syntactic keywords that are not captured in the existing AST.
The annotations, together with original source comments are made
available in the
field of pm_annotations
.
Comments are only retained if ParsedModule
is set in
Opt_KeepRawTokenStream
before parsing.DynFlags
The wiki page describing this feature is https://ghc.haskell.org/trac/ghc/wiki/ApiAnnotations
Note: in general the names of these are taken from the corresponding token, unless otherwise noted See note [Api annotations] above for details of the usage
Instances
data AnnotationComment #
AnnDocCommentNext String | something beginning '-- |' |
AnnDocCommentPrev String | something beginning '-- ^' |
AnnDocCommentNamed String | something beginning '-- $' |
AnnDocSection Int String | a section heading |
AnnDocOptions String | doc options (prune, ignore-exports, etc) |
AnnLineComment String | comment starting by "--" |
AnnBlockComment String | comment in {- -} |
Instances
getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan] #
getAndRemoveAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> ([SrcSpan], ApiAnns) #
getAnnotationComments :: ApiAnns -> SrcSpan -> [Located AnnotationComment] #
getAndRemoveAnnotationComments :: ApiAnns -> SrcSpan -> ([Located AnnotationComment], ApiAnns) #
Retrieve the comments allocated to the current SrcSpan
, and
remove them from the annotations
unicodeAnn :: AnnKeywordId -> AnnKeywordId #
Convert a normal annotation into its unicode equivalent one
Miscellaneous
cyclicModuleErr :: [ModSummary] -> SDoc Source #