ghcide-0.2.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

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

data GetModificationTime Source #

Constructors

GetModificationTime 
Instances
Eq GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

Show GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

Generic GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

Associated Types

type Rep GetModificationTime :: Type -> Type #

Hashable GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

Binary GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

NFData GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

rnf :: GetModificationTime -> () #

type Rep GetModificationTime Source # 
Instance details

Defined in Development.IDE.Core.Shake

type Rep GetModificationTime = D1 (MetaData "GetModificationTime" "Development.IDE.Core.Shake" "ghcide-0.2.0-HKsdlJpUfsj7QU2D2Ij409" False) (C1 (MetaCons "GetModificationTime" PrefixI False) (U1 :: Type -> Type))
type RuleResult GetModificationTime Source #

Get the modification time of a file.

Instance details

Defined in Development.IDE.Core.Shake

shakeOpen Source #

Arguments

:: IO LspId 
-> (FromServerMessage -> IO ())

diagnostic handler

-> Logger 
-> Debouncer NormalizedUri 
-> Maybe FilePath 
-> IdeReportProgress 
-> ShakeOptions 
-> Rules () 
-> IO IdeState 

Open a IdeState, should be shut using shakeShut.

shakeRun :: IdeState -> [Action a] -> IO (IO [a]) Source #

Spawn immediately. If you are already inside a call to shakeRun that will be aborted with an exception.

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

uses :: IdeRule k v => k -> [NormalizedFilePath] -> Action [Maybe v] Source #

Return up2date results. Stale results will be ignored.

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

Return the last computed result which might be stale.

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

uses_ :: IdeRule k v => k -> [NormalizedFilePath] -> Action [v] Source #

unsafeClearDiagnostics :: IdeState -> IO () Source #

FIXME: This function is temporary! Only required because the files of interest doesn't work

class Typeable a => IsIdeGlobal a Source #

Instances
IsIdeGlobal VFSHandle Source # 
Instance details

Defined in Development.IDE.Core.FileStore

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

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

data FileVersion Source #

Constructors

VFSVersion !Int 
ModificationTime 

Fields

  • !Int

    Large unit (platform dependent, do not make assumptions)

  • !Int

    Small unit (platform dependent, do not make assumptions)

Instances
Show FileVersion Source # 
Instance details

Defined in Development.IDE.Core.Shake

Generic FileVersion Source # 
Instance details

Defined in Development.IDE.Core.Shake

Associated Types

type Rep FileVersion :: Type -> Type #

NFData FileVersion Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

rnf :: FileVersion -> () #

type Rep FileVersion Source # 
Instance details

Defined in Development.IDE.Core.Shake

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