ide-backend-0.9.0.10: An IDE backend library

Safe HaskellNone
LanguageHaskell2010

IdeSession

Contents

Description

This module provides an interface to the IDE backend. It centres around the idea of a single threaded IDE session, and operations for updating the session or running queries given the current state of the session.

Interaction with the compiler

Ironically for a pure functional language, the interface to the compiler is rather stateful and sequential. In part this is because it's dealing with the state of files in the file system which are of course mutable variables.

So the general pattern of interaction is sequential and single-threaded. The state transitions are fairly simple:

  • update phase: we have a batch of updates, e.g. changes in module contents. This part is declarative, we just describe what changes we want to make.
  • compile phase: we apply the updates and invoke the compiler, which incrementally recompiles some modules. This may be a relatively long running operation and we may want progress info.
  • query phase: after compiling we can collect information like source errors, the list of successfully loaded modules or symbol maps.
  • run phase: regardless of compilation results, we may want to run some code from a module (compiled recently or compiled many updates ago), interact with the running code's input and output, interrupt its execution.

Then the whole process can repeat.

To clarify these different phases we use different types:

  • IdeSession for the query mode. This is in a sense also the default mode.
  • IdeSessionUpdate for accumulating updates.
  • Progress for the progress information in the compile mode.
  • RunActions for handles on the running code, through which one can interact with the code.

Additional notes

  • Responsibility for managing and mutating files in the sources dir.

In general, updating and changing source files in the sources dir has to be coordinated with the IdeSession, since we're in a concurrent mutable setting.

The model here is that the IdeSession alone manages the files in the sources directory. All file changes and file reading must be managed via the session, and sequenced relative to other session state changes.

The session will manage the files carefully, including in the case of exceptions and things going awry. Thus the caller does not need to duplicate the file state: it can rely on putting files in, applying updates to the files via the session, and extracting the files again at any time (before the session is closed).

  • Morally pure queries

Morally, a compiler is a pure function from the current value of the various source files (and other bits of the environment) to object code and/or other information about the modules (errors, types etc).

The intention is to reflect this purity property in this interface. The value of an IdeSession represents the state of the files/modules and contains the other parameters supplied by the user (compiler options, environment variables). It also contains or represents the result of the pure compilation function. It should always be the case that we can throw away all the compilation results and recover them just from the file state and user parameters.

One example where this notion makes a difference is with warnings. Traditionally, compilers just return the warnings for the modules they compiled, skipping warnings for the modules they didn't need to recompile. But this doesn't match the pure function idea, because the compilation result now depends on which steps we took to get there, rather than just on the current value of the files. So one of the things this wrapper can do is to restore the purity in these corner cases (which otherwise the client of this API would probably have to do).

  • Persistent and transitory state

The persistent state is obviously the files: source files and data files, as well as user-supplied parameters of the compilation. Internally there is a great deal of transitory and cached state, either in memory or on disk (such as .hi files on disk or the equivalent in memory). Note that none of the state persists in case of a fatal internal error (the files are wiped out before shutdown) and only the files persist in case of a power failure (but have to be recovered manually).

It should be possible to drop all the transitory state and recover, just at the cost of some extra work, as long as the original Session value is available. The restartSession function does almost exactly that.

This property is a useful correctness property for internal testing: the results of all the queries should be the same before and after blowing away all the transitory state and recovering.

Synopsis

Configuration

data SessionConfig Source

Configuration parameters for a session. These remain the same throughout the whole session's lifetime.

Constructors

SessionConfig 

Fields

configDir :: FilePath

The directory to use for all session files.

configExtraPathDirs :: [FilePath]

Extra directories in which to look for programs, including ghc and other tools. Note that the $PATH is still searched first, these directories are extra.

configInProcess :: InProcess

Should the GHC client run in-process? NOTE: This is currently broken. Set to False.

configGenerateModInfo :: Bool

Whether to generate module type/autocompletion info.

configPackageDBStack :: PackageDBStack

Package DBs to consult

configLicenseExc :: [String]

Packages that don't need the .cabal files provided for license concatenation (e.g., because they are covered by the core license set).

configLicenseFixed :: [(String, (Maybe License, Maybe FilePath, Maybe String))]

