ghcide-1.7.0.0: The core of an IDE
Safe HaskellNone
LanguageHaskell2010

Development.IDE.Core.Compile

Description

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

Documentation

data TcModuleResult Source #

Contains the typechecked module and the OrigNameCache entry for that module.

Constructors

TcModuleResult 

Fields

Instances

Instances details
Show TcModuleResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData TcModuleResult Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

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

Constructors

RunSimplifier Bool 

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 Source #

Arguments

:: IdeDefer 
-> HscEnv 
-> ModuleEnv UTCTime

linkables not to unload

-> ParsedModule 
-> IO (IdeResult TcModuleResult) 

computePackageDeps :: HscEnv -> Unit -> IO (Either [FileDiagnostic] [UnitId]) Source #

Given a package identifier, what packages does it depend on

mkHiFileResultCompile Source #

Arguments

:: HscEnv 
-> TcModuleResult 
-> ModGuts 
-> LinkableType

use object code or byte code?

-> IO (IdeResult HiFileResult) 

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 notfiying 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.

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.

loadInterface :: (MonadIO m, MonadMask m) => HscEnv -> ModSummary -> Maybe LinkableType -> RecompilationInfo m -> m ([FileDiagnostic], Maybe HiFileResult) Source #

Retuns 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]

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 Source #

Arguments

:: HscEnv 
-> Module

a moudle where the names are in scope

-> [Name] 
-> IO [Either String (Maybe HsDocString, IntMap HsDocString)] 

Non-interactive, batch version of getDocs. The interactive paths create problems in ghc-lib builds

lookupName Source #

Arguments

:: HscEnv 
-> Module

A module where the Names are in scope

-> Name 
-> IO (Maybe TyThing) 

Non-interactive, batch version of lookupNames. The interactive paths create problems in ghc-lib builds