Safe Haskell | None |
---|---|
Language | GHC2021 |
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
shakeDb
) stores a map of shake keys to shake values. In our case, these are all of typeQ
toA
. During a single run all the values in the Shake database are consistent so are used in conjunction with each other, e.g. inuses
. - The
Values
type stores a map of keys to values. These values are always stored as real Haskell values, whereas Shake serialises allA
values between runs. To deserialise a Shake value, we just consult Values.
Synopsis
- data IdeState
- shakeSessionInit :: Recorder (WithPriority Log) -> IdeState -> IO ()
- shakeExtras :: IdeState -> ShakeExtras
- shakeDb :: IdeState -> ShakeDatabase
- data ShakeExtras = ShakeExtras {
- lspEnv :: Maybe (LanguageContextEnv Config)
- debouncer :: Debouncer NormalizedUri
- logger :: Logger
- idePlugins :: IdePlugins IdeState
- globals :: TVar (HashMap TypeRep Dynamic)
- state :: Values
- diagnostics :: STMDiagnosticStore
- hiddenDiagnostics :: STMDiagnosticStore
- publishedDiagnostics :: Map NormalizedUri [Diagnostic]
- semanticTokensCache :: Map NormalizedFilePath SemanticTokens
- semanticTokensId :: TVar Int
- positionMapping :: Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
- progress :: ProgressReporting
- ideTesting :: IdeTesting
- restartShakeSession :: VFSModified -> String -> [DelayedAction ()] -> IO ()
- ideNc :: NameCache
- knownTargetsVar :: TVar (Hashed KnownTargets)
- exportsMap :: TVar ExportsMap
- actionQueue :: ActionQueue
- clientCapabilities :: ClientCapabilities
- withHieDb :: WithHieDb
- hiedbWriter :: HieDbWriter
- persistentKeys :: TVar (KeyMap GetStalePersistent)
- vfsVar :: TVar VFS
- defaultConfig :: Config
- dirtyKeys :: TVar KeySet
- getShakeExtras :: Action ShakeExtras
- getShakeExtrasRules :: Rules ShakeExtras
- type KnownTargets = HashMap Target (HashSet NormalizedFilePath)
- data Target
- toKnownFiles :: KnownTargets -> HashSet NormalizedFilePath
- type IdeRule k v = (RuleResult k ~ v, ShakeValue k, Show v, Typeable v, NFData v)
- type IdeResult v = ([FileDiagnostic], Maybe v)
- newtype GetModificationTime where
- GetModificationTime_ { }
- pattern GetModificationTime :: GetModificationTime
- shakeOpen :: Recorder (WithPriority Log) -> Maybe (LanguageContextEnv Config) -> Config -> IdePlugins IdeState -> Logger -> Debouncer NormalizedUri -> Maybe FilePath -> IdeReportProgress -> IdeTesting -> WithHieDb -> IndexQueue -> ShakeOptions -> Monitoring -> Rules () -> IO IdeState
- shakeShut :: IdeState -> IO ()
- shakeEnqueue :: ShakeExtras -> DelayedAction a -> IO (IO a)
- newSession :: Recorder (WithPriority Log) -> ShakeExtras -> VFSModified -> ShakeDatabase -> [DelayedActionInternal] -> String -> IO ShakeSession
- use :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe v)
- useNoFile :: IdeRule k v => k -> Action (Maybe v)
- uses :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (Maybe v))
- useWithStaleFast :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping))
- useWithStaleFast' :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (FastResult v)
- delayedAction :: DelayedAction a -> IdeAction (IO a)
- data FastResult a = FastResult {}
- use_ :: IdeRule k v => k -> NormalizedFilePath -> Action v
- useNoFile_ :: IdeRule k v => k -> Action v
- uses_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f v)
- useWithStale :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
- usesWithStale :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (Maybe (v, PositionMapping)))
- useWithStale_ :: IdeRule k v => k -> NormalizedFilePath -> Action (v, PositionMapping)
- usesWithStale_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (v, PositionMapping))
- newtype BadDependency = BadDependency String
- data RuleBody k v
- = Rule (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v))
- | RuleNoDiagnostics (k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
- | RuleWithCustomNewnessCheck {
- newnessCheck :: ByteString -> ByteString -> Bool
- build :: k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)
- | RuleWithOldValue (k -> NormalizedFilePath -> Value v -> Action (Maybe ByteString, IdeResult v))
- define :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules ()
- defineNoDiagnostics :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules ()
- defineEarlyCutoff :: IdeRule k v => Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
- defineNoFile :: IdeRule k v => Recorder (WithPriority Log) -> (k -> Action v) -> Rules ()
- defineEarlyCutOffNoFile :: IdeRule k v => Recorder (WithPriority Log) -> (k -> Action (ByteString, v)) -> Rules ()
- getDiagnostics :: IdeState -> STM [FileDiagnostic]
- mRunLspT :: Applicative m => Maybe (LanguageContextEnv c) -> LspT c m () -> m ()
- mRunLspTCallback :: Monad m => Maybe (LanguageContextEnv c) -> (LspT c m a -> LspT c m a) -> m a -> m a
- getHiddenDiagnostics :: IdeState -> STM [FileDiagnostic]
- class Typeable a => IsIdeGlobal (a :: k)
- addIdeGlobal :: IsIdeGlobal a => a -> Rules ()
- addIdeGlobalExtras :: IsIdeGlobal a => ShakeExtras -> a -> IO ()
- getIdeGlobalState :: IsIdeGlobal a => IdeState -> IO a
- getIdeGlobalAction :: (HasCallStack, IsIdeGlobal a) => Action a
- getIdeGlobalExtras :: (HasCallStack, IsIdeGlobal a) => ShakeExtras -> IO a
- getIdeOptions :: Action IdeOptions
- getIdeOptionsIO :: ShakeExtras -> IO IdeOptions
- newtype GlobalIdeOptions = GlobalIdeOptions IdeOptions
- getClientConfig :: MonadLsp Config m => m Config
- getPluginConfigAction :: PluginId -> Action PluginConfig
- knownTargets :: Action (Hashed KnownTargets)
- setPriority :: Priority -> Action ()
- ideLogger :: IdeState -> Logger
- actionLogger :: Action Logger
- getVirtualFile :: NormalizedFilePath -> Action (Maybe VirtualFile)
- data FileVersion
- newtype Priority = Priority Double
- updatePositionMapping :: IdeState -> VersionedTextDocumentIdentifier -> [TextDocumentContentChangeEvent] -> STM ()
- updatePositionMappingHelper :: Int32 -> [TextDocumentContentChangeEvent] -> EnumMap Int32 (PositionDelta, PositionMapping) -> EnumMap Int32 (PositionDelta, PositionMapping)
- deleteValue :: ShakeValue k => ShakeExtras -> k -> NormalizedFilePath -> STM ()
- recordDirtyKeys :: ShakeValue k => ShakeExtras -> k -> [NormalizedFilePath] -> STM (IO ())
- type WithProgressFunc = forall a. Text -> ProgressCancellable -> ((ProgressAmount -> IO ()) -> IO a) -> IO a
- type WithIndefiniteProgressFunc = forall a. Text -> ProgressCancellable -> IO a -> IO a
- data ProgressEvent
- data DelayedAction a
- mkDelayedAction :: String -> Priority -> Action a -> DelayedAction a
- newtype IdeAction a = IdeAction {}
- runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a
- mkUpdater :: NameCache -> NameCacheUpdater
- newtype Q k = Q (k, NormalizedFilePath)
- type IndexQueue = TQueue (((HieDb -> IO ()) -> IO ()) -> IO ())
- data HieDb
- data HieDbWriter = HieDbWriter {
- indexQueue :: IndexQueue
- indexPending :: TVar (HashMap NormalizedFilePath Fingerprint)
- indexCompleted :: TVar Int
- indexProgressToken :: Var (Maybe ProgressToken)
- addPersistentRule :: IdeRule k v => k -> (NormalizedFilePath -> IdeAction (Maybe (v, PositionDelta, Maybe Int32))) -> Rules ()
- garbageCollectDirtyKeys :: Action [Key]
- garbageCollectDirtyKeysOlderThan :: Int -> CheckParents -> Action [Key]
- data Log
- = LogCreateHieDbExportsMapStart
- | LogCreateHieDbExportsMapFinish !Int
- | LogBuildSessionRestart !String ![DelayedActionInternal] !KeySet !Seconds !(Maybe FilePath)
- | LogBuildSessionRestartTakingTooLong !Seconds
- | LogDelayedAction !(DelayedAction ()) !Seconds
- | LogBuildSessionFinish !(Maybe SomeException)
- | LogDiagsDiffButNoLspEnv ![FileDiagnostic]
- | LogDefineEarlyCutoffRuleNoDiagHasDiag !FileDiagnostic
- | LogDefineEarlyCutoffRuleCustomNewnessHasDiag !FileDiagnostic
- data VFSModified
- getClientConfigAction :: Action Config
Documentation
A Shake database plus persistent store. Can be thought of as storing
mappings from (FilePath, k)
to RuleResult k
.
Instances
MonadReader (ReactorChan, IdeState) (ServerM c) # | |
Defined in Development.IDE.LSP.Server Methods ask :: ServerM c (ReactorChan, IdeState) # local :: ((ReactorChan, IdeState) -> (ReactorChan, IdeState)) -> ServerM c a -> ServerM c a # reader :: ((ReactorChan, IdeState) -> a) -> ServerM c a # |
shakeSessionInit :: Recorder (WithPriority Log) -> IdeState -> IO () #
Must be called in the Initialized
handler and only once
shakeExtras :: IdeState -> ShakeExtras #
shakeDb :: IdeState -> ShakeDatabase #
data ShakeExtras #
Constructors
ShakeExtras | |
Fields
|
Instances
MonadReader ShakeExtras IdeAction # | |
Defined in Development.IDE.Core.Shake Methods ask :: IdeAction ShakeExtras # local :: (ShakeExtras -> ShakeExtras) -> IdeAction a -> IdeAction a # reader :: (ShakeExtras -> a) -> IdeAction a # |
type KnownTargets = HashMap Target (HashSet NormalizedFilePath) #
A mapping of module name to known files
Constructors
TargetModule ModuleName | |
TargetFile NormalizedFilePath |
Instances
type IdeRule k v = (RuleResult k ~ v, ShakeValue k, Show v, Typeable v, NFData v) #
type IdeResult v = ([FileDiagnostic], Maybe v) #
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 #
Constructors
GetModificationTime_ | |
Fields
|
Bundled Patterns
pattern GetModificationTime :: GetModificationTime |
Instances
Generic GetModificationTime # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
Methods from :: GetModificationTime -> Rep GetModificationTime x # to :: Rep GetModificationTime x -> GetModificationTime # | |||||
Show GetModificationTime # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> GetModificationTime -> ShowS # show :: GetModificationTime -> String # showList :: [GetModificationTime] -> ShowS # | |||||
NFData GetModificationTime # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: GetModificationTime -> () # | |||||
Eq GetModificationTime # | |||||
Defined in Development.IDE.Core.RuleTypes Methods (==) :: GetModificationTime -> GetModificationTime -> Bool # (/=) :: GetModificationTime -> GetModificationTime -> Bool # | |||||
Hashable GetModificationTime # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
type Rep GetModificationTime # | |||||
Defined in Development.IDE.Core.RuleTypes type Rep GetModificationTime = D1 ('MetaData "GetModificationTime" "Development.IDE.Core.RuleTypes" "ghcide-2.7.0.0-4RFlm38cSV494413rRqzNs" 'True) (C1 ('MetaCons "GetModificationTime_" 'PrefixI 'True) (S1 ('MetaSel ('Just "missingFileDiagnostics") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) | |||||
type RuleResult GetModificationTime # | Get the modification time of a file. | ||||
Defined in Development.IDE.Core.RuleTypes |
shakeOpen :: Recorder (WithPriority Log) -> Maybe (LanguageContextEnv Config) -> Config -> IdePlugins IdeState -> Logger -> Debouncer NormalizedUri -> Maybe FilePath -> IdeReportProgress -> IdeTesting -> WithHieDb -> IndexQueue -> ShakeOptions -> Monitoring -> Rules () -> IO IdeState #
shakeEnqueue :: ShakeExtras -> DelayedAction a -> IO (IO a) #
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 #
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) #
Request a Rule result if available
uses :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (Maybe v)) #
Plural version of use
useWithStaleFast :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping)) #
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) #
Same as useWithStaleFast but lets you wait for an up to date result
delayedAction :: DelayedAction a -> IdeAction (IO a) #
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
use_ :: IdeRule k v => k -> NormalizedFilePath -> Action v #
useNoFile_ :: IdeRule k v => k -> Action v #
uses_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f v) #
Plural version of use_
Throws an BadDependency
exception which is caught by the rule system if
none available.
WARNING: Not suitable for PluginHandlers. Use usesE
instead.
useWithStale :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping)) #
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))) #
Return the last computed result which might be stale.
useWithStale_ :: IdeRule k v => k -> NormalizedFilePath -> Action (v, PositionMapping) #
Request a Rule result, it not available return the last computed result which may be stale.
Throws an BadDependency
exception which is caught by the rule system if
none available.
WARNING: Not suitable for PluginHandlers. Use useWithStaleE
instead.
usesWithStale_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (v, PositionMapping)) #
Plural version of useWithStale_
Throws an BadDependency
exception which is caught by the rule system if
none available.
WARNING: Not suitable for PluginHandlers.
newtype BadDependency #
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 |
Instances
Exception BadDependency # | |
Defined in Development.IDE.Types.Shake Methods toException :: BadDependency -> SomeException # fromException :: SomeException -> Maybe BadDependency # displayException :: BadDependency -> String # | |
Show BadDependency # | |
Defined in Development.IDE.Types.Shake Methods showsPrec :: Int -> BadDependency -> ShowS # show :: BadDependency -> String # showList :: [BadDependency] -> ShowS # |
Constructors
Rule (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v)) | |
RuleNoDiagnostics (k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)) | |
RuleWithCustomNewnessCheck | |
Fields
| |
RuleWithOldValue (k -> NormalizedFilePath -> Value v -> Action (Maybe ByteString, IdeResult v)) |
define :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules () #
Define a new Rule without early cutoff
defineNoDiagnostics :: IdeRule k v => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules () #
defineEarlyCutoff :: IdeRule k v => Recorder (WithPriority Log) -> RuleBody k v -> Rules () #
Define a new Rule with early cutoff
defineNoFile :: IdeRule k v => Recorder (WithPriority Log) -> (k -> Action v) -> Rules () #
defineEarlyCutOffNoFile :: IdeRule k v => Recorder (WithPriority Log) -> (k -> Action (ByteString, v)) -> Rules () #
getDiagnostics :: IdeState -> STM [FileDiagnostic] #
mRunLspT :: Applicative m => Maybe (LanguageContextEnv c) -> LspT c m () -> m () #
mRunLspTCallback :: Monad m => Maybe (LanguageContextEnv c) -> (LspT c m a -> LspT c m a) -> m a -> m a #
getHiddenDiagnostics :: IdeState -> STM [FileDiagnostic] #
class Typeable a => IsIdeGlobal (a :: k) #
Instances
IsIdeGlobal OfInterestVar # | |
Defined in Development.IDE.Core.OfInterest | |
IsIdeGlobal CompiledLinkables # | |
Defined in Development.IDE.Core.Rules | |
IsIdeGlobal DisplayTHWarning # | |
Defined in Development.IDE.Core.Rules | |
IsIdeGlobal GlobalIdeOptions # | |
Defined in Development.IDE.Core.Shake |
addIdeGlobal :: IsIdeGlobal a => a -> Rules () #
addIdeGlobalExtras :: IsIdeGlobal a => ShakeExtras -> a -> IO () #
getIdeGlobalState :: IsIdeGlobal a => IdeState -> IO a #
getIdeGlobalAction :: (HasCallStack, IsIdeGlobal a) => Action a #
getIdeGlobalExtras :: (HasCallStack, IsIdeGlobal a) => ShakeExtras -> IO a #
getIdeOptionsIO :: ShakeExtras -> IO IdeOptions #
newtype GlobalIdeOptions #
Constructors
GlobalIdeOptions IdeOptions |
Instances
IsIdeGlobal GlobalIdeOptions # | |
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) #
Get all the files in the project
setPriority :: Priority -> Action () #
getVirtualFile :: NormalizedFilePath -> Action (Maybe VirtualFile) #
Read a virtual file from the current snapshot
data FileVersion #
Either the mtime from disk or an LSP version LSP versions always compare as greater than on disk versions
Constructors
ModificationTime !POSIXTime | |
VFSVersion !Int32 |
Instances
Generic FileVersion # | |||||
Defined in Development.IDE.Core.RuleTypes Associated Types
| |||||
Show FileVersion # | |||||
Defined in Development.IDE.Core.RuleTypes Methods showsPrec :: Int -> FileVersion -> ShowS # show :: FileVersion -> String # showList :: [FileVersion] -> ShowS # | |||||
NFData FileVersion # | |||||
Defined in Development.IDE.Core.RuleTypes Methods rnf :: FileVersion -> () # | |||||
Eq FileVersion # | |||||
Defined in Development.IDE.Core.RuleTypes | |||||
Ord FileVersion # | |||||
Defined in Development.IDE.Core.RuleTypes Methods compare :: FileVersion -> FileVersion -> Ordering # (<) :: FileVersion -> FileVersion -> Bool # (<=) :: FileVersion -> FileVersion -> Bool # (>) :: FileVersion -> FileVersion -> Bool # (>=) :: FileVersion -> FileVersion -> Bool # max :: FileVersion -> FileVersion -> FileVersion # min :: FileVersion -> FileVersion -> FileVersion # | |||||
type Rep FileVersion # | |||||
Defined in Development.IDE.Core.RuleTypes type Rep FileVersion = D1 ('MetaData "FileVersion" "Development.IDE.Core.RuleTypes" "ghcide-2.7.0.0-4RFlm38cSV494413rRqzNs" '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))) |
updatePositionMapping :: IdeState -> VersionedTextDocumentIdentifier -> [TextDocumentContentChangeEvent] -> STM () #
updatePositionMappingHelper :: Int32 -> [TextDocumentContentChangeEvent] -> EnumMap Int32 (PositionDelta, PositionMapping) -> EnumMap Int32 (PositionDelta, PositionMapping) #
deleteValue :: ShakeValue k => ShakeExtras -> k -> NormalizedFilePath -> STM () #
Delete the value stored for a given ide build key
recordDirtyKeys :: ShakeValue k => ShakeExtras -> k -> [NormalizedFilePath] -> STM (IO ()) #
type WithProgressFunc = forall a. Text -> ProgressCancellable -> ((ProgressAmount -> IO ()) -> IO a) -> IO a #
type WithIndefiniteProgressFunc = forall a. Text -> ProgressCancellable -> IO a -> IO a #
data ProgressEvent #
Constructors
KickStarted | |
KickCompleted |
data DelayedAction a #
Instances
Functor DelayedAction # | |
Defined in Development.IDE.Types.Action Methods fmap :: (a -> b) -> DelayedAction a -> DelayedAction b # (<$) :: a -> DelayedAction b -> DelayedAction a # | |
Show (DelayedAction a) # | |
Defined in Development.IDE.Types.Action Methods showsPrec :: Int -> DelayedAction a -> ShowS # show :: DelayedAction a -> String # showList :: [DelayedAction a] -> ShowS # | |
Eq (DelayedAction a) # | |
Defined in Development.IDE.Types.Action Methods (==) :: DelayedAction a -> DelayedAction a -> Bool # (/=) :: DelayedAction a -> DelayedAction a -> Bool # | |
Hashable (DelayedAction a) # | |
Defined in Development.IDE.Types.Action |
mkDelayedAction :: String -> Priority -> Action a -> DelayedAction a #
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 | |
Fields |
Instances
MonadIO IdeAction # | |
Defined in Development.IDE.Core.Shake | |
Applicative IdeAction # | |
Defined in Development.IDE.Core.Shake | |
Functor IdeAction # | |
Monad IdeAction # | |
MonadReader ShakeExtras IdeAction # | |
Defined in Development.IDE.Core.Shake Methods ask :: IdeAction ShakeExtras # local :: (ShakeExtras -> ShakeExtras) -> IdeAction a -> IdeAction a # reader :: (ShakeExtras -> a) -> IdeAction a # | |
Semigroup a => Semigroup (IdeAction a) # | |
runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a #
mkUpdater :: NameCache -> NameCacheUpdater #
Constructors
Q (k, NormalizedFilePath) |
type IndexQueue = TQueue (((HieDb -> IO ()) -> IO ()) -> IO ()) #
Actions to queue up on the index worker thread The inner `(HieDb -> IO ()) -> IO ()` wraps `HieDb -> IO ()` with (currently) retry functionality
data HieDbWriter #
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, Maybe Int32))) -> Rules () #
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 stale
, and a proper
rebuild of the rule will
be queued if the rule hasn't run before.
garbageCollectDirtyKeys :: Action [Key] #
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
garbageCollectDirtyKeysOlderThan :: Int -> CheckParents -> Action [Key] #
Constructors
LogCreateHieDbExportsMapStart | |
LogCreateHieDbExportsMapFinish !Int | |
LogBuildSessionRestart !String ![DelayedActionInternal] !KeySet !Seconds !(Maybe FilePath) | |
LogBuildSessionRestartTakingTooLong !Seconds | |
LogDelayedAction !(DelayedAction ()) !Seconds | |
LogBuildSessionFinish !(Maybe SomeException) | |
LogDiagsDiffButNoLspEnv ![FileDiagnostic] | |
LogDefineEarlyCutoffRuleNoDiagHasDiag !FileDiagnostic | |
LogDefineEarlyCutoffRuleCustomNewnessHasDiag !FileDiagnostic |
data VFSModified #
Constructors
VFSUnmodified | |
VFSModified !VFS |
getClientConfigAction :: Action Config #
Returns the client configuration, creating a build dependency. You should always use this function when accessing client configuration from build rules.