| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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 typeQtoA. 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
Valuestype stores a map of keys to values. These values are always stored as real Haskell values, whereas Shake serialises allAvalues between runs. To deserialise a Shake value, we just consult Values.
Synopsis
- data IdeState
- shakeExtras :: IdeState -> ShakeExtras
- 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 (HashMap NormalizedUri [Diagnostic])
- positionMapping :: Var (HashMap NormalizedUri (Map TextDocumentVersion (PositionDelta, PositionMapping)))
- inProgress :: Var (HashMap NormalizedFilePath Int)
- getShakeExtras :: Action ShakeExtras
- getShakeExtrasRules :: Rules 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 -> Debouncer NormalizedUri -> 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 ()
- addIdeGlobalExtras :: IsIdeGlobal a => ShakeExtras -> a -> IO ()
- 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
- = VFSVersion !Int
- | ModificationTime !Int !Int
- modificationTime :: FileVersion -> Maybe (Int, Int)
- 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.
shakeExtras :: IdeState -> ShakeExtras Source #
data ShakeExtras Source #
Constructors
| ShakeExtras | |
Fields
| |
type IdeRule k v = (RuleResult k ~ v, ShakeValue k, Show v, Typeable v, NFData v) Source #
type IdeResult v = ([FileDiagnostic], Maybe v) Source #
data GetModificationTime Source #
Constructors
| GetModificationTime |
Instances
Arguments
| :: IO LspId | |
| -> (FromServerMessage -> IO ()) | diagnostic handler |
| -> Logger | |
| -> Debouncer NormalizedUri | |
| -> 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 #
addIdeGlobalExtras :: IsIdeGlobal a => ShakeExtras -> a -> IO () 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 #
Constructors
| VFSVersion !Int | |
| ModificationTime | |
Instances
| Show FileVersion Source # | |
Defined in Development.IDE.Core.Shake Methods showsPrec :: Int -> FileVersion -> ShowS # show :: FileVersion -> String # showList :: [FileVersion] -> ShowS # | |
| Generic FileVersion Source # | |
Defined in Development.IDE.Core.Shake Associated Types type Rep FileVersion :: Type -> Type # | |
| NFData FileVersion Source # | |
Defined in Development.IDE.Core.Shake Methods rnf :: FileVersion -> () # | |
| type Rep FileVersion Source # | |
Defined in Development.IDE.Core.Shake type Rep FileVersion = D1 (MetaData "FileVersion" "Development.IDE.Core.Shake" "ghcide-0.2.0-HKsdlJpUfsj7QU2D2Ij409" 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 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) | |
modificationTime :: FileVersion -> Maybe (Int, Int) Source #
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 #
Constructors
| OnDiskRule | |
Fields
| |