ghcide-1.0.0.0: The core of an IDE
Safe HaskellNone
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 shakeDb) 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.

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 [NormalizedFilePath] Source #

A mapping of module name to known files

data Target Source #

Instances

Instances details
Eq Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

Methods

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

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

Show Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

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 #

Hashable Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

Methods

hashWithSalt :: Int -> Target -> Int #

hash :: Target -> Int #

NFData Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

Methods

rnf :: Target -> () #

type Rep Target Source # 
Instance details

Defined in Development.IDE.Types.KnownTargets

type Rep Target = D1 ('MetaData "Target" "Development.IDE.Types.KnownTargets" "ghcide-1.0.0.0-L6DikjZcyrRHdytkRlGwfF" '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.

data GetModificationTime Source #

Constructors

GetModificationTime_ 

Fields

Bundled Patterns

pattern GetModificationTime :: GetModificationTime 

Instances

Instances details
Eq GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Show GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep GetModificationTime :: Type -> Type #

Hashable GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Binary GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

NFData GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: GetModificationTime -> () #

type Rep GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep GetModificationTime = D1 ('MetaData "GetModificationTime" "Development.IDE.Core.RuleTypes" "ghcide-1.0.0.0-L6DikjZcyrRHdytkRlGwfF" 'False) (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

shakeRestart :: IdeState -> [DelayedAction ()] -> IO () Source #

Restart the current ShakeSession with the given system actions. Any actions running in the current session will be aborted, but actions added via shakeEnqueue will be requeued.

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.

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 :: IdeRule k v => k -> [NormalizedFilePath] -> Action [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_ :: IdeRule k v => k -> [NormalizedFilePath] -> Action [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 :: IdeRule k v => k -> [NormalizedFilePath] -> Action [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 => (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules () Source #

Define a new Rule without early cutoff

defineEarlyCutoff :: IdeRule k v => (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult 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 #

class Typeable a => IsIdeGlobal a Source #

Instances

Instances details
IsIdeGlobal GlobalIdeOptions Source # 
Instance details

Defined in Development.IDE.Core.Shake

IsIdeGlobal VFSHandle Source # 
Instance details

Defined in Development.IDE.Core.Shake

IsIdeGlobal CompiledLinkables Source # 
Instance details

Defined in Development.IDE.Core.Rules

newtype GlobalIdeOptions Source #

Instances

Instances details
IsIdeGlobal GlobalIdeOptions Source # 
Instance details

Defined in Development.IDE.Core.Shake

garbageCollect :: (NormalizedFilePath -> Bool) -> Action () Source #

Clear the results for all files that do not match the given predicate.

knownTargets :: Action (Hashed KnownTargets) Source #

Get all the files in the project

data FileVersion Source #

Constructors

VFSVersion !Int 
ModificationTime 

Fields

  • !Int64

    Large unit (platform dependent, do not make assumptions)

  • !Int64

    Small unit (platform dependent, do not make assumptions)

Instances

Instances details
Show FileVersion Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Generic FileVersion Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Associated Types

type Rep FileVersion :: Type -> Type #

NFData FileVersion Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

Methods

rnf :: FileVersion -> () #

type Rep FileVersion Source # 
Instance details

Defined in Development.IDE.Core.RuleTypes

type Rep FileVersion = D1 ('MetaData "FileVersion" "Development.IDE.Core.RuleTypes" "ghcide-1.0.0.0-L6DikjZcyrRHdytkRlGwfF" 'False) (C1 ('MetaCons "VFSVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "ModificationTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64)))

newtype Priority Source #

Constructors

Priority Double 

deleteValue :: (Typeable k, Hashable k, Eq k, Show k) => IdeState -> k -> NormalizedFilePath -> IO () 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 #

Eq (DelayedAction a) Source # 
Instance details

Defined in Development.IDE.Types.Action

Show (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 #

Constructors

IdeAction 

Instances

Instances details
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 #

Functor IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

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

(<$) :: a -> IdeAction b -> 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 #

MonadIO IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

liftIO :: IO a -> IdeAction a #

MonadReader ShakeExtras IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO 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.

newtype Q k Source #

Constructors

Q (k, NormalizedFilePath) 

Instances

Instances details
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 #

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 #

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

Defined in Development.IDE.Types.Shake

Methods

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

hash :: Q k -> Int #

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

Defined in Development.IDE.Types.Shake

Methods

put :: Q k -> Put #

get :: Get (Q k) #

putList :: [Q k] -> Put #

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

Defined in Development.IDE.Types.Shake

Methods

rnf :: Q k -> () #

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 ()) Source #

Actions to queue up on the index worker thread

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

data VFSHandle Source #

haskell-lsp manages the VFS internally and automatically so we cannot use the builtin VFS without spawning up an LSP server. To be able to test things like setBufferModified we abstract over the VFS implementation.

Constructors

VFSHandle 

Fields

Instances

Instances details
IsIdeGlobal VFSHandle Source # 
Instance details

Defined in Development.IDE.Core.Shake

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 stale, and a proper rebuild of the rule will be queued if the rule hasn't run before.