Hard-coded package licence information, e.g., for the packages that always stay installed in-place in the GHC tree, so it's troublesome to automatically retrieve their .cabal files.

configLog :: String -> IO ()

Function to be used for logging. Messages logged in this manner may be provided to users in a special debugging UI.

configDeleteTempFiles :: Bool

Delete temporary files when session finishes? (Defaults to True; mostly for internal debugging purposes)

defaultSessionConfig :: SessionConfig Source

Default session configuration

Use this instead of creating your own SessionConfig to be robust against extensions of SessionConfig.

defaultSessionConfig = SessionConfig {
    configDir              = "."
  , configExtraPathDirs    = []
  , configInProcess        = False
  , configGenerateModInfo  = True
  , configPackageDBStack   = [GlobalPackageDB, UserPackageDB]
    -- ghc-prim, integer-gmp, etc., all have their own licenses specified
    -- in their .cabal files.
  , configLicenseExc       = ["rts"]
  , configLicenseFixed     = [
        ("bin-package-db", (Just BSD3, Nothing,           Nothing))
      , ("ghc",            (Just BSD3, Just "../LICENSE", Just "The GHC Team"))
      , ("ghc-prim",       (Just BSD3, Just "LICENSE",    Nothing))
      , ("integer-gmp",    (Just BSD3, Just "LICENSE",    Nothing))
      ]
  , configLog              = const $ return ()
  , configDeleteTempFiles  = True
  }

Updating the session

Starting and stopping

data IdeSession Source

This type is a handle to a session state. Values of this type point to the non-persistent parts of the session state in memory and to directories containing source and data file that form the persistent part of the session state. Whenever we perform updates or run queries, it's always in the context of a particular handle, representing the session we want to work within. Many sessions can be active at once, but in normal applications this shouldn't be needed.

initSession :: SessionInitParams -> SessionConfig -> IO IdeSession Source

Create a fresh session, using some initial configuration.

Throws an exception if the configuration is invalid, or if GHC_PACKAGE_PATH is set.

data SessionInitParams Source

How should the session be initialized?

Client code should use defaultSessionInitParams to protect itself against future extensions of this record.

Constructors

SessionInitParams 

Fields

sessionInitCabalMacros :: Maybe ByteString

Previously computed cabal macros, or Nothing to compute them on startup

sessionInitGhcOptions :: [String]

Initial ghc options

sessionInitRelativeIncludes :: [FilePath]

