Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Based on https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/API.
Given a list of paths to find libraries, and a file to compile, produce a list of CoreModule
values.
Synopsis
- data TcModuleResult = TcModuleResult {}
- newtype RunSimplifier = RunSimplifier Bool
- compileModule :: RunSimplifier -> HscEnv -> ModSummary -> TcGblEnv -> IO (IdeResult ModGuts)
- parseModule :: IdeOptions -> HscEnv -> FilePath -> ModSummary -> IO (IdeResult ParsedModule)
- typecheckModule :: IdeDefer -> HscEnv -> TypecheckHelpers -> ParsedModule -> IO (IdeResult TcModuleResult)
- computePackageDeps :: HscEnv -> Unit -> IO (Either [FileDiagnostic] [UnitId])
- addRelativeImport :: NormalizedFilePath -> ModuleName -> DynFlags -> DynFlags
- mkHiFileResultCompile :: ShakeExtras -> HscEnv -> TcModuleResult -> ModGuts -> IO (IdeResult HiFileResult)
- mkHiFileResultNoCompile :: HscEnv -> TcModuleResult -> IO HiFileResult
- generateObjectCode :: HscEnv -> ModSummary -> CgGuts -> IO (IdeResult Linkable)
- generateByteCode :: CoreFileTime -> HscEnv -> ModSummary -> CgGuts -> IO (IdeResult Linkable)
- generateHieAsts :: HscEnv -> TcModuleResult -> IO ([FileDiagnostic], Maybe (HieASTs Type))
- writeAndIndexHieFile :: HscEnv -> ShakeExtras -> ModSummary -> NormalizedFilePath -> [AvailInfo] -> HieASTs Type -> ByteString -> IO [FileDiagnostic]
- indexHieFile :: ShakeExtras -> ModSummary -> NormalizedFilePath -> Fingerprint -> HieFile -> IO ()
- writeHiFile :: ShakeExtras -> HscEnv -> HiFileResult -> IO [FileDiagnostic]
- getModSummaryFromImports :: HscEnv -> FilePath -> UTCTime -> Maybe StringBuffer -> ExceptT [FileDiagnostic] IO ModSummaryResult
- loadHieFile :: NameCacheUpdater -> FilePath -> IO HieFile
- loadInterface :: (MonadIO m, MonadMask m) => HscEnv -> ModSummary -> Maybe LinkableType -> RecompilationInfo m -> m ([FileDiagnostic], Maybe HiFileResult)
- data RecompilationInfo m = RecompilationInfo {
- source_version :: FileVersion
- old_value :: Maybe (HiFileResult, FileVersion)
- get_file_version :: NormalizedFilePath -> m (Maybe FileVersion)
- get_linkable_hashes :: [NormalizedFilePath] -> m [ByteString]
- regenerate :: Maybe LinkableType -> m ([FileDiagnostic], Maybe HiFileResult)
- loadModulesHome :: [HomeModInfo] -> HscEnv -> HscEnv
- getDocsBatch :: HscEnv -> [Name] -> IO [Either String (Maybe [HsDoc GhcRn], IntMap (HsDoc GhcRn))]
- lookupName :: HscEnv -> Name -> IO (Maybe TyThing)
- mergeEnvs :: HscEnv -> ModuleGraph -> ModSummary -> [HomeModInfo] -> [HscEnv] -> IO HscEnv
- ml_core_file :: ModLocation -> FilePath
- coreFileToLinkable :: LinkableType -> HscEnv -> ModSummary -> ModIface -> ModDetails -> CoreFile -> UTCTime -> IO ([FileDiagnostic], Maybe HomeModInfo)
- newtype TypecheckHelpers = TypecheckHelpers {
- getLinkables :: [NormalizedFilePath] -> IO [LinkableResult]
- sourceTypecheck :: Text
- sourceParser :: Text
- shareUsages :: ModIface -> ModIface
Documentation
data TcModuleResult Source #
Contains the typechecked module and the OrigNameCache entry for that module.
TcModuleResult | |
|
Instances
Show TcModuleResult Source # | |
Defined in Development.IDE.Core.RuleTypes showsPrec :: Int -> TcModuleResult -> ShowS # show :: TcModuleResult -> String # showList :: [TcModuleResult] -> ShowS # | |
NFData TcModuleResult Source # | |
Defined in Development.IDE.Core.RuleTypes rnf :: TcModuleResult -> () # |
newtype RunSimplifier Source #
Whether we should run the -O0 simplifier when generating core.
This is required for template Haskell to work but we disable this in DAML. See #256
compileModule :: RunSimplifier -> HscEnv -> ModSummary -> TcGblEnv -> IO (IdeResult ModGuts) Source #
Compile a single type-checked module to a CoreModule
value, or
provide errors.
parseModule :: IdeOptions -> HscEnv -> FilePath -> ModSummary -> IO (IdeResult ParsedModule) Source #
Given a string buffer, return the string (after preprocessing) and the ParsedModule
.
typecheckModule :: IdeDefer -> HscEnv -> TypecheckHelpers -> ParsedModule -> IO (IdeResult TcModuleResult) Source #
computePackageDeps :: HscEnv -> Unit -> IO (Either [FileDiagnostic] [UnitId]) Source #
Given a package identifier, what packages does it depend on
addRelativeImport :: NormalizedFilePath -> ModuleName -> DynFlags -> DynFlags Source #
mkHiFileResultCompile :: ShakeExtras -> HscEnv -> TcModuleResult -> ModGuts -> IO (IdeResult HiFileResult) Source #
generateObjectCode :: HscEnv -> ModSummary -> CgGuts -> IO (IdeResult Linkable) Source #
generateByteCode :: CoreFileTime -> HscEnv -> ModSummary -> CgGuts -> IO (IdeResult Linkable) Source #
generateHieAsts :: HscEnv -> TcModuleResult -> IO ([FileDiagnostic], Maybe (HieASTs Type)) Source #
writeAndIndexHieFile :: HscEnv -> ShakeExtras -> ModSummary -> NormalizedFilePath -> [AvailInfo] -> HieASTs Type -> ByteString -> IO [FileDiagnostic] Source #
indexHieFile :: ShakeExtras -> ModSummary -> NormalizedFilePath -> Fingerprint -> HieFile -> IO () Source #
In addition to indexing the `.hie` file, this function is responsible for
maintaining the IndexQueue
state and notifying the user about indexing
progress.
We maintain a record of all pending index operations in the $sel:indexPending:HieDbWriter
TVar.
When indexHieFile
is called, it must check to ensure that the file hasn't
already be queued up for indexing. If it has, then we can just skip it
Otherwise, we record the current file as pending and write an indexing operation to the queue
When the indexing operation is picked up and executed by the worker thread,
the first thing it does is ensure that a newer index for the same file hasn't
been scheduled by looking at $sel:indexPending:HieDbWriter
. If a newer index has been
scheduled, we can safely skip this one
Otherwise, we start or continue a progress reporting session, telling it about progress so far and the current file we are attempting to index. Then we can go ahead and call in to hiedb to actually do the indexing operation
Once this completes, we have to update the IndexQueue
state. First, we
must remove the just indexed file from $sel:indexPending:HieDbWriter
Then we check if
$sel:indexPending:HieDbWriter
is now empty. In that case, we end the progress session and
report the total number of file indexed. We also set the $sel:indexCompleted:HieDbWriter
TVar to 0 in order to set it up for a fresh indexing session. Otherwise, we
can just increment the $sel:indexCompleted:HieDbWriter
TVar and exit.
writeHiFile :: ShakeExtras -> HscEnv -> HiFileResult -> IO [FileDiagnostic] Source #
getModSummaryFromImports :: HscEnv -> FilePath -> UTCTime -> Maybe StringBuffer -> ExceptT [FileDiagnostic] IO ModSummaryResult Source #
Given a buffer, env and filepath, produce a module summary by parsing only the imports. Runs preprocessors as needed.
loadHieFile :: NameCacheUpdater -> FilePath -> IO HieFile Source #
loadInterface :: (MonadIO m, MonadMask m) => HscEnv -> ModSummary -> Maybe LinkableType -> RecompilationInfo m -> m ([FileDiagnostic], Maybe HiFileResult) Source #
Returns an up-to-date module interface, regenerating if needed.
Assumes file exists.
Requires the HscEnv
to be set up with dependencies
See Note [Recompilation avoidance in the presence of TH]
data RecompilationInfo m Source #
RecompilationInfo | |
|
loadModulesHome :: [HomeModInfo] -> HscEnv -> HscEnv Source #
Load modules, quickly. Input doesn't need to be desugared. A module must be loaded before dependent modules can be typechecked. This variant of loadModuleHome will *never* cause recompilation, it just modifies the session. The order modules are loaded is important when there are hs-boot files. In particular you should make sure to load the .hs version of a file after the .hs-boot version.
getDocsBatch :: HscEnv -> [Name] -> IO [Either String (Maybe [HsDoc GhcRn], IntMap (HsDoc GhcRn))] Source #
Non-interactive, batch version of getDocs
.
The interactive paths create problems in ghc-lib builds
lookupName :: HscEnv -> Name -> IO (Maybe TyThing) Source #
Non-interactive, batch version of lookupNames
.
The interactive paths create problems in ghc-lib builds
mergeEnvs :: HscEnv -> ModuleGraph -> ModSummary -> [HomeModInfo] -> [HscEnv] -> IO HscEnv Source #
ml_core_file :: ModLocation -> FilePath Source #
coreFileToLinkable :: LinkableType -> HscEnv -> ModSummary -> ModIface -> ModDetails -> CoreFile -> UTCTime -> IO ([FileDiagnostic], Maybe HomeModInfo) Source #
newtype TypecheckHelpers Source #
TypecheckHelpers | |
|
sourceParser :: Text Source #
shareUsages :: ModIface -> ModIface Source #
Mitigation for https://gitlab.haskell.org/ghc/ghc/-/issues/22744
Important to do this immediately after reading the unit before
anything else has a chance to read mi_usages