|
|
|
|
|
|
Synopsis |
|
defaultErrorHandler :: (ExceptionMonad m, MonadIO m) => DynFlags -> m a -> m a | | defaultCleanupHandler :: (ExceptionMonad m, MonadIO m) => DynFlags -> m a -> m a | | data Ghc a | | data GhcT m a | | class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m) => GhcMonad m where | | | runGhc :: Maybe FilePath -> Ghc a -> IO a | | runGhcT :: (ExceptionMonad m, Functor m, MonadIO 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 | | clearWarnings :: WarnLogMonad m => m () | | getWarnings :: WarnLogMonad m => m WarningMessages | | hasWarnings :: WarnLogMonad m => m Bool | | printExceptionAndWarnings :: GhcMonad m => SourceError -> m () | | printWarnings :: GhcMonad m => m () | | handleSourceError :: ExceptionMonad m => (SourceError -> m a) -> m a -> m a | | data DynFlags = DynFlags {} | | | | | | | | dopt :: DynFlag -> DynFlags -> Bool | | | | | | defaultObjectTarget :: HscTarget | | parseDynamicFlags :: Monad m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Located String]) | | getSessionDynFlags :: GhcMonad m => m DynFlags | | setSessionDynFlags :: GhcMonad m => DynFlags -> m [PackageId] | | parseStaticFlags :: [Located String] -> IO ([Located String], [Located String]) | | data Target = Target {} | | | | 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 | | extendGlobalRdrScope :: GhcMonad m => [GlobalRdrElt] -> m () | | setGlobalRdrScope :: GhcMonad m => [GlobalRdrElt] -> m () | | extendGlobalTypeScope :: GhcMonad m => [Id] -> m () | | setGlobalTypeScope :: GhcMonad m => [Id] -> m () | | depanal :: GhcMonad m => [ModuleName] -> Bool -> m ModuleGraph | | load :: GhcMonad m => LoadHowMuch -> m SuccessFlag | | loadWithLogger :: GhcMonad m => WarnErrLogger -> LoadHowMuch -> m SuccessFlag | | | | | | defaultWarnErrLogger :: WarnErrLogger | | type WarnErrLogger = 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 | | data TypecheckedModule | | data DesugaredModule | | type TypecheckedSource = LHsBinds Id | | type ParsedSource = Located (HsModule RdrName) | | type RenamedSource = (HsGroup Name, [LImportDecl Name], Maybe [LIE Name], Maybe (HsDoc Name), HaddockModInfo Name) | | class ParsedMod m => TypecheckedMod m where | | | class ParsedMod m where | | | coreModule :: DesugaredMod m => m -> ModGuts | | compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule | | compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule | | compileCoreToObj :: GhcMonad m => Bool -> CoreModule -> m () | | getModSummary :: GhcMonad m => ModuleName -> m ModSummary | | parseHaddockComment :: String -> Either String (HsDoc RdrName) | | type ModuleGraph = [ModSummary] | | data ModSummary = ModSummary {} | | ms_mod_name :: ModSummary -> ModuleName | | data ModLocation = ModLocation {} | | getModuleGraph :: GhcMonad m => m ModuleGraph | | isLoaded :: GhcMonad m => ModuleName -> m Bool | | topSortModuleGraph :: Bool -> [ModSummary] -> Maybe ModuleName -> [SCC ModSummary] | | data ModuleInfo | | getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo) | | modInfoTyThings :: ModuleInfo -> [TyThing] | | modInfoTopLevelScope :: ModuleInfo -> Maybe [Name] | | modInfoExports :: ModuleInfo -> [Name] | | modInfoInstances :: ModuleInfo -> [Instance] | | modInfoIsExportedName :: ModuleInfo -> Name -> Bool | | modInfoLookupName :: GhcMonad m => ModuleInfo -> Name -> m (Maybe TyThing) | | lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing) | | mkPrintUnqualifiedForModule :: GhcMonad m => ModuleInfo -> m (Maybe PrintUnqualified) | | packageDbModules :: GhcMonad m => Bool -> m [Module] | | type PrintUnqualified = (QueryQualifyName, QueryQualifyModule) | | alwaysQualify :: PrintUnqualified | | getBindings :: GhcMonad m => m [TyThing] | | getPrintUnqual :: GhcMonad m => m PrintUnqualified | | findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module | | setContext :: GhcMonad m => [Module] -> [Module] -> m () | | getContext :: GhcMonad m => m ([Module], [Module]) | | getNamesInScope :: GhcMonad m => m [Name] | | getRdrNamesInScope :: GhcMonad m => m [RdrName] | | getGRE :: GhcMonad m => m GlobalRdrEnv | | moduleIsInterpreted :: GhcMonad m => Module -> m Bool | | getInfo :: GhcMonad m => Name -> m (Maybe (TyThing, Fixity, [Instance])) | | exprType :: GhcMonad m => String -> m Type | | typeKind :: GhcMonad m => String -> m Kind | | parseName :: GhcMonad m => String -> m [Name] | | | | runStmt :: GhcMonad m => String -> SingleStep -> m RunResult | | | | resume :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> m RunResult | | data Resume | | data History | | getHistorySpan :: GhcMonad m => History -> m SrcSpan | | getHistoryModule :: History -> Module | | getResumeContext :: GhcMonad m => m [Resume] | | abandon :: GhcMonad m => m Bool | | abandonAll :: GhcMonad m => m Bool | | back :: GhcMonad m => m ([Name], Int, SrcSpan) | | forward :: GhcMonad m => m ([Name], Int, SrcSpan) | | showModule :: GhcMonad m => ModSummary -> m String | | isModuleInterpreted :: GhcMonad m => ModSummary -> m Bool | | compileExpr :: GhcMonad m => String -> m HValue | | data HValue | | dynCompileExpr :: GhcMonad m => String -> m Dynamic | | lookupName :: GhcMonad m => Name -> m (Maybe TyThing) | | 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 | | data BreakArray | | setBreakOn :: BreakArray -> Int -> IO Bool | | setBreakOff :: BreakArray -> Int -> IO Bool | | getBreak :: BreakArray -> Int -> IO (Maybe Word) | | data PackageId | | data Module | | mkModule :: PackageId -> ModuleName -> Module | | pprModule :: Module -> SDoc | | moduleName :: Module -> ModuleName | | modulePackageId :: Module -> PackageId | | data ModuleName | | mkModuleName :: String -> ModuleName | | moduleNameString :: ModuleName -> String | | data Name | | isExternalName :: Name -> Bool | | nameModule :: Name -> Module | | pprParenSymName :: NamedThing a => a -> SDoc | | nameSrcSpan :: Name -> SrcSpan | | class NamedThing a where | | | | | type Id = Var | | idType :: Id -> Kind | | isImplicitId :: Id -> Bool | | isDeadBinder :: Id -> Bool | | isExportedId :: Id -> Bool | | isLocalId :: Id -> Bool | | isGlobalId :: Id -> Bool | | isRecordSelector :: Id -> Bool | | isPrimOpId :: Id -> Bool | | isFCallId :: Id -> Bool | | isClassOpId_maybe :: Id -> Maybe Class | | isDataConWorkId :: Id -> Bool | | idDataCon :: Id -> DataCon | | isBottomingId :: Id -> Bool | | isDictonaryId :: Id -> Bool | | recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel) | | data TyCon | | tyConTyVars :: TyCon -> [TyVar] | | tyConDataCons :: TyCon -> [DataCon] | | tyConArity :: TyCon -> Arity | | isClassTyCon :: TyCon -> Bool | | isSynTyCon :: TyCon -> Bool | | isNewTyCon :: TyCon -> Bool | | isPrimTyCon :: TyCon -> Bool | | isFunTyCon :: TyCon -> Bool | | isOpenTyCon :: TyCon -> Bool | | synTyConDefn :: TyCon -> ([TyVar], Type) | | synTyConType :: TyCon -> Type | | synTyConResKind :: TyCon -> Kind | | type TyVar = Var | | alphaTyVars :: [TyVar] | | data DataCon | | dataConSig :: DataCon -> ([TyVar], ThetaType, [Type], Type) | | dataConType :: DataCon -> Type | | dataConTyCon :: DataCon -> TyCon | | dataConFieldLabels :: DataCon -> [FieldLabel] | | dataConIsInfix :: DataCon -> Bool | | isVanillaDataCon :: DataCon -> Bool | | dataConStrictMarks :: DataCon -> [StrictnessMark] | | | | isMarkedStrict :: StrictnessMark -> Bool | | data Class | | classMethods :: Class -> [Id] | | classSCTheta :: Class -> [PredType] | | classTvsFds :: Class -> ([TyVar], [FunDep TyVar]) | | pprFundeps :: Outputable a => [FunDep a] -> SDoc | | data Instance | | instanceDFunId :: Instance -> DFunId | | pprInstance :: Instance -> SDoc | | pprInstanceHdr :: Instance -> SDoc | | data Type | | splitForAllTys :: Type -> ([TyVar], Type) | | funResultTy :: Type -> Type | | pprParendType :: Type -> SDoc | | pprTypeApp :: NamedThing a => a -> [Type] -> SDoc | | type Kind = Type | | data PredType | | type ThetaType = [PredType] | | pprThetaArrow :: ThetaType -> SDoc | | | | module HsSyn | | | | defaultFixity :: Fixity | | maxPrecedence :: Int | | negateFixity :: Fixity | | compareFixity :: Fixity -> Fixity -> (Bool, Bool) | | data SrcLoc | | pprDefnLoc :: SrcSpan -> SDoc | | mkSrcLoc :: FastString -> Int -> Int -> SrcLoc | | isGoodSrcLoc :: SrcLoc -> Bool | | noSrcLoc :: SrcLoc | | srcLocFile :: SrcLoc -> FastString | | srcLocLine :: SrcLoc -> Int | | srcLocCol :: SrcLoc -> Int | | data SrcSpan | | mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan | | srcLocSpan :: SrcLoc -> SrcSpan | | isGoodSrcSpan :: SrcSpan -> Bool | | noSrcSpan :: SrcSpan | | srcSpanStart :: SrcSpan -> SrcLoc | | srcSpanEnd :: SrcSpan -> SrcLoc | | srcSpanFile :: SrcSpan -> FastString | | srcSpanStartLine :: SrcSpan -> Int | | srcSpanEndLine :: SrcSpan -> Int | | srcSpanStartCol :: SrcSpan -> Int | | srcSpanEndCol :: SrcSpan -> Int | | data Located e = L SrcSpan e | | noLoc :: e -> Located e | | mkGeneralLocated :: String -> e -> Located e | | getLoc :: Located e -> SrcSpan | | unLoc :: Located e -> e | | eqLocated :: Eq a => Located a -> Located a -> Bool | | cmpLocated :: Ord a => Located a -> Located a -> Ordering | | combineLocs :: Located a -> Located b -> SrcSpan | | addCLoc :: Located a -> Located b -> c -> Located c | | leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering | | leftmost_largest :: SrcSpan -> SrcSpan -> Ordering | | rightmost :: SrcSpan -> SrcSpan -> Ordering | | spans :: SrcSpan -> (Int, Int) -> Bool | | isSubspanOf :: SrcSpan -> SrcSpan -> Bool | | | | showGhcException :: GhcException -> String -> String | | data Token | | getTokenStream :: GhcMonad m => Module -> m [Located Token] | | getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)] | | showRichTokenStream :: [(Located Token, String)] -> String | | addSourceToTokens :: SrcLoc -> StringBuffer -> [Located Token] -> [(Located Token, String)] | | cyclicModuleErr :: [ModSummary] -> SDoc |
|
|
|
Initialisation
|
|
defaultErrorHandler :: (ExceptionMonad m, MonadIO m) => DynFlags -> m a -> m a |
Install some default exception handlers and run the inner computation.
Unless you want to handle exceptions yourself, you should wrap this around
the top level of your program. The default handlers output the error
message(s) to stderr and exit cleanly.
|
|
defaultCleanupHandler :: (ExceptionMonad m, MonadIO m) => DynFlags -> m a -> m a |
Install a default cleanup handler to remove temporary files deposited by
a GHC run. This is seperate from defaultErrorHandler, because you might
want to override the error handling, but still get the ordinary cleanup
behaviour.
|
|
GHC Monad
|
|
data Ghc a |
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 | |
|
|
data GhcT m 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 | |
|
|
class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m) => GhcMonad m 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 GHC.initGhcMonad
before any call to the GHC API functions can occur.
| | Methods | | | Instances | |
|
|
runGhc |
:: | | => Maybe FilePath | See argument to initGhcMonad.
| -> 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.
|
|
|
runGhcT |
|
|
initGhcMonad :: GhcMonad m => Maybe FilePath -> m () |
Initialise a GHC session.
If you implement a custom GhcMonad you must call this function in the
monad run function. It will initialise the session variable and clear all
warnings.
The first argument should point to the directory where GHC's library files
reside. More precisely, this should be the output of ghc --print-libdir
of the version of GHC the module using this API is compiled with. For
portability, you should use the ghc-paths package, available at
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ghc-paths.
|
|
gcatch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m a |
Generalised version of catch, allowing an arbitrary
exception handling monad instead of just IO.
|
|
gbracket :: ExceptionMonad m => m a -> (a -> m b) -> (a -> m c) -> m c |
Generalised version of bracket, allowing an arbitrary
exception handling monad instead of just IO.
|
|
gfinally :: ExceptionMonad m => m a -> m b -> m a |
Generalised version of finally, allowing an arbitrary
exception handling monad instead of just IO.
|
|
clearWarnings :: WarnLogMonad m => m () |
Clear the log of Warnings.
|
|
getWarnings :: WarnLogMonad m => m WarningMessages |
|
hasWarnings :: WarnLogMonad m => m Bool |
Returns true if there were any warnings.
|
|
printExceptionAndWarnings :: GhcMonad m => SourceError -> m () |
Print the error message and all warnings. Useful inside exception
handlers. Clears warnings after printing.
|
|
printWarnings :: GhcMonad m => m () |
Print all accumulated warnings using log_action.
|
|
handleSourceError |
|
|
Flags and settings
|
|
data DynFlags |
Contains not only a collection of DynFlags but also a plethora of
information relating to the compilation of a single file or GHC session
| Constructors | |
|
|
data DynFlag |
Enumerates the simple on-or-off dynamic flags
| Constructors | Opt_D_dump_cmm | | Opt_D_dump_cmmz | | Opt_D_dump_cmmz_pretty | | Opt_D_dump_cps_cmm | | Opt_D_dump_cvt_cmm | | Opt_D_dump_asm | | Opt_D_dump_asm_native | | Opt_D_dump_asm_liveness | | Opt_D_dump_asm_coalesce | | Opt_D_dump_asm_regalloc | | Opt_D_dump_asm_regalloc_stages | | Opt_D_dump_asm_conflicts | | Opt_D_dump_asm_stats | | Opt_D_dump_cpranal | | Opt_D_dump_deriv | | Opt_D_dump_ds | | Opt_D_dump_flatC | | Opt_D_dump_foreign | | Opt_D_dump_inlinings | | Opt_D_dump_rule_firings | | Opt_D_dump_occur_anal | | Opt_D_dump_parsed | | Opt_D_dump_rn | | Opt_D_dump_simpl | | Opt_D_dump_simpl_iterations | | Opt_D_dump_simpl_phases | | Opt_D_dump_spec | | Opt_D_dump_prep | | Opt_D_dump_stg | | Opt_D_dump_stranal | | Opt_D_dump_tc | | Opt_D_dump_types | | Opt_D_dump_rules | | Opt_D_dump_cse | | Opt_D_dump_worker_wrapper | | Opt_D_dump_rn_trace | | Opt_D_dump_rn_stats | | Opt_D_dump_opt_cmm | | Opt_D_dump_simpl_stats | | Opt_D_dump_tc_trace | | Opt_D_dump_if_trace | | Opt_D_dump_splices | | Opt_D_dump_BCOs | | Opt_D_dump_vect | | Opt_D_dump_hpc | | Opt_D_dump_rtti | | Opt_D_source_stats | | Opt_D_verbose_core2core | | Opt_D_verbose_stg2stg | | Opt_D_dump_hi | | Opt_D_dump_hi_diffs | | Opt_D_dump_minimal_imports | | Opt_D_dump_mod_cycles | | Opt_D_dump_view_pattern_commoning | | Opt_D_faststring_stats | | Opt_DumpToFile | Append dump output to files instead of stdout.
| Opt_D_no_debug_output | | Opt_DoCoreLinting | | Opt_DoStgLinting | | Opt_DoCmmLinting | | Opt_DoAsmLinting | | Opt_WarnIsError | | Opt_WarnDuplicateExports | | Opt_WarnHiShadows | | Opt_WarnImplicitPrelude | | Opt_WarnIncompletePatterns | | Opt_WarnIncompletePatternsRecUpd | | Opt_WarnMissingFields | | Opt_WarnMissingMethods | | Opt_WarnMissingSigs | | Opt_WarnNameShadowing | | Opt_WarnOverlappingPatterns | | Opt_WarnSimplePatterns | | Opt_WarnTypeDefaults | | Opt_WarnMonomorphism | | Opt_WarnUnusedBinds | | Opt_WarnUnusedImports | | Opt_WarnUnusedMatches | | Opt_WarnWarningsDeprecations | | Opt_WarnDeprecatedFlags | | Opt_WarnDodgyImports | | Opt_WarnOrphans | | Opt_WarnTabs | | Opt_WarnUnrecognisedPragmas | | Opt_WarnDodgyForeignImports | | Opt_OverlappingInstances | | Opt_UndecidableInstances | | Opt_IncoherentInstances | | Opt_MonomorphismRestriction | | Opt_MonoPatBinds | | Opt_ExtendedDefaultRules | | Opt_ForeignFunctionInterface | | Opt_UnliftedFFITypes | | Opt_PArr | | Opt_Arrows | | Opt_TemplateHaskell | | Opt_QuasiQuotes | | Opt_ImplicitParams | | Opt_Generics | | Opt_ImplicitPrelude | | Opt_ScopedTypeVariables | | Opt_UnboxedTuples | | Opt_BangPatterns | | Opt_TypeFamilies | | Opt_OverloadedStrings | | Opt_DisambiguateRecordFields | | Opt_RecordWildCards | | Opt_RecordPuns | | Opt_ViewPatterns | | Opt_GADTs | | Opt_RelaxedPolyRec | | Opt_StandaloneDeriving | | Opt_DeriveDataTypeable | | Opt_TypeSynonymInstances | | Opt_FlexibleContexts | | Opt_FlexibleInstances | | Opt_ConstrainedClassMethods | | Opt_MultiParamTypeClasses | | Opt_FunctionalDependencies | | Opt_UnicodeSyntax | | Opt_PolymorphicComponents | | Opt_ExistentialQuantification | | Opt_MagicHash | | Opt_EmptyDataDecls | | Opt_KindSignatures | | Opt_ParallelListComp | | Opt_TransformListComp | | Opt_GeneralizedNewtypeDeriving | | Opt_RecursiveDo | | Opt_PostfixOperators | | Opt_PatternGuards | | Opt_LiberalTypeSynonyms | | Opt_Rank2Types | | Opt_RankNTypes | | Opt_ImpredicativeTypes | | Opt_TypeOperators | | Opt_PackageImports | | Opt_NewQualifiedOperators | | Opt_PrintExplicitForalls | | Opt_Strictness | | Opt_FullLaziness | | Opt_StaticArgumentTransformation | | Opt_CSE | | Opt_LiberateCase | | Opt_SpecConstr | | Opt_IgnoreInterfacePragmas | | Opt_OmitInterfacePragmas | | Opt_DoLambdaEtaExpansion | | Opt_IgnoreAsserts | | Opt_DoEtaReduction | | Opt_CaseMerge | | Opt_UnboxStrictFields | | Opt_MethodSharing | | Opt_DictsCheap | | Opt_InlineIfEnoughArgs | | Opt_EnableRewriteRules | | Opt_Vectorise | | Opt_RegsGraph | | Opt_RegsIterative | | Opt_Cpp | | Opt_Pp | | Opt_ForceRecomp | | Opt_DryRun | | Opt_DoAsmMangling | | Opt_ExcessPrecision | | Opt_ReadUserPackageConf | | Opt_NoHsMain | | Opt_SplitObjs | | Opt_StgStats | | Opt_HideAllPackages | | Opt_PrintBindResult | | Opt_Haddock | | Opt_HaddockOptions | | Opt_Hpc_No_Auto | | Opt_BreakOnException | | Opt_BreakOnError | | Opt_PrintEvldWithShow | | Opt_PrintBindContents | | Opt_GenManifest | | Opt_EmbedManifest | | Opt_RunCPSZ | | Opt_ConvertToZipCfgAndBack | | Opt_AutoLinkPackages | | Opt_ImplicitImportQualified | | Opt_KeepHiDiffs | | Opt_KeepHcFiles | | Opt_KeepSFiles | | Opt_KeepRawSFiles | | Opt_KeepTmpFiles | | Opt_KeepRawTokenStream | |
| Instances | |
|
|
data Severity |
Constructors | SevInfo | | SevWarning | | SevError | | SevFatal | |
|
|
|
data HscTarget |
The target code type of the compilation (if any).
HscNothing can be used to avoid generating any output, however, note
that:
- This will not run the desugaring step, thus no warnings generated in
this step will be output. In particular, this includes warnings
related to pattern matching.
- At the moment switching from HscNothing to HscInterpreted without
unloading first is not safe. To unload use
GHC.setTargets [] >> GHC.load LoadAllTargets.
| Constructors | HscC | | HscAsm | | HscJava | | HscInterpreted | | HscNothing | |
| Instances | |
|
|
dopt :: DynFlag -> DynFlags -> Bool |
Test whether a DynFlag is set
|
|
data GhcMode |
The GhcMode tells us whether we're doing multi-module
compilation (controlled via the GHC API) or one-shot
(single-module) compilation. This makes a difference primarily to
the Finder: in one-shot mode we look for interface files for
imported modules, but in multi-module mode we look for source files
in order to check whether they need to be recompiled.
| Constructors | CompManager | --make, GHCi, etc.
| OneShot | ghc -c Foo.hs | MkDepend | ghc -M, see Finder for why we need this
|
| Instances | |
|
|
data GhcLink |
What to do in the link step, if there is one.
| Constructors | NoLink | Don't link at all
| LinkBinary | Link object code into a binary
| LinkInMemory | Use the in-memory dynamic linker
| LinkDynLib | Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
|
| Instances | |
|
|
defaultObjectTarget :: HscTarget |
The HscTarget value corresponding to the default way to create
object files on the current platform.
|
|
parseDynamicFlags |
|
|
getSessionDynFlags :: GhcMonad m => m DynFlags |
Grabs the DynFlags from the Session
|
|
setSessionDynFlags :: GhcMonad m => DynFlags -> m [PackageId] |
Updates the 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.
|
|
parseStaticFlags :: [Located String] -> IO ([Located String], [Located String]) |
Parses GHC's static flags from a list of command line arguments.
These flags are static in the sense that they can be set only once and they
are global, meaning that they affect every instance of GHC running;
multiple GHC threads will use the same flags.
This function must be called before any session is started, i.e., before
the first call to GHC.withGhc.
Static flags are more of a hack and are static for more or less historical
reasons. In the long run, most static flags should eventually become
dynamic flags.
XXX: can we add an auto-generated list of static flags here?
|
|
Targets
|
|
data Target |
A compilation target.
A target may be supplied with the actual text of the
module. If so, use this instead of the file contents (this
is for use in an IDE where the file hasn't been saved by
the user yet).
| Constructors | | Instances | |
|
|
data TargetId |
Constructors | TargetModule ModuleName | A module name: search for the file
| TargetFile FilePath (Maybe Phase) | A filename: preprocess & parse it to find the module name.
If specified, the Phase indicates how to compile this file
(which phase to start from). Nothing indicates the starting phase
should be determined from the suffix of the filename.
|
| Instances | |
|
|
data Phase |
Instances | |
|
|
setTargets :: GhcMonad m => [Target] -> m () |
Sets the targets for this session. Each target may be a module name
or a filename. The targets correspond to the set of root modules for
the program/library. Unloading the current program is achieved by
setting the current set of targets to be empty, followed by load.
|
|
getTargets :: GhcMonad m => m [Target] |
Returns the current set of targets
|
|
addTarget :: GhcMonad m => Target -> m () |
Add another target.
|
|
removeTarget :: GhcMonad m => TargetId -> m () |
Remove a target
|
|
guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target |
Attempts to guess what Target a string refers to. This function
implements the --make/GHCi command-line syntax for filenames:
- if the string looks like a Haskell source filename, then interpret it
as such
- if adding a .hs or .lhs suffix yields the name of an existing file,
then use that
- otherwise interpret the string as a module name
|
|
Extending the program scope
|
|
extendGlobalRdrScope :: GhcMonad m => [GlobalRdrElt] -> m () |
|
setGlobalRdrScope :: GhcMonad m => [GlobalRdrElt] -> m () |
|
extendGlobalTypeScope :: GhcMonad m => [Id] -> m () |
|
setGlobalTypeScope :: GhcMonad m => [Id] -> m () |
|
Loading/compiling the program
|
|
depanal |
:: 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.
|
|
|
load :: GhcMonad m => LoadHowMuch -> m SuccessFlag |
Try to load the program. Calls loadWithLogger with the default
compiler that just immediately logs all warnings and errors.
This function may throw a SourceError if errors are encountered before
the actual compilation starts (e.g., during dependency analysis).
|
|
loadWithLogger :: GhcMonad m => WarnErrLogger -> LoadHowMuch -> m SuccessFlag |
Try to load the program. If a Module is supplied, then just
attempt to load up to this target. If no Module is supplied,
then try to load all targets.
The first argument is a function that is called after compiling each
module to print wanrings and errors.
While compiling a module, all SourceErrors are caught and passed to the
logger, however, this function may still throw a SourceError if
dependency analysis failed (e.g., due to a parse error).
|
|
data LoadHowMuch |
|
|
data SuccessFlag |
Constructors | | Instances | |
|
|
defaultWarnErrLogger :: WarnErrLogger |
|
type WarnErrLogger = GhcMonad m => Maybe SourceError -> m () |
A function called to log warnings and errors.
|
|
workingDirectoryChanged :: GhcMonad m => m () |
Inform GHC that the working directory has changed. GHC will flush
its cache of module locations, since it may no longer be valid.
Note: 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 |
Parse a module.
Throws a SourceError on parse error.
|
|
typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule |
Typecheck and rename a parsed module.
Throws a SourceError if either fails.
|
|
desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule |
Desugar a typechecked module.
|
|
loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod |
Load a module. Input doesn't need to be desugared.
XXX: Describe usage.
|
|
data ParsedModule |
The result of successful parsing.
| Instances | |
|
|
data TypecheckedModule |
The result of successful typechecking. It also contains the parser
result.
| Instances | |
|
|
data DesugaredModule |
The result of successful desugaring (i.e., translation to core). Also
contains all the information of a typechecked module.
| Instances | |
|
|
type TypecheckedSource = LHsBinds Id |
|
type ParsedSource = Located (HsModule RdrName) |
|
type RenamedSource = (HsGroup Name, [LImportDecl Name], Maybe [LIE Name], Maybe (HsDoc Name), HaddockModInfo Name) |
|
class ParsedMod m => TypecheckedMod m where |
| Methods | | | Instances | |
|
|
class ParsedMod m where |
| Methods | | | Instances | |
|
|
coreModule :: DesugaredMod m => m -> ModGuts |
|
compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule |
This is the way to get access to the Core bindings corresponding
to a module. compileToCore parses, typechecks, and
desugars the module, then returns the resulting Core module (consisting of
the module name, type declarations, and function declarations) if
successful.
|
|
compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule |
Like compileToCoreModule, but invokes the simplifier, so
as to return simplified and tidied Core.
|
|
compileCoreToObj :: GhcMonad m => Bool -> CoreModule -> m () |
Takes a CoreModule and compiles the bindings therein
to object code. The first argument is a bool flag indicating
whether to run the simplifier.
The resulting .o, .hi, and executable files, if any, are stored in the
current directory, and named according to the module name.
Returns True iff compilation succeeded.
This has only so far been tested with a single self-contained module.
|
|
getModSummary :: GhcMonad m => ModuleName -> m ModSummary |
Return the ModSummary of a module with the given name.
The module must be part of the module graph (see hsc_mod_graph and
ModuleGraph). If this is not the case, this function will throw a
GhcApiError.
This function ignores boot modules and requires that there is only one
non-boot module with the given name.
|
|
Parsing Haddock comments
|
|
parseHaddockComment :: String -> Either String (HsDoc RdrName) |
|
Inspecting the module structure of the program
|
|
type ModuleGraph = [ModSummary] |
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.
|
|
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
- An external-core source module
| Constructors | ModSummary | | ms_mod :: Module | Identity of the module
| ms_hsc_src :: HscSource | The module source either plain Haskell, hs-boot or external core
| ms_location :: ModLocation | Location of the various files belonging to the module
| ms_hs_date :: ClockTime | Timestamp of source file
| ms_obj_date :: Maybe ClockTime | Timestamp of object, if we have one
| ms_srcimps :: [Located ModuleName] | Source imports of the module
| ms_imps :: [Located ModuleName] | Non-source imports of the module
| ms_hspp_file :: FilePath | Filename of preprocessed source file
| ms_hspp_opts :: DynFlags | Cached flags from OPTIONS, INCLUDE
and LANGUAGE pragmas in the modules source code
| ms_hspp_buf :: Maybe StringBuffer | The actual preprocessed source, if we have it
|
|
| Instances | |
|
|
ms_mod_name :: ModSummary -> ModuleName |
|
data ModLocation |
Where a module lives on the file system: the actual locations
of the .hs, .hi and .o files, if we have them
| Constructors | | Instances | |
|
|
getModuleGraph :: GhcMonad m => m ModuleGraph |
Get the module dependency graph.
|
|
isLoaded :: GhcMonad m => ModuleName -> m Bool |
Return True == module is loaded.
|
|
topSortModuleGraph :: Bool -> [ModSummary] -> Maybe ModuleName -> [SCC ModSummary] |
|
Inspecting modules
|
|
data ModuleInfo |
Container for information about a Module.
|
|
|
getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo) |
Request information about a loaded Module
|
|
modInfoTyThings :: ModuleInfo -> [TyThing] |
The list of top-level entities defined in a module
|
|
modInfoTopLevelScope :: ModuleInfo -> Maybe [Name] |
|
modInfoExports :: ModuleInfo -> [Name] |
|
modInfoInstances :: ModuleInfo -> [Instance] |
Returns the instances defined by the specified module.
Warning: currently unimplemented for package modules.
|
|
modInfoIsExportedName :: ModuleInfo -> Name -> Bool |
|
modInfoLookupName :: GhcMonad m => ModuleInfo -> Name -> m (Maybe TyThing) |
|
lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing) |
Looks up a global name: that is, any top-level name in any
visible module. Unlike lookupName, lookupGlobalName does not use
the interactive context, and therefore does not require a preceding
setContext.
|
|
mkPrintUnqualifiedForModule :: GhcMonad m => ModuleInfo -> m (Maybe PrintUnqualified) |
|
Querying the environment
|
|
packageDbModules |
:: GhcMonad m | | => Bool | Only consider exposed packages.
| -> m [Module] | | Return all external modules available in the package database.
Modules from the current session (i.e., from the HomePackageTable) are
not included.
|
|
|
Printing
|
|
type PrintUnqualified = (QueryQualifyName, QueryQualifyModule) |
|
alwaysQualify :: PrintUnqualified |
|
Interactive evaluation
|
|
getBindings :: GhcMonad m => m [TyThing] |
Return the bindings for the current interactive session.
|
|
getPrintUnqual :: GhcMonad m => m PrintUnqualified |
|
findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module |
Takes a ModuleName and possibly a PackageId, and consults the
filesystem and package database to find the corresponding Module,
using the algorithm that is used for an import declaration.
|
|
setContext |
:: GhcMonad m | | => [Module] | entire top level scope of these modules
| -> [Module] | exports only of these modules
| -> m () | | Set the interactive evaluation context.
Setting the context doesn't throw away any bindings; the bindings
we've built up in the InteractiveContext simply move to the new
module. They always shadow anything in scope in the current context.
|
|
|
getContext :: GhcMonad m => m ([Module], [Module]) |
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.
|
|
getNamesInScope :: GhcMonad m => m [Name] |
Returns all names in scope in the current interactive context
|
|
getRdrNamesInScope :: GhcMonad m => m [RdrName] |
|
getGRE :: GhcMonad m => m GlobalRdrEnv |
get the GlobalRdrEnv for a session
|
|
moduleIsInterpreted :: GhcMonad m => Module -> m Bool |
Returns True if the specified module is interpreted, and hence has
its full top-level scope available.
|
|
getInfo :: GhcMonad m => Name -> m (Maybe (TyThing, Fixity, [Instance])) |
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)
|
|
exprType :: GhcMonad m => String -> m Type |
Get the type of an expression
|
|
typeKind :: GhcMonad m => String -> m Kind |
Get the kind of a type
|
|
parseName :: GhcMonad m => String -> m [Name] |
Parses a string as an identifier, and returns the list of Names that
the identifier can refer to in the current interactive context.
|
|
data RunResult |
|
|
runStmt :: GhcMonad m => String -> SingleStep -> m RunResult |
Run a statement in the current interactive context. Statement
may bind multple values.
|
|
data SingleStep |
Constructors | RunToCompletion | | SingleStep | | RunAndLogSteps | |
|
|
|
resume :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> m RunResult |
|
data Resume |
|
data History |
|
getHistorySpan :: GhcMonad m => History -> m SrcSpan |
|
getHistoryModule :: History -> Module |
|
getResumeContext :: GhcMonad m => m [Resume] |
|
abandon :: GhcMonad m => m Bool |
|
abandonAll :: GhcMonad m => m Bool |
|
back :: GhcMonad m => m ([Name], Int, SrcSpan) |
|
forward :: GhcMonad m => m ([Name], Int, SrcSpan) |
|
showModule :: GhcMonad m => ModSummary -> m String |
|
isModuleInterpreted :: GhcMonad m => ModSummary -> m Bool |
|
compileExpr :: GhcMonad m => String -> m HValue |
|
data HValue |
|
dynCompileExpr :: GhcMonad m => String -> m Dynamic |
|
lookupName :: GhcMonad m => Name -> m (Maybe TyThing) |
Returns the TyThing for a Name. The Name may refer to any
entity known to GHC, including Names defined using runStmt.
|
|
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 |
All the information about the breakpoints for a given module
| Constructors | ModBreaks | | modBreaks_flags :: BreakArray | The array of flags, one per breakpoint,
indicating which breakpoints are enabled.
| modBreaks_locs :: !(Array BreakIndex SrcSpan) | An array giving the source span of each breakpoint.
| modBreaks_vars :: !(Array BreakIndex [OccName]) | An array giving the names of the free variables at each breakpoint.
|
|
|
|
|
type BreakIndex = Int |
Breakpoint index
|
|
data BreakInfo |
Instances | |
|
|
data BreakArray |
|
setBreakOn :: BreakArray -> Int -> IO Bool |
|
setBreakOff :: BreakArray -> Int -> IO Bool |
|
getBreak :: BreakArray -> Int -> IO (Maybe Word) |
|
Abstract syntax elements
|
|
Packages
|
|
data PackageId |
Essentially just a string identifying a package, including the version: e.g. parsec-1.0
| Instances | |
|
|
Modules
|
|
data Module |
|
|
mkModule :: PackageId -> ModuleName -> Module |
|
pprModule :: Module -> SDoc |
|
moduleName :: Module -> ModuleName |
|
modulePackageId :: Module -> PackageId |
|
data ModuleName |
A ModuleName is essentially a simple string, e.g. Data.List.
| Instances | |
|
|
mkModuleName :: String -> ModuleName |
|
moduleNameString :: ModuleName -> String |
|
Names
|
|
data Name |
A unique, unambigious name for something, containing information about where
that thing originated.
| Instances | |
|
|
isExternalName :: Name -> Bool |
|
nameModule :: Name -> Module |
|
pprParenSymName :: NamedThing a => a -> SDoc |
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
| | Methods | | | Instances | |
|
|
data RdrName |
Do not use the data constructors of RdrName directly: prefer the family
of functions that creates them, such as mkRdrUnqual
| Constructors | Unqual OccName | Used for ordinary, unqualified occurrences, e.g. x, y or Foo.
Create such a RdrName with mkRdrUnqual
| Qual ModuleName OccName | 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 Bar.x, Bar.y or Bar.Foo.
Create such a RdrName with mkRdrQual
|
| Instances | |
|
|
Identifiers
|
|
type Id = Var |
|
idType :: Id -> Kind |
|
isImplicitId :: Id -> Bool |
isImplicitId tells whether an Ids info is implied by other
declarations, so we don't need to put its signature in an interface
file, even if it's mentioned in some other interface unfolding.
|
|
isDeadBinder :: Id -> Bool |
|
isExportedId :: Id -> Bool |
Determines whether an Id is marked as exported and hence will not be considered dead code
|
|
isLocalId :: Id -> Bool |
For an explanation of global vs. local Ids, see Var
|
|
isGlobalId :: Id -> Bool |
For an explanation of global vs. local Ids, see Var
|
|
isRecordSelector :: Id -> Bool |
|
isPrimOpId :: Id -> Bool |
|
isFCallId :: Id -> Bool |
|
isClassOpId_maybe :: Id -> Maybe Class |
|
isDataConWorkId :: Id -> Bool |
|
idDataCon :: Id -> DataCon |
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 :: Id -> Bool |
Returns true if an application to n args would diverge
|
|
isDictonaryId :: Id -> Bool |
|
recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel) |
If the Id is that for a record selector, extract the sel_tycon and label. Panic otherwise
|
|
Type constructors
|
|
data TyCon |
Represents 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 *
5) Type coercions! This is because we represent a coercion from t1 to t2 as a Type, where
that type has kind t1 ~ t2. See Coercion for more on this
This data type also encodes a number of primitive, built in type constructors such as those
for function and tuple types.
| Instances | |
|
|
tyConTyVars :: TyCon -> [TyVar] |
|
tyConDataCons :: TyCon -> [DataCon] |
As tyConDataCons_maybe, but returns the empty list of constructors if no constructors
could be found
|
|
tyConArity :: TyCon -> Arity |
|
isClassTyCon :: TyCon -> Bool |
Is this TyCon that for a class instance?
|
|
isSynTyCon :: TyCon -> Bool |
A product TyCon must both:
1. Have one constructor
2. Not be existential
However other than this there are few restrictions: they may be data or newtype
TyCons of any boxity and may even be recursive.
Is this a TyCon representing a type synonym (type)?
|
|
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 |
|
isOpenTyCon :: TyCon -> Bool |
Is this a TyCon, synonym or otherwise, that may have further instances appear?
|
|
synTyConDefn :: TyCon -> ([TyVar], Type) |
Extract the TyVars bound by a type synonym and the corresponding (unsubstituted) right hand side.
If the given TyCon is not a type synonym, panics
|
|
synTyConType :: TyCon -> Type |
Find the expansion of the type synonym represented by the given TyCon. The free variables of this
type will typically include those TyVars bound by the TyCon. Panics if the TyCon is not that of
a type synonym
|
|
synTyConResKind :: TyCon -> Kind |
Find the Kind of an open type synonym. Panics if the TyCon is not an open type synonym
|
|
Type variables
|
|
type TyVar = Var |
|
alphaTyVars :: [TyVar] |
|
Data constructors
|
|
data DataCon |
A data constructor
| Instances | |
|
|
dataConSig :: DataCon -> ([TyVar], ThetaType, [Type], Type) |
The "signature" of the DataCon returns, in order:
1) The result of dataConAllTyVars,
2) All the ThetaTypes relating to the DataCon (coercion, dictionary, implicit
parameter - whatever)
3) The type arguments to the constructor
4) The original result type of the DataCon
|
|
dataConType :: DataCon -> Type |
|
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 DataCons are those that are nice boring Haskell 98 constructors
|
|
dataConStrictMarks :: DataCon -> [StrictnessMark] |
The strictness markings decided on by the compiler. Does not include those for
existential dictionaries. The list is in one-to-one correspondence with the arity of the DataCon
|
|
data StrictnessMark |
Constructors | MarkedStrict | | MarkedUnboxed | | NotMarkedStrict | |
| Instances | |
|
|
isMarkedStrict :: StrictnessMark -> Bool |
|
Classes
|
|
data Class |
Instances | |
|
|
classMethods :: Class -> [Id] |
|
classSCTheta :: Class -> [PredType] |
|
classTvsFds :: Class -> ([TyVar], [FunDep TyVar]) |
|
pprFundeps :: Outputable a => [FunDep a] -> SDoc |
|
Instances
|
|
data Instance |
Instances | |
|
|
instanceDFunId :: Instance -> DFunId |
|
pprInstance :: Instance -> SDoc |
|
pprInstanceHdr :: Instance -> SDoc |
|
Types and Kinds
|
|
data Type |
The key representation of types within the compiler
| Instances | |
|
|
splitForAllTys :: Type -> ([TyVar], Type) |
Attempts to take a forall type apart, returning all the immediate such bound
type variables and the remainder of the type. Always suceeds, even if that means
returning an empty list of TyVars
|
|
funResultTy :: Type -> Type |
Extract the function result type and panic if that is not possible
|
|
pprParendType :: Type -> SDoc |
|
pprTypeApp :: NamedThing a => a -> [Type] -> SDoc |
|
type Kind = Type |
The key type representing kinds in the compiler.
Invariant: a kind is always in one of these forms:
FunTy k1 k2
TyConApp PrimTyCon [...]
TyVar kv -- (during inference only)
ForAll ... -- (for top-level coercions)
|
|
data PredType |
A type of the form PredTy p represents a value whose type is
the Haskell predicate p, where a predicate is what occurs before
the => in a Haskell type.
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"
| Instances | |
|
|
type ThetaType = [PredType] |
A collection of PredTypes
|
|
pprThetaArrow :: ThetaType -> SDoc |
|
Entities
|
|
data TyThing |
A typecheckable-thing, essentially anything that has a name
| Constructors | | Instances | |
|
|
Syntax
|
|
module HsSyn |
|
Fixities
|
|
data FixityDirection |
Constructors | | Instances | |
|
|
defaultFixity :: Fixity |
|
maxPrecedence :: Int |
|
negateFixity :: Fixity |
|
compareFixity :: Fixity -> Fixity -> (Bool, Bool) |
|
Source locations
|
|
data SrcLoc |
Represents a single point within a file
| Instances | |
|
|
pprDefnLoc :: SrcSpan -> SDoc |
Pretty prints information about the SrcSpan in the style defined at ...
|
|
mkSrcLoc :: FastString -> Int -> Int -> SrcLoc |
|
isGoodSrcLoc :: SrcLoc -> Bool |
Good SrcLocs have precise information about their location
|
|
noSrcLoc :: SrcLoc |
|
srcLocFile :: SrcLoc -> FastString |
Gives the filename of the SrcLoc if it is available, otherwise returns a dummy value
|
|
srcLocLine :: SrcLoc -> Int |
Raises an error when used on a bad SrcLoc
|
|
srcLocCol :: SrcLoc -> Int |
Raises an error when used on a bad SrcLoc
|
|
data SrcSpan |
A SrcSpan delimits a portion of a text file. It could be represented
by a pair of (line,column) coordinates, but in fact we optimise
slightly by using more compact representations for single-line and
zero-length spans, both of which are quite common.
The end position is defined to be the column after the end of the
span. That is, a span of (1,1)-(1,2) is one character long, and a
span of (1,1)-(1,1) is zero characters long.
| Instances | |
|
|
mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan |
Create a SrcSpan between two points in a file
|
|
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
|
|
noSrcSpan :: SrcSpan |
|
srcSpanStart :: SrcSpan -> SrcLoc |
Returns the location at the start of the SrcSpan or a bad SrcSpan if that is unavailable
|
|
srcSpanEnd :: SrcSpan -> SrcLoc |
Returns the location at the end of the SrcSpan or a bad SrcSpan if that is unavailable
|
|
srcSpanFile :: SrcSpan -> FastString |
|
srcSpanStartLine :: SrcSpan -> Int |
Raises an error when used on a bad SrcSpan
|
|
srcSpanEndLine :: SrcSpan -> Int |
Raises an error when used on a bad SrcSpan
|
|
srcSpanStartCol :: SrcSpan -> Int |
Raises an error when used on a bad SrcSpan
|
|
srcSpanEndCol :: SrcSpan -> Int |
Raises an error when used on a bad SrcSpan
|
|
Located
|
|
data Located e |
We attach SrcSpans to lots of things, so let's have a datatype for it.
| Constructors | | Instances | |
|
|
Constructing Located
|
|
noLoc :: e -> Located e |
|
mkGeneralLocated :: String -> e -> Located e |
|
Deconstructing Located
|
|
getLoc :: Located e -> SrcSpan |
|
unLoc :: Located e -> e |
|
Combining and comparing Located values
|
|
eqLocated :: Eq a => Located a -> Located a -> Bool |
Tests whether the two located things are equal
|
|
cmpLocated :: Ord a => Located a -> Located a -> Ordering |
Tests the ordering of the two located things
|
|
combineLocs :: Located a -> Located b -> SrcSpan |
|
addCLoc :: Located a -> Located b -> c -> Located c |
Combine locations from two Located things and add them to a third thing
|
|
leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering |
|
leftmost_largest :: SrcSpan -> SrcSpan -> Ordering |
Alternative strategies for ordering SrcSpans
|
|
rightmost :: SrcSpan -> SrcSpan -> Ordering |
|
spans :: SrcSpan -> (Int, Int) -> Bool |
Determines whether a span encloses a given line and column index
|
|
isSubspanOf |
:: SrcSpan | The span that may be enclosed by the other
| -> SrcSpan | The span it may be enclosed by
| -> Bool | | Determines whether a span is enclosed by another one
|
|
|
Exceptions
|
|
data GhcException |
Constructors | | Instances | |
|
|
showGhcException :: GhcException -> String -> String |
|
Token stream manipulations
|
|
data Token |
|
getTokenStream :: GhcMonad m => Module -> m [Located Token] |
Return module source as token stream, including comments.
The module must be in the module graph and its source must be available.
Throws a SourceError on parse error.
|
|
getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)] |
Give even more information on the source than getTokenStream
This function allows reconstructing the source completely with
showRichTokenStream.
|
|
showRichTokenStream :: [(Located Token, String)] -> String |
Take a rich token stream such as produced from getRichTokenStream and
return source code almost identical to the original code (except for
insignificant whitespace.)
|
|
addSourceToTokens :: SrcLoc -> StringBuffer -> [Located Token] -> [(Located Token, String)] |
Given a source location and a StringBuffer corresponding to this
location, return a rich token stream with the source associated to the
tokens.
|
|
Miscellaneous
|
|
cyclicModuleErr :: [ModSummary] -> SDoc |
|
Produced by Haddock version 2.4.2 |