Include paths (equivalent of GHC's -i parameter) relative to the temporary directory where we store the session's source files.

By default this is the singleton list [""] -- i.e., we include the sources dir but nothing else.

sessionInitTargets :: Targets

Targets for compilation

Defaults to TargetsExclude [] -- i.e., compile all modules in the project.

sessionInitRtsOpts :: [String]

RTS options

Defaults to -K8M

shutdownSession :: IdeSession -> IO () Source

Close a session down, releasing the resources.

This operation is the only one that can be run after a shutdown was already performed. This lets the API user execute an early shutdown, e.g., before the shutdownSession placed inside bracket is triggered by a normal program control flow.

If code is still running, it will be interrupted.

forceShutdownSession :: IdeSession -> IO () Source

Like shutdownSession, but don't be nice about it (SIGKILL)

restartSession :: IdeSession -> IO () Source

Restart a session

This puts the session in a "dead" state; it won't _actually_ be restarted until the next call to updateSession.

Session updates

data IdeSessionUpdate Source

Declarative description of session updates

IdeSessionUpdate forms a monoid, which is right-biased: "later" calls override "earlier" ones:

updateTargets targets1 <> updateTargets2

is equivalent to

updateTargets2

However, updates of a different nature are not necessarily executed in order; for instance,

updateDynamicOpts opts <> updateSourceFile fp bs

is equivalent to

updateSourceFile fp bs <> updateDynamicOpts opts

In both cases options are set before new source files are compiled.

File commands are updated in order, so that

updateSourceFile fp bs <> updateSourceFile fp bs'

is equivalent to

updateSourceFile fp bs'

which is consistent with "later updates override earlier ones".

updateSession :: IdeSession -> IdeSessionUpdate -> (Progress -> IO ()) -> IO () Source

Given the current IDE session state, go ahead and update the session, eventually resulting in a new session state, with fully updated computed information (typing, etc.).

The update can be a long running operation, so we support a callback which can be used to monitor progress of the operation.

updateSourceFile :: FilePath -> ByteString -> IdeSessionUpdate Source

A session update that changes a source file by providing some contents. This can be used to add a new module or update an existing one. The FilePath argument determines the directory and file where the module is located within the project. In case of Haskell source files, the actual internal compiler module name, such as the one given by the getLoadedModules query, comes from within module ... end. Usually the two names are equal, but they needn't be.

updateSourceFileFromFile :: FilePath -> IdeSessionUpdate Source

Like updateSourceFile except that instead of passing the source by value, it's given by reference to an existing file, which will be copied.

updateSourceFileDelete :: FilePath -> IdeSessionUpdate Source

A session update that deletes an existing source file.

updateGhcOpts :: [String] -> IdeSessionUpdate Source

Set ghc options

This function is stateless: the set of actions options is the set provided by the last call to updateGhcOptions.

updateRtsOpts :: [String] -> IdeSessionUpdate Source

Set RTS options for the ghc session (this does not affect executables)

This will cause a session restart.

NOTE: Limiting stack size does not seem to work for ghc 7.4 (https:/github.comfpcoide-backendissues/258).

updateRelativeIncludes :: [FilePath] -> IdeSessionUpdate Source

Set include paths (equivalent of GHC's -i parameter). In general, this requires session restart, because GHC doesn't revise module dependencies when targets or include paths change, but only when files change.

This function is stateless: semantically, the set of currently active include paths are those set in the last call to updateRelativeIncludes. Any paths set earlier (including those from configRelativeIncludes) are wiped out and overwritten in each call to updateRelativeIncludes.

updateCodeGeneration :: Bool -> IdeSessionUpdate Source

Enable or disable code generation in addition to type-checking. Required by runStmt.

updateDataFile :: FilePath -> ByteString -> IdeSessionUpdate Source

A session update that changes a data file by giving a new value for the file. This can be used to add a new file or update an existing one.

updateDataFileFromFile :: FilePath -> FilePath -> IdeSessionUpdate Source

Like updateDataFile except that instead of passing the file content by value, it's given by reference to an existing file (the second argument), which will be copied.

updateDataFileDelete :: FilePath -> IdeSessionUpdate Source

Deletes an existing data file.

updateDeleteManagedFiles :: IdeSessionUpdate Source

Delete all files currently managed in this session

updateEnv :: [(String, Maybe String)] -> IdeSessionUpdate Source

Set environment variables

Use updateEnv [(var, Nothing)] to unset var.

Note that this is intended to be stateless:

updateEnv []

will reset the environment to the server's original environment.

updateArgs :: [String] -> IdeSessionUpdate Source

Set command line arguments for snippets (i.e., the expected value of getArgs)

updateStdoutBufferMode :: RunBufferMode -> IdeSessionUpdate Source

Set buffering mode for snippets' stdout

updateStderrBufferMode :: RunBufferMode -> IdeSessionUpdate Source

Set buffering mode for snippets' stderr

updateTargets :: Targets -> IdeSessionUpdate Source

Set compilation targets. In general, this requires session restart, because GHC doesn't revise module dependencies when targets or include paths change, but only when files change.

buildExe :: [String] -> [(ModuleName, FilePath)] -> IdeSessionUpdate Source

Build an exe from sources added previously via the ide-backend updateSourceFile* mechanism. The modules that contains the main code are indicated in second argument to buildExe. The function can be called multiple times with different arguments. Additional GHC options, applied only when building executables, are supplied in the first argument.

We assume any indicated module is already successfully processed by GHC API in a compilation mode that makes computedImports available (but no code needs to be generated). The environment (package dependencies, ghc options, preprocessor program options, etc.) for building the exe is the same as when previously compiling the code via GHC API. The module does not have to be called Main, but we assume the main function is always main (we don't check this and related conditions, but GHC does when eventually called to build the exe).

The executable files are placed in the filesystem inside the build subdirectory of getDistDir, in subdirectories corresponding to the given module names. The build directory does not overlap with any of the other used directories and with its path.

Logs from the building process are saved in files build/ide-backend-exe.stdout and build/ide-backend-exe.stderr in the getDistDir directory.

Note: currently it requires configGenerateModInfo to be set (see #86). Also, after session restart, one has to call updateSession at least once (even with empty updates list) before calling it for buildExe. This ensures the code is compiled again and the results made accessible.

buildDoc :: IdeSessionUpdate Source

Build haddock documentation from sources added previously via the ide-backend updateSourceFile* mechanism. Similarly to buildExe, it needs the project modules to be already loaded within the session and the generated docs can be found in the doc subdirectory of getDistDir.

Logs from the documentation building process are saved in files doc/ide-backend-doc.stdout and doc/ide-backend-doc.stderr in the getDistDir directory.

Note: currently it requires configGenerateModInfo to be set (see #86).

buildLicenses :: FilePath -> IdeSessionUpdate Source

Build a file containing licenses of all used packages. Similarly to buildExe, the function needs the project modules to be already loaded within the session. The concatenated licenses can be found in file licenses.txt inside the getDistDir directory.

The function expects .cabal files of all used packages, except those mentioned in configLicenseExc, to be gathered in the directory given as the first argument (which needs to be an absolute path or a path relative to the data dir). The code then expects to find those packages installed and their license files in the usual place that Cabal puts them (or the in-place packages should be correctly embedded in the GHC tree).

We guess the installed locations of the license files on the basis of the haddock interfaces path. If the default setting does not work properly, the haddock interfaces path should be set manually. E.g., cabal configure --docdir=the_same_path --htmldir=the_same_path affects the haddock interfaces path (because it is by default based on htmldir) and is reported to work for some values of the_same_path.

Logs from the license search and catenation process are saved in files licenses.stdout and licenses.stderr in the getDistDir directory.

Note: currently configGenerateModInfo needs to be set for this function to work (see #86).

Note: if the executable uses TH and its module is named Main (and so it's not compiled as a part of a temporary library) configDynLink needs to be set. See #162.

Progress

data Progress :: *

This type represents intermediate progress information during compilation.

Constructors

Progress 

Fields

progressStep :: Int

The current step number

When these Progress messages are generated from progress updates from ghc, it is entirely possible that we might get step 426, 1626, 3/26; the steps may not be continuous, might even be out of order, and may not finish at X/X.

progressNumSteps :: Int

The total number of steps

progressParsedMsg :: Maybe Text

The parsed message. For instance, in the case of progress messages during compilation, progressOrigMsg might be

[1 of 2] Compiling M (some/path/to/file.hs, some/other/path/to/file.o)

while progressMsg will just be 'Compiling M'

progressOrigMsg :: Maybe Text

The full original message (see progressMsg)

Instances

Eq Progress 
Ord Progress 
Show Progress 
Generic Progress 
Binary Progress 
PrettyVal Progress 
type Rep Progress = D1 D1Progress (C1 C1_0Progress ((:*:) ((:*:) (S1 S1_0_0Progress (Rec0 Int)) (S1 S1_0_1Progress (Rec0 Int))) ((:*:) (S1 S1_0_2Progress (Rec0 (Maybe Text))) (S1 S1_0_3Progress (Rec0 (Maybe Text)))))) 

Running code

data RunActions a Source

Handles to the running code snippet, through which one can interact with the snippet.

Requirement: concurrent uses of supplyStdin should be possible, e.g., two threads that share a RunActions should be able to provide input concurrently without problems. (Currently this is ensured by supplyStdin writing to a channel.)

Constructors

RunActions 

Fields

runWait :: IO (Either ByteString a)

Wait for the code to output something or terminate

interrupt :: IO ()

Send a UserInterrupt exception to the code

A call to interrupt after the snippet has terminated has no effect.

supplyStdin :: ByteString -> IO ()

Make data available on the code's stdin

A call to supplyStdin after the snippet has terminated has no effect.

forceCancel :: IO ()

Force terminate the runaction (The server will be useless after this -- for internal use only).

Guranteed not to block.

data RunResult :: *

The outcome of running code

Constructors

RunOk

The code terminated okay

RunProgException String

The code threw an exception

RunGhcException String

GHC itself threw an exception when we tried to run the code

RunForceCancelled

The session was restarted

RunBreak

Execution was paused because of a breakpoint

Instances

Eq RunResult 
Show RunResult 
Generic RunResult 
ToJSON RunResult 
FromJSON RunResult 
PrettyVal RunResult 
Typeable * RunResult 
type Rep RunResult = D1 D1RunResult ((:+:) ((:+:) (C1 C1_0RunResult U1) (C1 C1_1RunResult (S1 NoSelector (Rec0 String)))) ((:+:) (C1 C1_2RunResult (S1 NoSelector (Rec0 String))) ((:+:) (C1 C1_3RunResult U1) (C1 C1_4RunResult U1)))) 
type XShared RunResult = RunResult 

data RunBufferMode :: *

Buffer modes for running code

Note that NoBuffering means that something like putStrLn will do a syscall per character, and each of these characters will be read and sent back to the client. This results in a large overhead.

When using LineBuffering or BlockBuffering, runWait will not report any output from the snippet until it outputs a linebreak/fills the buffer, respectively (or does an explicit flush). However, you can specify a timeout in addition to the buffering mode; if you set this to Just n, the buffer will be flushed every n microseconds.

NOTE: This is duplicated in the IdeBackendRTS (defined in IdeSession)

Instances

Eq RunBufferMode 
Show RunBufferMode 
Generic RunBufferMode 
Binary RunBufferMode 
ToJSON RunBufferMode 
FromJSON RunBufferMode 
PrettyVal RunBufferMode 
Typeable * RunBufferMode 
type Rep RunBufferMode = D1 D1RunBufferMode ((:+:) (C1 C1_0RunBufferMode U1) ((:+:) (C1 C1_1RunBufferMode (S1 S1_1_0RunBufferMode (Rec0 (Maybe Int)))) (C1 C1_2RunBufferMode ((:*:) (S1 S1_2_0RunBufferMode (Rec0 (Maybe Int))) (S1 S1_2_1RunBufferMode (Rec0 (Maybe Int))))))) 

data BreakInfo :: *

Information about a triggered breakpoint

Constructors

BreakInfo 

Fields

breakInfoModule :: ModuleName

Module containing the breakpoint

breakInfoSpan :: SourceSpan

Location of the breakpoint

breakInfoResultType :: Type

Type of the result

breakInfoVariableEnv :: VariableEnv

Local variables and their values

Instances

Eq BreakInfo 
Show BreakInfo 
Generic BreakInfo 
ToJSON BreakInfo 
FromJSON BreakInfo 
ExplicitSharing BreakInfo 
PrettyVal BreakInfo 
Typeable * BreakInfo 
type Rep BreakInfo = D1 D1BreakInfo (C1 C1_0BreakInfo ((:*:) ((:*:) (S1 S1_0_0BreakInfo (Rec0 ModuleName)) (S1 S1_0_1BreakInfo (Rec0 SourceSpan))) ((:*:) (S1 S1_0_2BreakInfo (Rec0 Type)) (S1 S1_0_3BreakInfo (Rec0 VariableEnv))))) 
type XShared BreakInfo = BreakInfo 

runStmt :: IdeSession -> String -> String -> IO (RunActions RunResult) Source

Run a given function in a given module (the name of the module is the one between module ... end, which may differ from the file name). The function resembles a query, but it's not instantaneous and the running code can be interrupted or interacted with.

runStmt will throw an exception if the code has not been compiled yet, or when the server is in a dead state (i.e., when ghc has crashed). In the latter case getSourceErrors will report the ghc exception; it is the responsibility of the client code to check for this.

runStmtPty :: IdeSession -> String -> String -> IO (RunActions RunResult) Source

Like runStmt, but runs the statement in a pseudoterminal.

runExe :: IdeSession -> String -> IO (RunActions ExitCode) Source

Run the main function from the last compiled executable.

runExe will throw an exception if there were no executables compiled since session init, or if the last compilation was not successful (checked as in getBuildExeStatus) or if none of the executables last compiled have the supplied name or when the server is in a dead state (i.e., when ghc has crashed). In the last case getSourceErrors will report the ghc exception; it is the responsibility of the client code to check for this.

resume :: IdeSession -> IO (RunActions RunResult) Source

Resume a previously interrupted statement

runWaitAll :: forall a. RunActions a -> IO (ByteString, a) Source

Repeatedly call runWait until we receive a Right result, while collecting all Left results

setBreakpoint Source

Arguments

:: IdeSession 
-> ModuleName

Module where the breakshould should be set

-> SourceSpan

Location of the breakpoint

-> Bool

New value for the breakpoint

-> IO (Maybe Bool)

Old value of the breakpoint (if valid)

Breakpoint

Set a breakpoint at the specified location. Returns Just the old value of the breakpoint if successful, or Nothing otherwise.

printVar Source

Arguments

:: IdeSession 
-> Name

Variable to print

-> Bool

Should printing bind new vars? (:print vs. :sprint)

-> Bool

Should the value be forced? (:print vs. :force)

-> IO VariableEnv 

Print and/or force values during debugging

Only valid in breakpoint state.

Queries

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.

Constructors

ManagedFiles 

Instances

data Targets :: *

Instances

data GhcVersion :: *

GHC version

NOTE: Defined in such a way that the Ord instance makes sense.

Constructors

GHC_7_4 
GHC_7_8 
GHC_7_10 

Instances

Eq GhcVersion 
Ord GhcVersion 
Show GhcVersion 
Generic GhcVersion 
Binary GhcVersion 
PrettyVal GhcVersion 
Typeable * GhcVersion 
type Rep GhcVersion = D1 D1GhcVersion ((:+:) (C1 C1_0GhcVersion U1) ((:+:) (C1 C1_1GhcVersion U1) (C1 C1_2GhcVersion U1))) 

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?

getEnv :: Query [(String, Maybe String)] Source

Get all current environment overrides

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.

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)

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.

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

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.

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

Autocompletion

Use idInfoQN to translate these IdInfos into qualified names, taking into account the module imports.

getPkgDeps :: Query (ModuleName -> Maybe [PackageId]) Source

(Transitive) package dependencies

These are only available for modules that got compiled successfully.

Types for identifier info, errors, etc.

Types

data IdNameSpace :: *

Identifiers in Haskell are drawn from a number of different name spaces

Constructors

VarName

Variables, including real data constructors

DataName

Source data constructors

TvName

Type variables

TcClsName

Type constructors and classes

Instances

Eq IdNameSpace 
Show IdNameSpace 
Generic IdNameSpace 
Binary IdNameSpace 
ToJSON IdNameSpace 
FromJSON IdNameSpace 
PrettyVal IdNameSpace 
type Rep IdNameSpace = D1 D1IdNameSpace ((:+:) ((:+:) (C1 C1_0IdNameSpace U1) (C1 C1_1IdNameSpace U1)) ((:+:) (C1 C1_2IdNameSpace U1) (C1 C1_3IdNameSpace U1))) 

type Type = Text

For now we represent types in pretty-printed form

data IdInfo :: *

Information about identifiers

Constructors

IdInfo 

Fields

idProp :: !IdProp
 
idScope :: !IdScope
 

Instances

Eq IdInfo 
Show IdInfo 
Generic IdInfo 
Binary IdInfo 
ToJSON IdInfo 
FromJSON IdInfo 
ExplicitSharing IdInfo 
PrettyVal IdInfo 
type Rep IdInfo = D1 D1IdInfo (C1 C1_0IdInfo ((:*:) (S1 S1_0_0IdInfo (Rec0 IdProp)) (S1 S1_0_1IdInfo (Rec0 IdScope)))) 
type XShared IdInfo = IdInfo 

data IdProp :: *

Identifier info that is independent of the usage site

Constructors

IdProp 

Fields

idName :: !Name

The base name of the identifer at this location. Module prefix is not included.

idSpace :: !IdNameSpace

Namespace this identifier is drawn from

idType :: !(Maybe Type)

The type We don't always know this; in particular, we don't know kinds because the type checker does not give us LSigs for top-level annotations)

idDefinedIn :: !ModuleId

Module the identifier was defined in

idDefSpan :: !EitherSpan

Where in the module was it defined (not always known)

idHomeModule :: !(Maybe ModuleId)

Haddock home module

Instances

Eq IdProp 
Show IdProp 
Generic IdProp 
Binary IdProp 
ToJSON IdProp 
FromJSON IdProp 
ExplicitSharing IdProp 
PrettyVal IdProp 
type Rep IdProp = D1 D1IdProp (C1 C1_0IdProp ((:*:) ((:*:) (S1 S1_0_0IdProp (Rec0 Name)) ((:*:) (S1 S1_0_1IdProp (Rec0 IdNameSpace)) (S1 S1_0_2IdProp (Rec0 (Maybe Type))))) ((:*:) (S1 S1_0_3IdProp (Rec0 ModuleId)) ((:*:) (S1 S1_0_4IdProp (Rec0 EitherSpan)) (S1 S1_0_5IdProp (Rec0 (Maybe ModuleId))))))) 
type XShared IdProp = IdProp 

data IdScope :: *

Constructors

Binder

This is a binding occurrence (f x = .., x -> .., etc.)

Local

Defined within this module

Imported

Imported from a different module

Fields

idImportedFrom :: !ModuleId
 
idImportSpan :: !EitherSpan
 
idImportQual :: !Text

Qualifier used for the import

IMPORTED AS                       idImportQual
import Data.List                  ""
import qualified Data.List        "Data.List."
import qualified Data.List as L   "L."
WiredIn

Wired into the compiler ((), True, etc.)

Instances

Eq IdScope 
Show IdScope 
Generic IdScope 
Binary IdScope 
ToJSON IdScope 
FromJSON IdScope 
ExplicitSharing IdScope 
PrettyVal IdScope 
type Rep IdScope = D1 D1IdScope ((:+:) ((:+:) (C1 C1_0IdScope U1) (C1 C1_1IdScope U1)) ((:+:) (C1 C1_2IdScope ((:*:) (S1 S1_2_0IdScope (Rec0 ModuleId)) ((:*:) (S1 S1_2_1IdScope (Rec0 EitherSpan)) (S1 S1_2_2IdScope (Rec0 Text))))) (C1 C1_3IdScope U1))) 
type XShared IdScope = IdScope 

data SourceSpan :: *

Instances

Eq SourceSpan 
Ord SourceSpan 
Show SourceSpan 
Generic SourceSpan 
Binary SourceSpan 
ToJSON SourceSpan 
FromJSON SourceSpan 
ExplicitSharing SourceSpan 
IntroduceSharing SourceSpan 
PrettyVal SourceSpan 
type Rep SourceSpan = D1 D1SourceSpan (C1 C1_0SourceSpan ((:*:) ((:*:) (S1 S1_0_0SourceSpan (Rec0 FilePath)) (S1 S1_0_1SourceSpan (Rec0 Int))) ((:*:) (S1 S1_0_2SourceSpan (Rec0 Int)) ((:*:) (S1 S1_0_3SourceSpan (Rec0 Int)) (S1 S1_0_4SourceSpan (Rec0 Int)))))) 
type XShared SourceSpan = SourceSpan 

data SourceError :: *

An error or warning in a source module.

Most errors are associated with a span of text, but some have only a location point.

Instances

data SourceErrorKind :: *

Severity of an error.

Instances

Eq SourceErrorKind 
Show SourceErrorKind 
Generic SourceErrorKind 
Binary SourceErrorKind 
ToJSON SourceErrorKind 
FromJSON SourceErrorKind 
PrettyVal SourceErrorKind 
type Rep SourceErrorKind = D1 D1SourceErrorKind ((:+:) (C1 C1_0SourceErrorKind U1) ((:+:) (C1 C1_1SourceErrorKind U1) (C1 C1_2SourceErrorKind U1))) 

data ModuleId :: *

Constructors

ModuleId 

data PackageId :: *

A package ID in ide-backend consists of a human-readable package name and version (what Cabal calls a source ID) along with ghc's internal package key (primarily for internal use).

Constructors

PackageId 

Instances

Eq PackageId 
Ord PackageId 
Show PackageId 
Generic PackageId 
Binary PackageId 
ToJSON PackageId 
FromJSON PackageId 
ExplicitSharing PackageId 
PrettyVal PackageId 
type Rep PackageId = D1 D1PackageId (C1 C1_0PackageId ((:*:) (S1 S1_0_0PackageId (Rec0 Text)) ((:*:) (S1 S1_0_1PackageId (Rec0 (Maybe Text))) (S1 S1_0_2PackageId (Rec0 Text))))) 
type XShared PackageId = PackageId 

data Import :: *

Constructors

Import 

Fields

importModule :: !ModuleId
 
importPackage :: !(Maybe Text)

Used only for ghc's PackageImports extension

importQualified :: !Bool
 
importImplicit :: !Bool
 
importAs :: !(Maybe ModuleName)
 
importEntities :: !ImportEntities
 

Instances

Eq Import 
Ord Import 
Show Import 
Generic Import 
Binary Import 
ToJSON Import 
FromJSON Import 
ExplicitSharing Import 
PrettyVal Import 
type Rep Import = D1 D1Import (C1 C1_0Import ((:*:) ((:*:) (S1 S1_0_0Import (Rec0 ModuleId)) ((:*:) (S1 S1_0_1Import (Rec0 (Maybe Text))) (S1 S1_0_2Import (Rec0 Bool)))) ((:*:) (S1 S1_0_3Import (Rec0 Bool)) ((:*:) (S1 S1_0_4Import (Rec0 (Maybe ModuleName))) (S1 S1_0_5Import (Rec0 ImportEntities)))))) 
type XShared Import = Import 

data SpanInfo :: *

Returned when the IDE asks "what's at this particular location?"

Constructors

SpanId IdInfo

Identifier

SpanQQ IdInfo

Quasi-quote. The IdInfo field gives the quasi-quoter

Util

idInfoQN :: IdInfo -> String

Construct qualified name following Haskell's scoping rules

haddockLink :: IdProp -> IdScope -> String

Show approximately a haddock link (without haddock root) for an id. This is an illustration and a test of the id info, but under ideal conditions could perhaps serve to link to documentation without going via Hoogle.

Exception types

data ExternalException :: *

Exceptions thrown by the remote server

Constructors

ExternalException 

Fields

externalStdErr :: String

The output from the server on stderr

externalException :: Maybe IOException

The local exception that was thrown and alerted us to the problem

Re-exports from Cabal

type PackageDBStack = [PackageDB]

We typically get packages from several databases, and stack them together. This type lets us be explicit about that stacking. For example typical stacks include:

[GlobalPackageDB]
[GlobalPackageDB, UserPackageDB]
[GlobalPackageDB, SpecificPackageDB "package.conf.inplace"]

Note that the GlobalPackageDB is invariably at the bottom since it contains the rts, base and other special compiler-specific packages.

We are not restricted to using just the above combinations. In particular we can use several custom package dbs and the user package db together.

When it comes to writing, the top most (last) package is used.

data PackageDB :: *

Some compilers have a notion of a database of available packages. For some there is just one global db of packages, other compilers support a per-user or an arbitrary db specified at some location in the file system. This can be used to build isloated environments of packages, for example to build a collection of related packages without installing them globally.

Instances

Eq PackageDB 
Ord PackageDB 
Read PackageDB 
Show PackageDB 
Generic PackageDB 
Binary PackageDB 
type Rep PackageDB = D1 D1PackageDB ((:+:) (C1 C1_0PackageDB U1) ((:+:) (C1 C1_1PackageDB U1) (C1 C1_2PackageDB (S1 NoSelector (Rec0 FilePath))))) 

For internal/debugging 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)

crashGhcServer :: IdeSession -> Maybe Int -> IO () Source

Crash the GHC server. For debugging only. If the specified delay is Nothing, crash immediately; otherwise, set up a thread that throws an exception to the main thread after the delay.

sourceExtensions :: [FilePath]

Extensions of all source files we keep in our source directory.

ideBackendApiVersion :: Int

For detecting runtime version mismatch between the server and the library

We use a Unix timestamp for this so that these API versions have some semantics (http:/www.epochconverter.com, GMT).

buildLicsFromPkgs :: Bool -> LicenseArgs -> IO ExitCode Source

Build the concatenation of all license files from a given list of packages. See buildLicenses.

data LicenseArgs Source

Constructors

LicenseArgs 

Fields

liPackageDBStack :: PackageDBStack

3 fields from session configuration

liExtraPathDirs :: [FilePath]
 
liLicenseExc :: [String]
 
liDistDir :: FilePath

the working directory; the resulting file is written there

liStdoutLog :: FilePath
 
liStderrLog :: FilePath
 
licenseFixed :: [(String, (Maybe License, Maybe FilePath, Maybe String))]

see configLicenseFixed

liCabalsDir :: FilePath

the directory with all the .cabal files

liPkgs :: [PackageId]

the list of packages to process

Instances