Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data ShakeExtras = ShakeExtras {
- eventer :: FromServerMessage -> IO ()
- debouncer :: Debouncer NormalizedUri
- logger :: Logger
- globals :: Var (HashMap TypeRep Dynamic)
- state :: Var Values
- diagnostics :: Var DiagnosticStore
- hiddenDiagnostics :: Var DiagnosticStore
- publishedDiagnostics :: Var (Map NormalizedUri [Diagnostic])
- positionMapping :: Var (Map NormalizedUri (Map TextDocumentVersion PositionMapping))
- inProgress :: Var (Map NormalizedFilePath Int)
- getShakeExtras :: Action ShakeExtras
- type IdeRule k v = (RuleResult k ~ v, ShakeValue k, Show v, Typeable v, NFData v)
- type IdeResult v = ([FileDiagnostic], Maybe v)
- data GetModificationTime = GetModificationTime
- shakeOpen :: IO LspId -> (FromServerMessage -> IO ()) -> Logger -> Maybe FilePath -> IdeReportProgress -> ShakeOptions -> Rules () -> IO IdeState
- shakeShut :: IdeState -> IO ()
- shakeRun :: IdeState -> [Action a] -> IO (IO [a])
- shakeProfile :: IdeState -> FilePath -> IO ()
- use :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe v)
- useWithStale :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
- useNoFile :: IdeRule k v => k -> Action (Maybe v)
- uses :: IdeRule k v => k -> [NormalizedFilePath] -> Action [Maybe v]
- usesWithStale :: IdeRule k v => k -> [NormalizedFilePath] -> Action [Maybe (v, PositionMapping)]
- use_ :: IdeRule k v => k -> NormalizedFilePath -> Action v
- useNoFile_ :: IdeRule k v => k -> Action v
- uses_ :: IdeRule k v => k -> [NormalizedFilePath] -> Action [v]
- define :: IdeRule k v => (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules ()
- defineEarlyCutoff :: IdeRule k v => (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v)) -> Rules ()
- defineOnDisk :: (ShakeValue k, RuleResult k ~ ()) => (k -> NormalizedFilePath -> OnDiskRule) -> Rules ()
- needOnDisk :: (ShakeValue k, RuleResult k ~ ()) => k -> NormalizedFilePath -> Action ()
- needOnDisks :: (ShakeValue k, RuleResult k ~ ()) => k -> [NormalizedFilePath] -> Action ()
- getDiagnostics :: IdeState -> IO [FileDiagnostic]
- unsafeClearDiagnostics :: IdeState -> IO ()
- getHiddenDiagnostics :: IdeState -> IO [FileDiagnostic]
- class Typeable a => IsIdeGlobal a
- addIdeGlobal :: IsIdeGlobal a => a -> Rules ()
- getIdeGlobalState :: forall a. IsIdeGlobal a => IdeState -> IO a
- getIdeGlobalAction :: forall a. IsIdeGlobal a => Action a
- garbageCollect :: (NormalizedFilePath -> Bool) -> Action ()
- setPriority :: Priority -> Action ()
- sendEvent :: FromServerMessage -> Action ()
- ideLogger :: IdeState -> Logger
- actionLogger :: Action Logger
- data FileVersion
- newtype Priority = Priority Double
- updatePositionMapping :: IdeState -> VersionedTextDocumentIdentifier -> List TextDocumentContentChangeEvent -> IO ()
- deleteValue :: (Typeable k, Hashable k, Eq k, Show k) => IdeState -> k -> NormalizedFilePath -> IO ()
- data OnDiskRule = OnDiskRule {}
Documentation
A Shake database plus persistent store. Can be thought of as storing
mappings from (FilePath, k)
to RuleResult k
.
data ShakeExtras Source #
ShakeExtras | |
|
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 #
Instances
:: IO LspId | |
-> (FromServerMessage -> IO ()) | diagnostic handler |
-> Logger | |
-> Maybe FilePath | |
-> IdeReportProgress | |
-> ShakeOptions | |
-> Rules () | |
-> IO IdeState |
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.
useWithStale :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping)) 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 #
defineEarlyCutoff :: IdeRule k v => (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v)) -> Rules () Source #
defineOnDisk :: (ShakeValue k, RuleResult k ~ ()) => (k -> NormalizedFilePath -> OnDiskRule) -> Rules () Source #
needOnDisk :: (ShakeValue k, RuleResult k ~ ()) => k -> NormalizedFilePath -> Action () Source #
needOnDisks :: (ShakeValue k, RuleResult k ~ ()) => k -> [NormalizedFilePath] -> Action () Source #
getDiagnostics :: IdeState -> IO [FileDiagnostic] Source #
unsafeClearDiagnostics :: IdeState -> IO () Source #
FIXME: This function is temporary! Only required because the files of interest doesn't work
getHiddenDiagnostics :: IdeState -> IO [FileDiagnostic] Source #
class Typeable a => IsIdeGlobal a Source #
Instances
IsIdeGlobal VFSHandle Source # | |
Defined in Development.IDE.Core.FileStore |
addIdeGlobal :: IsIdeGlobal a => a -> Rules () Source #
getIdeGlobalState :: forall a. IsIdeGlobal a => IdeState -> IO a Source #
getIdeGlobalAction :: forall a. IsIdeGlobal a => Action a Source #
garbageCollect :: (NormalizedFilePath -> Bool) -> Action () Source #
Clear the results for all files that do not match the given predicate.
setPriority :: Priority -> Action () Source #
sendEvent :: FromServerMessage -> Action () Source #
data FileVersion Source #
We store the modification time as a ByteString since we need a ByteString anyway for Shake and we do not care about how times are represented.
Instances
Show FileVersion Source # | |
Defined in Development.IDE.Core.Shake showsPrec :: Int -> FileVersion -> ShowS # show :: FileVersion -> String # showList :: [FileVersion] -> ShowS # | |
Generic FileVersion Source # | |
Defined in Development.IDE.Core.Shake type Rep FileVersion :: Type -> Type # from :: FileVersion -> Rep FileVersion x # to :: Rep FileVersion x -> FileVersion # | |
NFData FileVersion Source # | |
Defined in Development.IDE.Core.Shake rnf :: FileVersion -> () # | |
type Rep FileVersion Source # | |
Defined in Development.IDE.Core.Shake type Rep FileVersion = D1 (MetaData "FileVersion" "Development.IDE.Core.Shake" "ghcide-0.1.0-C0d1MTwub4dDHKtuFGkKNT" False) (C1 (MetaCons "VFSVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "ModificationTime" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
updatePositionMapping :: IdeState -> VersionedTextDocumentIdentifier -> List TextDocumentContentChangeEvent -> IO () Source #
deleteValue :: (Typeable k, Hashable k, Eq k, Show k) => IdeState -> k -> NormalizedFilePath -> IO () Source #
Delete the value stored for a given ide build key
data OnDiskRule Source #