ide-backend-0.10.0: An IDE backend library

Safe HaskellNone
LanguageHaskell2010

IdeSession.State

Contents

Description

Internal state of the session

This uses the internal types only.

Synopsis

Types

data Computed Source

Constructors

Computed 

Fields

computedErrors :: !(Strict [] SourceError)

Last compilation and run errors

computedLoadedModules :: !(Strict [] ModuleName)

Modules that got loaded okay

computedFileMap :: !(Strict (Map FilePath) ModuleId)

Mapping from filepaths to the modules they define

computedImports :: !(Strict (Map ModuleName) (Strict [] Import))

Import information. This is (usually) available even for modules with parsing or type errors

computedAutoMap :: !(Strict (Map ModuleName) (Strict Trie (Strict [] IdInfo)))

Autocompletion map

Mapping, per module, from prefixes to fully qualified names I.e., fo might map to Control.Monad.forM, Control.Monad.forM_ etc. (or possibly to M.forM, M.forM_, etc when Control.Monad was imported qualified as M).

computedSpanInfo :: !(Strict (Map ModuleName) IdMap)

Information about identifiers/quasi-quotes

computedExpTypes :: !(Strict (Map ModuleName) ExpMap)

Type information about subexpressions

computedUseSites :: !(Strict (Map ModuleName) UseSites)

Use sites

computedPkgDeps :: !(Strict (Map ModuleName) (Strict [] PackageId))

(Transitive) package dependencies

computedCache :: !ExplicitSharingCache

We access IdProps indirectly through this cache

Instances

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.

data IdeStaticInfo Source

Constructors

IdeStaticInfo 

Fields

ideConfig :: !SessionConfig

Configuration

ideSessionDir :: !FilePath

(Temporary) directory for session files

See also: * ideSessionSourceDir * ideSessionDataDir, * ideSessionDistDir

ideDistDir :: !FilePath
 

data IdeIdleState Source

Constructors

IdeIdleState 

Fields

_ideLogicalTimestamp :: !LogicalTimestamp

A workaround for http://hackage.haskell.org/trac/ghc/ticket/7473. Logical timestamps (used to force ghc to recompile files)

_ideComputed :: !(Strict Maybe Computed)

The result computed by the GHC API typing/compilation invocation in the last call to updateSession invocation.

_ideGhcOpts :: ![String]

Current GHC options

_ideRelativeIncludes :: ![FilePath]

Include paths (equivalent of GHC's -i parameter) relative to the temporary directory where we store the session's source files. The initial value, used also for server startup, is taken from configRelativeIncludes.

By default this is the singleton list [""] -- i.e., we include the sources dir (located there in simple setups, e.g., ide-backend tests) but nothing else.

_ideGenerateCode :: !Bool

Whether to generate code in addition to type-checking.

_ideManagedFiles :: !ManagedFilesInternal

Files submitted by the user and not deleted yet.

_ideObjectFiles :: !ObjectFiles

Object files created from .c files

_ideBuildExeStatus :: !(Maybe ExitCode)

Exit status of the last invocation of buildExe, if any.

_ideBuildDocStatus :: !(Maybe ExitCode)

Exit status of the last invocation of buildDoc, if any.

_ideBuildLicensesStatus :: !(Maybe ExitCode)

Exit status of the last invocation of buildDoc, if any.

_ideEnv :: ![(String, Maybe String)]

Environment overrides

_ideArgs :: ![String]

Command line arguments for snippets (expected value of getArgs)

_ideGhcServer :: GhcServer

The GHC server (this is replaced in restartSession)

_ideGhcVersion :: GhcVersion

GHC version

_ideStdoutBufferMode :: !RunBufferMode

Buffer mode for standard output for runStmt

_ideStderrBufferMode :: !RunBufferMode

Buffer mode for standard error for runStmt

_ideBreakInfo :: !(Strict Maybe BreakInfo)

Are we currently in a breakpoint?

_ideTargets :: !Targets

Targets for compilation

_ideRtsOpts :: [String]

RTS options (for the ghc session, not for executables)

data ManagedFilesInternal Source

The collection of source and data files submitted by the user.

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

Session callbacks. Currently this just configures how logging is handled.

Constructors

IdeCallbacks 

Accessors

To allow for non-server environments

ideSourceDir :: IdeStaticInfo -> FilePath Source

Get the directory that holds source files.

ideDataDir :: IdeStaticInfo -> FilePath Source

Get the directory that holds data files.

Callbacks

defaultIdeCallbacks :: IdeCallbacks Source

Default session configuration.

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

> defaultIdeCallbacks = IdeCallbacks
>  { ideCallbacksLogFunc = \_ _ _ _ -> return ()
>  }

ideLogFunc :: IdeSession -> LogFunc Source

Get the LogFunc for use with the functions in IdeSession.Util.Logger