ghcide-1.9.1.0: The core of an IDE
Safe HaskellSafe-Inferred
LanguageHaskell2010

Development.IDE.Core.Shake

Description

A Shake implementation of the compiler service.

There are two primary locations where data lives, and both of these contain much the same data:

  • The Shake database (inside $sel:shakeDb:IdeState) stores a map of shake keys to shake values. In our case, these are all of type Q to A. During a single run all the values in the Shake database are consistent so are used in conjunction with each other, e.g. in uses.
  • The Values type stores a map of keys to values. These values are always stored as real Haskell values, whereas Shake serialises all A values between runs. To deserialise a Shake value, we just consult Values.
Synopsis

Documentation

data IdeState Source #

A Shake database plus persistent store. Can be thought of as storing mappings from (FilePath, k) to RuleResult k.

Instances

Instances details
MonadReader (ReactorChan, IdeState) (ServerM c) Source # 
Instance details

Defined in Development.IDE.LSP.Server

shakeSessionInit :: Recorder (WithPriority Log) -> IdeState -> IO () Source #

Must be called in the Initialized handler and only once

data ShakeExtras Source #

Constructors

ShakeExtras 

Fields

Instances

Instances details
MonadReader ShakeExtras IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

type KnownTargets = HashMap Target (HashSet NormalizedFilePath) Source #

A mapping of module name to known files

data Target Source #

Instances

Instances details
Generic Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

Associated Types

type Rep Target :: Type -> Type #

Methods

from :: Target -> Rep Target x #

to :: Rep Target x -> Target #

Show Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

NFData Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

Methods

rnf :: Target -> () #

Eq Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

Methods

(==) :: Target -> Target -> Bool #

(/=) :: Target -> Target -> Bool #

Hashable Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

Methods

hashWithSalt :: Int -> Target -> Int #

hash :: Target -> Int #

type Rep Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

type Rep Target = D1 ('MetaData "Target" "Development.IDE.Types.KnownTargets" "ghcide-1.9.1.0-8JOWQPiUY1pHCotNfblyhi" 'False) (C1 ('MetaCons "TargetModule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName)) :+: C1 ('MetaCons "TargetFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NormalizedFilePath)))

type IdeRule k v = (RuleResult k ~ v, ShakeValue k, Show v, Typeable v, NFData v) Source #

type IdeResult v = ([FileDiagnostic], Maybe v) Source #

The result of an IDE operation. Warnings and errors are in the Diagnostic, and a value is in the Maybe. For operations that throw an error you expect a non-empty list of diagnostics, at least one of which is an error, and a Nothing. For operations that succeed you expect perhaps some warnings and a Just. For operations that depend on other failing operations you may get empty diagnostics and a Nothing, to indicate this phase throws no fresh errors but still failed.

A rule on a file should only return diagnostics for that given file. It should not propagate diagnostic errors through multiple phases.

newtype GetModificationTime Source #

Constructors

GetModificationTime_ 

Fields

Bundled Patterns

pattern GetModificationTime :: GetModificationTime 

Instances

Instances details
Generic GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetModificationTime :: Type -> Type #

Show GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetModificationTime -> () #

Eq GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Hashable GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetModificationTime = D1 ('MetaData "GetModificationTime" "Development.IDE.Core.RuleTypes" "ghcide-1.9.1.0-8JOWQPiUY1pHCotNfblyhi" 'True) (C1 ('MetaCons "GetModificationTime_" 'PrefixI 'True) (S1 ('MetaSel ('Just "missingFileDiagnostics") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))
type RuleResult GetModificationTime Source #

Get the modification time of a file.

Instance details

Defined in Development.IDE.Core.RuleTypes

shakeEnqueue :: ShakeExtras -> DelayedAction a -> IO (IO a) Source #

Enqueue an action in the existing ShakeSession. Returns a computation to block until the action is run, propagating exceptions. Assumes a ShakeSession is available.

Appropriate for user actions other than edits.

newSession :: Recorder (WithPriority Log) -> ShakeExtras -> VFSModified -> ShakeDatabase -> [DelayedActionInternal] -> String -> IO ShakeSession Source #

Set up a new ShakeSession with a set of initial actions Will crash if there is an existing ShakeSession running.

use :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe v) Source #

Request a Rule result if available

useNoFile :: IdeRule k v => k -> Action (Maybe v) Source #

uses :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (Maybe v)) Source #

Plural version of use

useWithStaleFast :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping)) Source #

Lookup value in the database and return with the stale value immediately Will queue an action to refresh the value. Might block the first time the rule runs, but never blocks after that.

useWithStaleFast' :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (FastResult v) Source #

Same as useWithStaleFast but lets you wait for an up to date result

delayedAction :: DelayedAction a -> IdeAction (IO a) Source #

These actions are run asynchronously after the current action is finished running. For example, to trigger a key build after a rule has already finished as is the case with useWithStaleFast

data FastResult a Source #

A (maybe) stale result now, and an up to date one later

Constructors

FastResult 

Fields

useNoFile_ :: IdeRule k v => k -> Action v Source #

uses_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f v) Source #

