Safe Haskell | None |
---|---|
Language | Haskell2010 |
Session queries
We have to be very careful in the types in this module. We should not be using internal types (with explicit sharing or types such as StrictMap), except as part of abstract XShared types.
- type Query a = IdeSession -> IO a
- data ManagedFiles = ManagedFiles {
- sourceFiles :: [FilePath]
- dataFiles :: [FilePath]
- data InvalidSessionStateQueries = InvalidSessionStateQueries
- getSessionConfig :: Query SessionConfig
- getSourcesDir :: Query FilePath
- getDataDir :: Query FilePath
- getDistDir :: Query FilePath
- getSourceModule :: FilePath -> Query ByteString
- getDataFile :: FilePath -> Query ByteString
- getAllDataFiles :: Query [FilePath]
- getCabalMacros :: Query ByteString
- getCodeGeneration :: Query Bool
- getEnv :: Query [(String, Maybe String)]
- getArgs :: Query [String]
- getGhcServer :: Query GhcServer
- getGhcVersion :: Query GhcVersion
- getManagedFiles :: Query ManagedFiles
- getBuildExeStatus :: Query (Maybe ExitCode)
- getBuildDocStatus :: Query (Maybe ExitCode)
- getBuildLicensesStatus :: Query (Maybe ExitCode)
- getBreakInfo :: Query (Maybe BreakInfo)
- getSourceErrors :: Query [SourceError]
- getLoadedModules :: Query [ModuleName]
- getFileMap :: Query (FilePath -> Maybe ModuleId)
- getSpanInfo :: Query (ModuleName -> SourceSpan -> [(SourceSpan, SpanInfo)])
- getExpTypes :: Query (ModuleName -> SourceSpan -> [(SourceSpan, Text)])
- getImports :: Query (ModuleName -> Maybe [Import])
- getAutocompletion :: Query (ModuleName -> String -> [IdInfo])
- getPkgDeps :: Query (ModuleName -> Maybe [PackageId])
- getUseSites :: Query (ModuleName -> SourceSpan -> [SourceSpan])
- getDotCabal :: Query (String -> Version -> ByteString)
- dumpIdInfo :: IdeSession -> IO ()
- dumpAutocompletion :: IdeSession -> IO ()
- dumpFileMap :: IdeSession -> IO ()
Types
type Query a = IdeSession -> IO a Source
The type of queries in a given session state.
Queries are in IO because they depend on the current state of the session but they promise not to alter the session state (at least not in any visible way; they might update caches, etc.).
data ManagedFiles Source
The collection of source and data files submitted by the user.
ManagedFiles | |
|
Queries that rely on the static part of the state only
getSessionConfig :: Query SessionConfig Source
Recover the fixed config the session was initialized with.
getSourcesDir :: Query FilePath Source
Obtain the source files directory for this session.
getDataDir :: Query FilePath Source
Obtain the data files directory for this session.
getDistDir :: Query FilePath Source
Obtain the directory prefix for results of Cabal invocations.
Executables compiled in this session end up in a subdirectory build
,
haddocks in doc
, concatenated licenses in file licenses
, etc.
getSourceModule :: FilePath -> Query ByteString Source
Read the current value of one of the source modules.
getDataFile :: FilePath -> Query ByteString Source
Read the current value of one of the data files.
getAllDataFiles :: Query [FilePath] Source
Get the list of all data files currently available to the session: both the files copied via an update and files created by user code.
Queries that do not rely on computed state
getCodeGeneration :: Query Bool Source
Is code generation currently enabled?
getGhcServer :: Query GhcServer Source
Get the RPC server used by the session.
getGhcVersion :: Query GhcVersion Source
Which GHC version is `ide-backend-server` using?
getManagedFiles :: Query ManagedFiles Source
Get the collection of files submitted by the user and not deleted yet.
The module names are those supplied by the user as the first
arguments of the updateSourceFile
and updateSourceFileFromFile
calls,
as opposed to the compiler internal module ... end
module names.
Usually the two names are equal, but they needn't be.
getBuildExeStatus :: Query (Maybe ExitCode) Source
Get exit status of the last invocation of buildExe
, if any.
getBuildDocStatus :: Query (Maybe ExitCode) Source
Get exit status of the last invocation of buildDoc
, if any.
getBuildLicensesStatus :: Query (Maybe ExitCode) Source
Get exit status of the last invocation of buildLicenses
, if any.
getBreakInfo :: Query (Maybe BreakInfo) Source
Get information about the last breakpoint that we hit
Returns Nothing if we are not currently stopped on a breakpoint.
Queries that rely on computed state
getSourceErrors :: Query [SourceError] Source
Get any compilation errors or warnings in the current state of the session, meaning errors that GHC reports for the current state of all the source modules.
Note that in the initial implementation this will only return warnings from the modules that changed in the last update, the intended semantics is that morally it be a pure function of the current state of the files, and so it would return all warnings (as if you did clean and rebuild each time).
getSourceErrors does internal normalization. This simplifies the life of the client and anyway there shouldn't be that many source errors that it really makes a big difference.
getLoadedModules :: Query [ModuleName] Source
Get the list of correctly compiled modules, as reported by the compiler
getFileMap :: Query (FilePath -> Maybe ModuleId) Source
Get the mapping from filenames to modules (as computed by GHC)
getSpanInfo :: Query (ModuleName -> SourceSpan -> [(SourceSpan, SpanInfo)]) Source
Get information about an identifier at a specific location
getExpTypes :: Query (ModuleName -> SourceSpan -> [(SourceSpan, Text)]) Source
Get information the type of a subexpressions and the subexpressions around it
getImports :: Query (ModuleName -> Maybe [Import]) Source
Get import information
This information is available even for modules with parse/type errors
getAutocompletion :: Query (ModuleName -> String -> [IdInfo]) Source
getPkgDeps :: Query (ModuleName -> Maybe [PackageId]) Source
(Transitive) package dependencies
These are only available for modules that got compiled successfully.
getUseSites :: Query (ModuleName -> SourceSpan -> [SourceSpan]) Source
Use sites
Use sites are only reported in modules that get compiled successfully.
getDotCabal :: Query (String -> Version -> ByteString) Source
Minimal .cabal file for the loaded modules seen as a library. The argument specifies the name of the library.
License is set to AllRightsReserved
.
All transitive package dependencies are included,
with package versions set to the currently used versions.
Only modules that get compiled successfully are included.
Source directory is the currently used session source directory.
Warning: all modules named Main
(even in subdirectories
or files with different names) are ignored so that they
don't get in the way when we build an executable using the library
and so that the behaviour is consistent with that of buildExe
.
Debugging (internal use only)
dumpIdInfo :: IdeSession -> IO () Source
Print the id info maps to stdout (for debugging purposes only)
dumpAutocompletion :: IdeSession -> IO () Source
Print autocompletion to stdout (for debugging purposes only)
dumpFileMap :: IdeSession -> IO () Source
Print file mapping to stdout (for debugging purposes only)