useWithStale :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping)) Source #

Request a Rule result, it not available return the last computed result, if any, which may be stale

usesWithStale :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (Maybe (v, PositionMapping))) Source #

Return the last computed result which might be stale.

useWithStale_ :: IdeRule k v => k -> NormalizedFilePath -> Action (v, PositionMapping) Source #

Request a Rule result, it not available return the last computed result which may be stale. Errors out if none available.

newtype BadDependency Source #

When we depend on something that reported an error, and we fail as a direct result, throw BadDependency which short-circuits the rest of the action

Constructors

BadDependency String 

define :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules () Source #

Define a new Rule without early cutoff

defineEarlyCutoff :: IdeRule k v => Recorder (WithPriority Log) -> RuleBody k v -> Rules () Source #

Define a new Rule with early cutoff

mRunLspT :: Applicative m => Maybe (LanguageContextEnv c) -> LspT c m () -> m () Source #

mRunLspTCallback :: Monad m => Maybe (LanguageContextEnv c) -> (LspT c m a -> LspT c m a) -> m a -> m a Source #

newtype GlobalIdeOptions Source #

Instances

Instances details
IsIdeGlobal GlobalIdeOptions Source # 
Instance details

Defined in Development.IDE.Core.Shake

getClientConfig :: MonadLsp Config m => m Config #

Returns the current client configuration. It is not wise to permanently cache the returned value of this function, as clients can at runtime change their configuration.

knownTargets :: Action (Hashed KnownTargets) Source #

Get all the files in the project

getVirtualFile :: NormalizedFilePath -> Action (Maybe VirtualFile) Source #

Read a virtual file from the current snapshot

data FileVersion Source #

Either the mtime from disk or an LSP version LSP versions always compare as greater than on disk versions

Instances

Instances details
Generic FileVersion Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep FileVersion :: Type -> Type #

Show FileVersion Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData FileVersion Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: FileVersion -> () #

Eq FileVersion Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Ord FileVersion Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep FileVersion Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep FileVersion = D1 ('MetaData "FileVersion" "Development.IDE.Core.RuleTypes" "ghcide-1.9.1.0-8JOWQPiUY1pHCotNfblyhi" 'False) (C1 ('MetaCons "ModificationTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 POSIXTime)) :+: C1 ('MetaCons "VFSVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32)))

newtype Priority Source #

Constructors

Priority Double 

deleteValue :: ShakeValue k => ShakeExtras -> k -> NormalizedFilePath -> STM () Source #

Delete the value stored for a given ide build key

type WithProgressFunc = forall a. Text -> ProgressCancellable -> ((ProgressAmount -> IO ()) -> IO a) -> IO a Source #

data DelayedAction a Source #

Instances

Instances details
Functor DelayedAction Source # 
Instance details

Defined in Development.IDE.Types.Action

Methods

fmap :: (a -> b) -> DelayedAction a -> DelayedAction b #

(<$) :: a -> DelayedAction b -> DelayedAction a #

Show (DelayedAction a) Source # 
Instance details

Defined in Development.IDE.Types.Action

Eq (DelayedAction a) Source # 
Instance details

Defined in Development.IDE.Types.Action

Hashable (DelayedAction a) Source # 
Instance details

Defined in Development.IDE.Types.Action

newtype IdeAction a Source #

IdeActions are used when we want to return a result immediately, even if it is stale Useful for UI actions like hover, completion where we don't want to block.

Run via runIdeAction.

Constructors

IdeAction 

Instances

Instances details
MonadIO IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

liftIO :: IO a -> IdeAction a #

Applicative IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

pure :: a -> IdeAction a #

(<*>) :: IdeAction (a -> b) -> IdeAction a -> IdeAction b #

liftA2 :: (a -> b -> c) -> IdeAction a -> IdeAction b -> IdeAction c #

(*>) :: IdeAction a -> IdeAction b -> IdeAction b #

(<*) :: IdeAction a -> IdeAction b -> IdeAction a #

Functor IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

fmap :: (a -> b) -> IdeAction a -> IdeAction b #

(<$) :: a -> IdeAction b -> IdeAction a #

Monad IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

(>>=) :: IdeAction a -> (a -> IdeAction b) -> IdeAction b #

(>>) :: IdeAction a -> IdeAction b -> IdeAction b #

return :: a -> IdeAction a #

MonadReader ShakeExtras IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

newtype Q k Source #

Constructors

Q (k, NormalizedFilePath) 

Instances

Instances details
Show k => Show (Q k) Source # 
Instance details

Defined in Development.IDE.Types.Shake

Methods

showsPrec :: Int -> Q k -> ShowS #

show :: Q k -> String #

showList :: [Q k] -> ShowS #

NFData k => NFData (Q k) Source # 
Instance details

Defined in Development.IDE.Types.Shake

Methods

rnf :: Q k -> () #

Eq k => Eq (Q k) Source # 
Instance details

Defined in Development.IDE.Types.Shake

Methods

(==) :: Q k -> Q k -> Bool #

(/=) :: Q k -> Q k -> Bool #

Hashable k => Hashable (Q k) Source # 
Instance details

Defined in Development.IDE.Types.Shake

Methods

hashWithSalt :: Int -> Q k -> Int #

hash :: Q k -> Int #

type RuleResult (Q k) Source # 
Instance details

Defined in Development.IDE.Types.Shake

type RuleResult (Q k) = A (RuleResult k)

type IndexQueue = TQueue (((HieDb -> IO ()) -> IO ()) -> IO ()) Source #

Actions to queue up on the index worker thread The inner `(HieDb -> IO ()) -> IO ()` wraps `HieDb -> IO ()` with (currently) retry functionality

data HieDb #

data HieDbWriter Source #

We need to serialize writes to the database, so we send any function that needs to write to the database over the channel, where it will be picked up by a worker thread.

Constructors

HieDbWriter 

Fields

addPersistentRule :: IdeRule k v => k -> (NormalizedFilePath -> IdeAction (Maybe (v, PositionDelta, TextDocumentVersion))) -> Rules () Source #

Register a function that will be called to get the "stale" result of a rule, possibly from disk This is called when we don't already have a result, or computing the rule failed. The result of this function will always be marked as $sel:stale:FastResult, and a proper rebuild of the rule will be queued if the rule hasn't run before.

garbageCollectDirtyKeys :: Action [Key] Source #

Find and release old keys from the state Hashmap For the record, there are other state sources that this process does not release: * diagnostics store (normal, hidden and published) * position mapping store * indexing queue * exports map

getClientConfigAction :: Action Config Source #

Returns the client configuration, creating a build dependency. You should always use this function when accessing client configuration from build rules.