From 050586d59e80fbbfd7b1aec2319cebcc3a3da251 Mon Sep 17 00:00:00 2001 From: Elodie Lander Date: Wed, 4 Sep 2024 06:48:42 -0500 Subject: [PATCH 1/6] WIP Add input rule constraints --- ghcide/ghcide.cabal | 1 + ghcide/src/Development/IDE/Core/InputPath.hs | 7 ++ ghcide/src/Development/IDE/Core/Shake.hs | 113 ++++++++++-------- hls-graph/hls-graph.cabal | 1 + .../IDE/Graph/Internal/RuleInput.hs | 17 +++ 5 files changed, 86 insertions(+), 53 deletions(-) create mode 100644 ghcide/src/Development/IDE/Core/InputPath.hs create mode 100644 hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs diff --git a/ghcide/ghcide.cabal b/ghcide/ghcide.cabal index bf88a55ed3..9c93aecc08 100644 --- a/ghcide/ghcide.cabal +++ b/ghcide/ghcide.cabal @@ -135,6 +135,7 @@ library Development.IDE.Core.FileStore Development.IDE.Core.FileUtils Development.IDE.Core.IdeConfiguration + Development.IDE.Core.InputPath Development.IDE.Core.OfInterest Development.IDE.Core.PluginUtils Development.IDE.Core.PositionMapping diff --git a/ghcide/src/Development/IDE/Core/InputPath.hs b/ghcide/src/Development/IDE/Core/InputPath.hs new file mode 100644 index 0000000000..7148ec682b --- /dev/null +++ b/ghcide/src/Development/IDE/Core/InputPath.hs @@ -0,0 +1,7 @@ +module Development.IDE.Core.InputPath where + +import Development.IDE.Graph.Internal.RuleInput (Input) +import Development.IDE (NormalizedFilePath) + +newtype InputPath (i :: Input) = + InputPath { unInputPath :: NormalizedFilePath } \ No newline at end of file diff --git a/ghcide/src/Development/IDE/Core/Shake.hs b/ghcide/src/Development/IDE/Core/Shake.hs index e37c3741c7..120d8a0515 100644 --- a/ghcide/src/Development/IDE/Core/Shake.hs +++ b/ghcide/src/Development/IDE/Core/Shake.hs @@ -1,6 +1,7 @@ -- Copyright (c) 2019 The DAML Authors. All rights reserved. -- SPDX-License-Identifier: Apache-2.0 +{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DuplicateRecordFields #-} @@ -121,6 +122,7 @@ import Data.Vector (Vector) import qualified Data.Vector as Vector import Development.IDE.Core.Debouncer import Development.IDE.Core.FileUtils (getModTime) +import Development.IDE.Core.InputPath (InputPath (unInputPath, InputPath)) import Development.IDE.Core.PositionMapping import Development.IDE.Core.ProgressReporting import Development.IDE.Core.RuleTypes @@ -179,6 +181,7 @@ import System.FilePath hiding (makeRelative) import System.IO.Unsafe (unsafePerformIO) import System.Time.Extra import UnliftIO (MonadUnliftIO (withRunInIO)) +import Development.IDE.Graph.Internal.RuleInput (RuleInput, HasInput) data Log @@ -342,7 +345,7 @@ type WithProgressFunc = forall a. type WithIndefiniteProgressFunc = forall a. T.Text -> LSP.ProgressCancellable -> IO a -> IO a -type GetStalePersistent = NormalizedFilePath -> IdeAction (Maybe (Dynamic,PositionDelta,Maybe Int32)) +type GetStalePersistent = InputPath i -> IdeAction (Maybe (Dynamic,PositionDelta,Maybe Int32)) getShakeExtras :: Action ShakeExtras getShakeExtras = do @@ -384,7 +387,7 @@ getPluginConfigAction plId = do -- 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. -addPersistentRule :: IdeRule k v => k -> (NormalizedFilePath -> IdeAction (Maybe (v,PositionDelta,Maybe Int32))) -> Rules () +addPersistentRule :: IdeRule k i is v => k -> (InputPath i -> IdeAction (Maybe (v,PositionDelta,Maybe Int32))) -> Rules () addPersistentRule k getVal = do ShakeExtras{persistentKeys} <- getShakeExtrasRules void $ liftIO $ atomically $ modifyTVar' persistentKeys $ insertKeyMap (newKey k) (fmap (fmap (first3 toDyn)) . getVal) @@ -452,7 +455,7 @@ getIdeOptionsIO ide = do -- | Return the most recent, potentially stale, value and a PositionMapping -- for the version of that value. -lastValueIO :: IdeRule k v => ShakeExtras -> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping)) +lastValueIO :: IdeRule k i is v => ShakeExtras -> k -> InputPath i -> IO (Maybe (v, PositionMapping)) lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do let readPersistent @@ -498,7 +501,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do -- | Return the most recent, potentially stale, value and a PositionMapping -- for the version of that value. -lastValue :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping)) +lastValue :: IdeRule k i is v => k -> InputPath i -> Action (Maybe (v, PositionMapping)) lastValue key file = do s <- getShakeExtras liftIO $ lastValueIO s key file @@ -513,9 +516,11 @@ mappingForVersion allMappings file (Just (VFSVersion ver)) = do return $ maybe zeroMapping snd $ EM.lookup ver =<< mapping mappingForVersion _ _ _ = pure zeroMapping -type IdeRule k v = +type IdeRule k i is v = ( Shake.RuleResult k ~ v , Shake.ShakeValue k + , RuleInput k ~ is + , HasInput i is , Show v , Typeable v , NFData v @@ -581,10 +586,10 @@ shakeDatabaseProfileIO mbProfileDir = do shakeProfileDatabase shakeDb $ dir file return (dir file) -setValues :: IdeRule k v +setValues :: IdeRule k i is v => Values -> k - -> NormalizedFilePath + -> InputPath i -> Value v -> Vector FileDiagnostic -> STM () @@ -607,11 +612,11 @@ deleteValue ShakeExtras{state} key file = do -- | We return Nothing if the rule has not run and Just Failed if it has failed to produce a value. getValues :: - forall k v. - IdeRule k v => + forall k i is v. + IdeRule k i is v => Values -> k -> - NormalizedFilePath -> + InputPath i -> STM (Maybe (Value v, Vector FileDiagnostic)) getValues state key file = do STM.lookup (toKey key file) state >>= \case @@ -1010,23 +1015,23 @@ preservedKeys checkParents = HSet.fromList $ -- | Define a new Rule without early cutoff define - :: IdeRule k v - => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules () + :: IdeRule k i is v + => Recorder (WithPriority Log) -> (k -> InputPath i -> Action (IdeResult v)) -> Rules () define recorder op = defineEarlyCutoff recorder $ Rule $ \k v -> (Nothing,) <$> op k v defineNoDiagnostics - :: IdeRule k v - => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules () + :: IdeRule k i is v + => Recorder (WithPriority Log) -> (k -> InputPath i -> Action (Maybe v)) -> Rules () defineNoDiagnostics recorder op = defineEarlyCutoff recorder $ RuleNoDiagnostics $ \k v -> (Nothing,) <$> op k v -- | Request a Rule result if available -use :: IdeRule k v - => k -> NormalizedFilePath -> Action (Maybe v) +use :: IdeRule k i is v + => k -> InputPath i -> Action (Maybe v) use key file = runIdentity <$> uses key (Identity file) -- | Request a Rule result, it not available return the last computed result, if any, which may be stale -useWithStale :: IdeRule k v - => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping)) +useWithStale :: IdeRule k i is v + => k -> InputPath i -> Action (Maybe (v, PositionMapping)) useWithStale key file = runIdentity <$> usesWithStale key (Identity file) -- |Request a Rule result, it not available return the last computed result @@ -1036,8 +1041,8 @@ useWithStale key file = runIdentity <$> usesWithStale key (Identity file) -- none available. -- -- WARNING: Not suitable for PluginHandlers. Use `useWithStaleE` instead. -useWithStale_ :: IdeRule k v - => k -> NormalizedFilePath -> Action (v, PositionMapping) +useWithStale_ :: IdeRule k i is v + => k -> InputPath i -> Action (v, PositionMapping) useWithStale_ key file = runIdentity <$> usesWithStale_ key (Identity file) -- |Plural version of 'useWithStale_' @@ -1046,7 +1051,7 @@ useWithStale_ key file = runIdentity <$> usesWithStale_ key (Identity file) -- none available. -- -- WARNING: Not suitable for PluginHandlers. -usesWithStale_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (v, PositionMapping)) +usesWithStale_ :: (Traversable f, IdeRule k i is v) => k -> f (InputPath i) -> Action (f (v, PositionMapping)) usesWithStale_ key files = do res <- usesWithStale key files case sequence res of @@ -1077,11 +1082,11 @@ data FastResult a = FastResult { stale :: Maybe (a,PositionMapping), uptoDate :: -- | 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 (Maybe (v, PositionMapping)) +useWithStaleFast :: IdeRule k i is v => k -> InputPath i -> IdeAction (Maybe (v, PositionMapping)) useWithStaleFast key file = stale <$> useWithStaleFast' key file -- | Same as useWithStaleFast but lets you wait for an up to date result -useWithStaleFast' :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (FastResult v) +useWithStaleFast' :: IdeRule k i is v => k -> InputPath i -> IdeAction (FastResult v) useWithStaleFast' key file = do -- This lookup directly looks up the key in the shake database and -- returns the last value that was computed for this key without @@ -1108,7 +1113,7 @@ useWithStaleFast' key file = do res <- lastValueIO s key file pure $ FastResult res waitValue -useNoFile :: IdeRule k v => k -> Action (Maybe v) +useNoFile :: IdeRule k i is v => k -> Action (Maybe v) useNoFile key = use key emptyFilePath -- Requests a rule if available. @@ -1117,10 +1122,10 @@ useNoFile key = use key emptyFilePath -- none available. -- -- WARNING: Not suitable for PluginHandlers. Use `useE` instead. -use_ :: IdeRule k v => k -> NormalizedFilePath -> Action v +use_ :: IdeRule k i is v => k -> InputPath i -> Action v use_ key file = runIdentity <$> uses_ key (Identity file) -useNoFile_ :: IdeRule k v => k -> Action v +useNoFile_ :: IdeRule k i is v => k -> Action v useNoFile_ key = use_ key emptyFilePath -- |Plural version of `use_` @@ -1129,7 +1134,7 @@ useNoFile_ key = use_ key emptyFilePath -- none available. -- -- WARNING: Not suitable for PluginHandlers. Use `usesE` instead. -uses_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f v) +uses_ :: (Traversable f, IdeRule k i is v) => k -> f (InputPath i) -> Action (f v) uses_ key files = do res <- uses key files case sequence res of @@ -1137,13 +1142,13 @@ uses_ key files = do Just v -> return v -- | Plural version of 'use' -uses :: (Traversable f, IdeRule k v) - => k -> f NormalizedFilePath -> Action (f (Maybe v)) +uses :: (Traversable f, IdeRule k i is v) + => k -> f (InputPath i) -> Action (f (Maybe v)) uses key files = fmap (\(A value) -> currentValue value) <$> apply (fmap (Q . (key,)) files) -- | Return the last computed result which might be stale. -usesWithStale :: (Traversable f, IdeRule k v) - => k -> f NormalizedFilePath -> Action (f (Maybe (v, PositionMapping))) +usesWithStale :: (Traversable f, IdeRule k i is v) + => k -> f (InputPath i) -> Action (f (Maybe (v, PositionMapping))) usesWithStale key files = do _ <- apply (fmap (Q . (key,)) files) -- We don't look at the result of the 'apply' since 'lastValue' will @@ -1151,25 +1156,25 @@ usesWithStale key files = do -- whether the rule succeeded or not. traverse (lastValue key) files -useWithoutDependency :: IdeRule k v - => k -> NormalizedFilePath -> Action (Maybe v) +useWithoutDependency :: IdeRule k i is v + => k -> InputPath i -> Action (Maybe v) useWithoutDependency key file = (\(Identity (A value)) -> currentValue value) <$> applyWithoutDependency (Identity (Q (key, file))) -data RuleBody k v - = Rule (k -> NormalizedFilePath -> Action (Maybe BS.ByteString, IdeResult v)) - | RuleNoDiagnostics (k -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe v)) +data RuleBody k i v + = Rule (k -> InputPath i -> Action (Maybe BS.ByteString, IdeResult v)) + | RuleNoDiagnostics (k -> InputPath i -> Action (Maybe BS.ByteString, Maybe v)) | RuleWithCustomNewnessCheck { newnessCheck :: BS.ByteString -> BS.ByteString -> Bool - , build :: k -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe v) + , build :: k -> InputPath i -> Action (Maybe BS.ByteString, Maybe v) } - | RuleWithOldValue (k -> NormalizedFilePath -> Value v -> Action (Maybe BS.ByteString, IdeResult v)) + | RuleWithOldValue (k -> InputPath i -> Value v -> Action (Maybe BS.ByteString, IdeResult v)) -- | Define a new Rule with early cutoff defineEarlyCutoff - :: IdeRule k v + :: IdeRule k i is v => Recorder (WithPriority Log) - -> RuleBody k v + -> RuleBody k i v -> Rules () defineEarlyCutoff recorder (Rule op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ \traceDiagnostics -> do extras <- getShakeExtras @@ -1197,32 +1202,33 @@ defineEarlyCutoff recorder (RuleWithOldValue op) = addRule $ \(Q (key, file)) (o updateFileDiagnostics recorder file ver (newKey key) extras . map (\(_,y,z) -> (y,z)) $ diags defineEarlyCutoff' diagnostics (==) key file old mode $ op key file -defineNoFile :: IdeRule k v => Recorder (WithPriority Log) -> (k -> Action v) -> Rules () +defineNoFile :: IdeRule k i is v => Recorder (WithPriority Log) -> (k -> Action v) -> Rules () defineNoFile recorder f = defineNoDiagnostics recorder $ \k file -> do if file == emptyFilePath then do res <- f k; return (Just res) else fail $ "Rule " ++ show k ++ " should always be called with the empty string for a file" -defineEarlyCutOffNoFile :: IdeRule k v => Recorder (WithPriority Log) -> (k -> Action (BS.ByteString, v)) -> Rules () -defineEarlyCutOffNoFile recorder f = defineEarlyCutoff recorder $ RuleNoDiagnostics $ \k file -> do +defineEarlyCutOffNoFile :: IdeRule k i is v => Recorder (WithPriority Log) -> (k -> Action (BS.ByteString, v)) -> Rules () +defineEarlyCutOffNoFile recorder f = defineEarlyCutoff recorder $ RuleNoDiagnostics $ \k (InputPath file) -> do if file == emptyFilePath then do (hashString, res) <- f k; return (Just hashString, Just res) else fail $ "Rule " ++ show k ++ " should always be called with the empty string for a file" defineEarlyCutoff' - :: forall k v. IdeRule k v + :: forall k i is v. IdeRule k i is v => (Maybe Int32 -> [FileDiagnostic] -> Action ()) -- ^ update diagnostics -- | compare current and previous for freshness -> (BS.ByteString -> BS.ByteString -> Bool) -> k - -> NormalizedFilePath + -> InputPath i -> Maybe BS.ByteString -> RunMode -> (Value v -> Action (Maybe BS.ByteString, IdeResult v)) -> Action (RunResult (A (RuleResult k))) defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do + let rawFile = unInputPath file ShakeExtras{state, progress, dirtyKeys} <- getShakeExtras options <- getIdeOptions let trans g x = withRunInIO $ \run -> g (run x) - (if optSkipProgress options key then id else trans (inProgress progress file)) $ do + (if optSkipProgress options key then id else trans (inProgress progress rawFile)) $ do val <- case mbOld of Just old | mode == RunDependenciesSame -> do mbValue <- liftIO $ atomicallyNamed "define - read 1" $ getValues state key file @@ -1249,7 +1255,7 @@ defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do (mbBs, (diags, mbRes)) <- actionCatch (do v <- action staleV; liftIO $ evaluate $ force v) $ \(e :: SomeException) -> do - pure (Nothing, ([ideErrorText file $ T.pack $ show e | not $ isBadDependency e],Nothing)) + pure (Nothing, ([ideErrorText rawFile $ T.pack $ show e | not $ isBadDependency e],Nothing)) ver <- estimateFileVersionUnsafely key mbRes file (bs, res) <- case mbRes of @@ -1270,7 +1276,7 @@ defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do -- this hook needs to be run in the same transaction as the key is marked clean -- see Note [Housekeeping rule cache and dirty key outside of hls-graph] setValues state key file res (Vector.fromList diags) - modifyTVar' dirtyKeys (deleteKeySet $ toKey key file) + modifyTVar' dirtyKeys (deleteKeySet $ toKey key rawFile) return res where -- Highly unsafe helper to compute the version of a file @@ -1279,10 +1285,10 @@ defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do estimateFileVersionUnsafely :: k -> Maybe v - -> NormalizedFilePath + -> InputPath i -> Action (Maybe FileVersion) estimateFileVersionUnsafely _k v fp - | fp == emptyFilePath = pure Nothing + | unInputPath fp == emptyFilePath = pure Nothing | Just Refl <- eqT @k @GetModificationTime = pure v -- GetModificationTime depends on these rules, so avoid creating a cycle | Just Refl <- eqT @k @AddWatchedFile = pure Nothing @@ -1457,9 +1463,10 @@ kickSignal testing lspEnv files msg = when testing $ liftIO $ mRunLspT lspEnv $ toJSON $ map fromNormalizedFilePath files -- | Add kick start/done signal to rule -runWithSignal :: (KnownSymbol s0, KnownSymbol s1, IdeRule k v) => Proxy s0 -> Proxy s1 -> [NormalizedFilePath] -> k -> Action () -runWithSignal msgStart msgEnd files rule = do +runWithSignal :: (KnownSymbol s0, KnownSymbol s1, IdeRule k i is v) => Proxy s0 -> Proxy s1 -> [InputPath i] -> k -> Action () +runWithSignal msgStart msgEnd inputFiles rule = do + let files = map unInputPath inputFiles ShakeExtras{ideTesting = Options.IdeTesting testing, lspEnv} <- getShakeExtras kickSignal testing lspEnv files msgStart - void $ uses rule files + void $ uses rule inputFiles kickSignal testing lspEnv files msgEnd diff --git a/hls-graph/hls-graph.cabal b/hls-graph/hls-graph.cabal index d5a9f781de..f9d3ca15ca 100644 --- a/hls-graph/hls-graph.cabal +++ b/hls-graph/hls-graph.cabal @@ -60,6 +60,7 @@ library Development.IDE.Graph.Internal.Key Development.IDE.Graph.Internal.Paths Development.IDE.Graph.Internal.Profile + Development.IDE.Graph.Internal.RuleInput Development.IDE.Graph.Internal.Rules Development.IDE.Graph.Internal.Types Development.IDE.Graph.KeyMap diff --git a/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs b/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs new file mode 100644 index 0000000000..093cd01269 --- /dev/null +++ b/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE TypeFamilies #-} +module Development.IDE.Graph.Internal.RuleInput where + +type ValidInputs = [Input] + +data Input + = ProjectHaskellFile + | DependencyHaskellFile + +type family RuleInput k :: ValidInputs + +class HasInput (i :: Input) (is :: ValidInputs) + +instance HasInput i (i : is) + +instance {-# OVERLAPPABLE #-} + HasInput i is => HasInput i (j : is) From bcc18e8d86efcbec03ef44f76fb1bbd4378df4c1 Mon Sep 17 00:00:00 2001 From: Elodie Lander Date: Sun, 8 Sep 2024 15:17:46 -0500 Subject: [PATCH 2/6] Add input constraints in Shake.hs --- ghcide/src/Development/IDE/Core/InputPath.hs | 4 +- ghcide/src/Development/IDE/Core/Shake.hs | 51 ++++++++++--------- .../IDE/Graph/Internal/RuleInput.hs | 1 + 3 files changed, 29 insertions(+), 27 deletions(-) diff --git a/ghcide/src/Development/IDE/Core/InputPath.hs b/ghcide/src/Development/IDE/Core/InputPath.hs index 7148ec682b..e807adbc0b 100644 --- a/ghcide/src/Development/IDE/Core/InputPath.hs +++ b/ghcide/src/Development/IDE/Core/InputPath.hs @@ -1,7 +1,7 @@ module Development.IDE.Core.InputPath where import Development.IDE.Graph.Internal.RuleInput (Input) -import Development.IDE (NormalizedFilePath) +import Language.LSP.Protocol.Types (NormalizedFilePath) newtype InputPath (i :: Input) = - InputPath { unInputPath :: NormalizedFilePath } \ No newline at end of file + InputPath { unInputPath :: NormalizedFilePath } deriving Eq \ No newline at end of file diff --git a/ghcide/src/Development/IDE/Core/Shake.hs b/ghcide/src/Development/IDE/Core/Shake.hs index 120d8a0515..d8091c6230 100644 --- a/ghcide/src/Development/IDE/Core/Shake.hs +++ b/ghcide/src/Development/IDE/Core/Shake.hs @@ -181,7 +181,7 @@ import System.FilePath hiding (makeRelative) import System.IO.Unsafe (unsafePerformIO) import System.Time.Extra import UnliftIO (MonadUnliftIO (withRunInIO)) -import Development.IDE.Graph.Internal.RuleInput (RuleInput, HasInput) +import Development.IDE.Graph.Internal.RuleInput (RuleInput, HasInput, Input(NoFile)) data Log @@ -345,7 +345,7 @@ type WithProgressFunc = forall a. type WithIndefiniteProgressFunc = forall a. T.Text -> LSP.ProgressCancellable -> IO a -> IO a -type GetStalePersistent = InputPath i -> IdeAction (Maybe (Dynamic,PositionDelta,Maybe Int32)) +type GetStalePersistent = NormalizedFilePath -> IdeAction (Maybe (Dynamic,PositionDelta,Maybe Int32)) getShakeExtras :: Action ShakeExtras getShakeExtras = do @@ -387,7 +387,7 @@ getPluginConfigAction plId = do -- 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. -addPersistentRule :: IdeRule k i is v => k -> (InputPath i -> IdeAction (Maybe (v,PositionDelta,Maybe Int32))) -> Rules () +addPersistentRule :: IdeRule k i is v => k -> (NormalizedFilePath -> IdeAction (Maybe (v,PositionDelta,Maybe Int32))) -> Rules () addPersistentRule k getVal = do ShakeExtras{persistentKeys} <- getShakeExtrasRules void $ liftIO $ atomically $ modifyTVar' persistentKeys $ insertKeyMap (newKey k) (fmap (fmap (first3 toDyn)) . getVal) @@ -456,7 +456,7 @@ getIdeOptionsIO ide = do -- | Return the most recent, potentially stale, value and a PositionMapping -- for the version of that value. lastValueIO :: IdeRule k i is v => ShakeExtras -> k -> InputPath i -> IO (Maybe (v, PositionMapping)) -lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do +lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k (InputPath file) = do let readPersistent | IdeTesting testing <- ideTesting s -- Don't read stale persistent values in tests @@ -593,7 +593,7 @@ setValues :: IdeRule k i is v -> Value v -> Vector FileDiagnostic -> STM () -setValues state key file val diags = +setValues state key (InputPath file) val diags = STM.insert (ValueWithDiagnostics (fmap toDyn val) diags) (toKey key file) state @@ -618,7 +618,7 @@ getValues :: k -> InputPath i -> STM (Maybe (Value v, Vector FileDiagnostic)) -getValues state key file = do +getValues state key (InputPath file) = do STM.lookup (toKey key file) state >>= \case Nothing -> pure Nothing Just (ValueWithDiagnostics v diagsV) -> do @@ -1094,7 +1094,7 @@ useWithStaleFast' key file = do -- Async trigger the key to be built anyway because we want to -- keep updating the value in the key. - waitValue <- delayedAction $ mkDelayedAction ("C:" ++ show key ++ ":" ++ fromNormalizedFilePath file) Debug $ use key file + waitValue <- delayedAction $ mkDelayedAction ("C:" ++ show key ++ ":" ++ fromNormalizedFilePath (unInputPath file)) Debug $ use key file s@ShakeExtras{state} <- askShake r <- liftIO $ atomicallyNamed "useStateFast" $ getValues state key file @@ -1113,8 +1113,8 @@ useWithStaleFast' key file = do res <- lastValueIO s key file pure $ FastResult res waitValue -useNoFile :: IdeRule k i is v => k -> Action (Maybe v) -useNoFile key = use key emptyFilePath +useNoFile :: forall k is v. IdeRule k NoFile is v => k -> Action (Maybe v) +useNoFile key = use key (InputPath @NoFile emptyFilePath) -- Requests a rule if available. -- @@ -1125,8 +1125,8 @@ useNoFile key = use key emptyFilePath use_ :: IdeRule k i is v => k -> InputPath i -> Action v use_ key file = runIdentity <$> uses_ key (Identity file) -useNoFile_ :: IdeRule k i is v => k -> Action v -useNoFile_ key = use_ key emptyFilePath +useNoFile_ :: forall k is v. IdeRule k NoFile is v => k -> Action v +useNoFile_ key = use_ key (InputPath @NoFile emptyFilePath) -- |Plural version of `use_` -- @@ -1144,13 +1144,13 @@ uses_ key files = do -- | Plural version of 'use' uses :: (Traversable f, IdeRule k i is v) => k -> f (InputPath i) -> Action (f (Maybe v)) -uses key files = fmap (\(A value) -> currentValue value) <$> apply (fmap (Q . (key,)) files) +uses key files = fmap (\(A value) -> currentValue value) <$> apply (fmap (Q . (key,) . unInputPath) files) -- | Return the last computed result which might be stale. usesWithStale :: (Traversable f, IdeRule k i is v) => k -> f (InputPath i) -> Action (f (Maybe (v, PositionMapping))) usesWithStale key files = do - _ <- apply (fmap (Q . (key,)) files) + _ <- apply (fmap (Q . (key,) . unInputPath) files) -- We don't look at the result of the 'apply' since 'lastValue' will -- return the most recent successfully computed value regardless of -- whether the rule succeeded or not. @@ -1158,7 +1158,7 @@ usesWithStale key files = do useWithoutDependency :: IdeRule k i is v => k -> InputPath i -> Action (Maybe v) -useWithoutDependency key file = +useWithoutDependency key (InputPath file) = (\(Identity (A value)) -> currentValue value) <$> applyWithoutDependency (Identity (Q (key, file))) data RuleBody k i v @@ -1172,7 +1172,8 @@ data RuleBody k i v -- | Define a new Rule with early cutoff defineEarlyCutoff - :: IdeRule k i is v + :: forall k i is v + . IdeRule k i is v => Recorder (WithPriority Log) -> RuleBody k i v -> Rules () @@ -1181,35 +1182,35 @@ defineEarlyCutoff recorder (Rule op) = addRule $ \(Q (key, file)) (old :: Maybe let diagnostics ver diags = do traceDiagnostics diags updateFileDiagnostics recorder file ver (newKey key) extras . map (\(_,y,z) -> (y,z)) $ diags - defineEarlyCutoff' diagnostics (==) key file old mode $ const $ op key file + defineEarlyCutoff' diagnostics (==) key (InputPath @i file) old mode $ const $ op key (InputPath @i file) defineEarlyCutoff recorder (RuleNoDiagnostics op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ \traceDiagnostics -> do let diagnostics _ver diags = do traceDiagnostics diags mapM_ (logWith recorder Warning . LogDefineEarlyCutoffRuleNoDiagHasDiag) diags - defineEarlyCutoff' diagnostics (==) key file old mode $ const $ second (mempty,) <$> op key file + defineEarlyCutoff' diagnostics (==) key (InputPath @i file) old mode $ const $ second (mempty,) <$> op key (InputPath @i file) defineEarlyCutoff recorder RuleWithCustomNewnessCheck{..} = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ \ traceDiagnostics -> do let diagnostics _ver diags = do traceDiagnostics diags mapM_ (logWith recorder Warning . LogDefineEarlyCutoffRuleCustomNewnessHasDiag) diags - defineEarlyCutoff' diagnostics newnessCheck key file old mode $ - const $ second (mempty,) <$> build key file + defineEarlyCutoff' diagnostics newnessCheck key (InputPath @i file) old mode $ + const $ second (mempty,) <$> build key (InputPath @i file) defineEarlyCutoff recorder (RuleWithOldValue op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ \traceDiagnostics -> do extras <- getShakeExtras let diagnostics ver diags = do traceDiagnostics diags updateFileDiagnostics recorder file ver (newKey key) extras . map (\(_,y,z) -> (y,z)) $ diags - defineEarlyCutoff' diagnostics (==) key file old mode $ op key file + defineEarlyCutoff' diagnostics (==) key (InputPath @i file) old mode $ op key (InputPath @i file) -defineNoFile :: IdeRule k i is v => Recorder (WithPriority Log) -> (k -> Action v) -> Rules () +defineNoFile :: forall k i is v. IdeRule k i is v => Recorder (WithPriority Log) -> (k -> Action v) -> Rules () defineNoFile recorder f = defineNoDiagnostics recorder $ \k file -> do - if file == emptyFilePath then do res <- f k; return (Just res) else + if file == (InputPath @i emptyFilePath) then do res <- f k; return (Just res) else fail $ "Rule " ++ show k ++ " should always be called with the empty string for a file" -defineEarlyCutOffNoFile :: IdeRule k i is v => Recorder (WithPriority Log) -> (k -> Action (BS.ByteString, v)) -> Rules () -defineEarlyCutOffNoFile recorder f = defineEarlyCutoff recorder $ RuleNoDiagnostics $ \k (InputPath file) -> do - if file == emptyFilePath then do (hashString, res) <- f k; return (Just hashString, Just res) else +defineEarlyCutOffNoFile :: forall k i is v. IdeRule k i is v => Recorder (WithPriority Log) -> (k -> Action (BS.ByteString, v)) -> Rules () +defineEarlyCutOffNoFile recorder f = defineEarlyCutoff recorder $ RuleNoDiagnostics $ \k file -> do + if file == (InputPath @i emptyFilePath) then do (hashString, res) <- f k; return (Just hashString, Just res) else fail $ "Rule " ++ show k ++ " should always be called with the empty string for a file" defineEarlyCutoff' diff --git a/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs b/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs index 093cd01269..ff531760e8 100644 --- a/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs +++ b/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs @@ -6,6 +6,7 @@ type ValidInputs = [Input] data Input = ProjectHaskellFile | DependencyHaskellFile + | NoFile type family RuleInput k :: ValidInputs From bafb42aa1a9da6bdfd31928b39fdd448ace921bf Mon Sep 17 00:00:00 2001 From: Elodie Lander Date: Sun, 8 Sep 2024 16:04:25 -0500 Subject: [PATCH 3/6] Define RuleInput type instances --- ghcide/src/Development/IDE/Core/RuleTypes.hs | 29 ++++++++++++++++++++ 1 file changed, 29 insertions(+) diff --git a/ghcide/src/Development/IDE/Core/RuleTypes.hs b/ghcide/src/Development/IDE/Core/RuleTypes.hs index 3d60669f5c..53f3fe8f33 100644 --- a/ghcide/src/Development/IDE/Core/RuleTypes.hs +++ b/ghcide/src/Development/IDE/Core/RuleTypes.hs @@ -29,6 +29,7 @@ import Development.IDE.GHC.Compat.Util import Development.IDE.GHC.CoreFile import Development.IDE.GHC.Util import Development.IDE.Graph +import Development.IDE.Graph.Internal.RuleInput (Input(ProjectHaskellFile, DependencyHaskellFile, NoFile), RuleInput) import Development.IDE.Import.DependencyInformation import Development.IDE.Types.HscEnvEq (HscEnvEq) import Development.IDE.Types.KnownTargets @@ -65,21 +66,26 @@ encodeLinkableType (Just ObjectLinkable) = "2" -- | The parse tree for the file using GetFileContents type instance RuleResult GetParsedModule = ParsedModule +type instance RuleInput GetParsedModule = '[ProjectHaskellFile, DependencyHaskellFile] -- | The parse tree for the file using GetFileContents, -- all comments included using Opt_KeepRawTokenStream type instance RuleResult GetParsedModuleWithComments = ParsedModule +type instance RuleInput GetParsedModuleWithComments = '[ProjectHaskellFile, DependencyHaskellFile] type instance RuleResult GetModuleGraph = DependencyInformation +type instance RuleInput GetModuleGraph = '[ProjectHaskellFile] data GetKnownTargets = GetKnownTargets deriving (Show, Generic, Eq, Ord) instance Hashable GetKnownTargets instance NFData GetKnownTargets type instance RuleResult GetKnownTargets = KnownTargets +type instance RuleInput GetKnownTargets = '[NoFile] -- | Convert to Core, requires TypeCheck* type instance RuleResult GenerateCore = ModGuts +type instance RuleInput GenerateCore = '[ProjectHaskellFile] data GenerateCore = GenerateCore deriving (Eq, Show, Typeable, Generic) @@ -87,6 +93,7 @@ instance Hashable GenerateCore instance NFData GenerateCore type instance RuleResult GetLinkable = LinkableResult +type instance RuleInput GetLinkable = '[ProjectHaskellFile] data LinkableResult = LinkableResult @@ -112,6 +119,7 @@ instance Hashable GetImportMap instance NFData GetImportMap type instance RuleResult GetImportMap = ImportMap +type instance RuleInput GetImportMap = '[ProjectHaskellFile] newtype ImportMap = ImportMap { importMap :: M.Map ModuleName NormalizedFilePath -- ^ Where are the modules imported by this file located? } deriving stock Show @@ -232,12 +240,15 @@ instance Show HieAstResult where -- | The type checked version of this file, requires TypeCheck+ type instance RuleResult TypeCheck = TcModuleResult +type instance RuleInput TypeCheck = '[ProjectHaskellFile] -- | The uncompressed HieAST type instance RuleResult GetHieAst = HieAstResult +type instance RuleInput GetHieAst = '[ProjectHaskellFile, DependencyHaskellFile] -- | A IntervalMap telling us what is in scope at each point type instance RuleResult GetBindings = Bindings +type instance RuleInput GetBindings = '[ProjectHaskellFile] data DocAndTyThingMap = DKMap {getDocMap :: !DocMap, getTyThingMap :: !TyThingMap} instance NFData DocAndTyThingMap where @@ -247,39 +258,50 @@ instance Show DocAndTyThingMap where show = const "docmap" type instance RuleResult GetDocMap = DocAndTyThingMap +type instance RuleInput GetDocMap = '[ProjectHaskellFile] -- | A GHC session that we reuse. type instance RuleResult GhcSession = HscEnvEq +type instance RuleInput GhcSession = '[ProjectHaskellFile] -- | A GHC session preloaded with all the dependencies -- This rule is also responsible for calling ReportImportCycles for the direct dependencies type instance RuleResult GhcSessionDeps = HscEnvEq +type instance RuleInput GhcSessionDeps = '[ProjectHaskellFile] -- | Resolve the imports in a module to the file path of a module in the same package type instance RuleResult GetLocatedImports = [(Located ModuleName, Maybe ArtifactsLocation)] +type instance RuleInput GetLocatedImports = '[ProjectHaskellFile] -- | This rule is used to report import cycles. It depends on GetModuleGraph. -- We cannot report the cycles directly from GetModuleGraph since -- we can only report diagnostics for the current file. type instance RuleResult ReportImportCycles = () +type instance RuleInput ReportImportCycles = '[ProjectHaskellFile] -- | Read the module interface file from disk. Throws an error for VFS files. -- This is an internal rule, use 'GetModIface' instead. type instance RuleResult GetModIfaceFromDisk = HiFileResult +type instance RuleInput GetModIfaceFromDisk = '[ProjectHaskellFile] -- | GetModIfaceFromDisk and index the `.hie` file into the database. -- This is an internal rule, use 'GetModIface' instead. type instance RuleResult GetModIfaceFromDiskAndIndex = HiFileResult +type instance RuleInput GetModIfaceFromDiskAndIndex = '[ProjectHaskellFile] -- | Get a module interface details, either from an interface file or a typechecked module type instance RuleResult GetModIface = HiFileResult +type instance RuleInput GetModIface = '[ProjectHaskellFile, DependencyHaskellFile] -- | Get the contents of a file, either dirty (if the buffer is modified) or Nothing to mean use from disk. type instance RuleResult GetFileContents = (FileVersion, Maybe Text) +type instance RuleInput GetFileContents = '[ProjectHaskellFile, DependencyHaskellFile] type instance RuleResult GetFileExists = Bool +type instance RuleInput GetFileExists = '[ProjectHaskellFile, DependencyHaskellFile] type instance RuleResult AddWatchedFile = Bool +type instance RuleInput AddWatchedFile = '[ProjectHaskellFile] -- The Shake key type for getModificationTime queries @@ -309,6 +331,7 @@ pattern GetModificationTime = GetModificationTime_ {missingFileDiagnostics=True} -- | Get the modification time of a file. type instance RuleResult GetModificationTime = FileVersion +type instance RuleInput GetModificationTime = '[ProjectHaskellFile, DependencyHaskellFile] -- | Either the mtime from disk or an LSP version -- LSP versions always compare as greater than on disk versions @@ -351,6 +374,7 @@ instance Hashable IsFileOfInterestResult instance NFData IsFileOfInterestResult type instance RuleResult IsFileOfInterest = IsFileOfInterestResult +type instance RuleInput IsFileOfInterest = '[ProjectHaskellFile, DependencyHaskellFile] data ModSummaryResult = ModSummaryResult { msrModSummary :: !ModSummary @@ -373,9 +397,11 @@ instance NFData ModSummaryResult where -- | Generate a ModSummary that has enough information to be used to get .hi and .hie files. -- without needing to parse the entire source type instance RuleResult GetModSummary = ModSummaryResult +type instance RuleInput GetModSummary = '[ProjectHaskellFile, DependencyHaskellFile] -- | Generate a ModSummary with the timestamps and preprocessed content elided, for more successful early cutoff type instance RuleResult GetModSummaryWithoutTimestamps = ModSummaryResult +type instance RuleInput GetModSummaryWithoutTimestamps = '[ProjectHaskellFile, DependencyHaskellFile] data GetParsedModule = GetParsedModule deriving (Eq, Show, Typeable, Generic) @@ -394,6 +420,7 @@ instance NFData GetLocatedImports -- | Does this module need to be compiled? type instance RuleResult NeedsCompilation = Maybe LinkableType +type instance RuleInput NeedsCompilation = '[ProjectHaskellFile] data NeedsCompilation = NeedsCompilation deriving (Eq, Show, Typeable, Generic) @@ -487,6 +514,7 @@ instance Hashable GetClientSettings instance NFData GetClientSettings type instance RuleResult GetClientSettings = Hashed (Maybe Value) +type instance RuleInput GetClientSettings = '[ProjectHaskellFile] data AddWatchedFile = AddWatchedFile deriving (Eq, Show, Typeable, Generic) instance Hashable AddWatchedFile @@ -497,6 +525,7 @@ instance NFData AddWatchedFile -- thread killed exception issues, so we lift it to a full rule. -- https://github.com/digital-asset/daml/pull/2808#issuecomment-529639547 type instance RuleResult GhcSessionIO = IdeGhcSession +type instance RuleInput GhcSessionIO = '[ProjectHaskellFile] data IdeGhcSession = IdeGhcSession { loadSessionFun :: FilePath -> IO (IdeResult HscEnvEq, [FilePath]) From af47b30297433900c5b2c5f21d0ce39c1aa5c912 Mon Sep 17 00:00:00 2001 From: Elodie Lander Date: Sat, 14 Sep 2024 13:43:09 -0500 Subject: [PATCH 4/6] Fix Shake.hs --- ghcide/src/Development/IDE/Core/RuleTypes.hs | 2 +- ghcide/src/Development/IDE/Core/Shake.hs | 18 +++++++++++------- 2 files changed, 12 insertions(+), 8 deletions(-) diff --git a/ghcide/src/Development/IDE/Core/RuleTypes.hs b/ghcide/src/Development/IDE/Core/RuleTypes.hs index 53f3fe8f33..6b46130be5 100644 --- a/ghcide/src/Development/IDE/Core/RuleTypes.hs +++ b/ghcide/src/Development/IDE/Core/RuleTypes.hs @@ -514,7 +514,7 @@ instance Hashable GetClientSettings instance NFData GetClientSettings type instance RuleResult GetClientSettings = Hashed (Maybe Value) -type instance RuleInput GetClientSettings = '[ProjectHaskellFile] +type instance RuleInput GetClientSettings = '[NoFile] data AddWatchedFile = AddWatchedFile deriving (Eq, Show, Typeable, Generic) instance Hashable AddWatchedFile diff --git a/ghcide/src/Development/IDE/Core/Shake.hs b/ghcide/src/Development/IDE/Core/Shake.hs index d8091c6230..da88a8c5ef 100644 --- a/ghcide/src/Development/IDE/Core/Shake.hs +++ b/ghcide/src/Development/IDE/Core/Shake.hs @@ -517,10 +517,14 @@ mappingForVersion allMappings file (Just (VFSVersion ver)) = do mappingForVersion _ _ _ = pure zeroMapping type IdeRule k i is v = - ( Shake.RuleResult k ~ v - , Shake.ShakeValue k + ( IdeValueRule k v , RuleInput k ~ is , HasInput i is + ) + +type IdeValueRule k v = + ( Shake.RuleResult k ~ v + , Shake.ShakeValue k , Show v , Typeable v , NFData v @@ -1156,9 +1160,9 @@ usesWithStale key files = do -- whether the rule succeeded or not. traverse (lastValue key) files -useWithoutDependency :: IdeRule k i is v - => k -> InputPath i -> Action (Maybe v) -useWithoutDependency key (InputPath file) = +useWithoutDependency :: IdeValueRule k v + => k -> NormalizedFilePath -> Action (Maybe v) +useWithoutDependency key file = (\(Identity (A value)) -> currentValue value) <$> applyWithoutDependency (Identity (Q (key, file))) data RuleBody k i v @@ -1288,8 +1292,8 @@ defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do -> Maybe v -> InputPath i -> Action (Maybe FileVersion) - estimateFileVersionUnsafely _k v fp - | unInputPath fp == emptyFilePath = pure Nothing + estimateFileVersionUnsafely _k v (InputPath fp) + | fp == emptyFilePath = pure Nothing | Just Refl <- eqT @k @GetModificationTime = pure v -- GetModificationTime depends on these rules, so avoid creating a cycle | Just Refl <- eqT @k @AddWatchedFile = pure Nothing From 9a4e704b40aa58228742313374d0b76f6d9afd3b Mon Sep 17 00:00:00 2001 From: Elodie Lander Date: Sat, 14 Sep 2024 17:49:23 -0500 Subject: [PATCH 5/6] WIP Add InputPath type to rules --- ghcide/src/Development/IDE/Core/FileStore.hs | 29 +++---- ghcide/src/Development/IDE/Core/Rules.hs | 79 +++++++++++--------- 2 files changed, 59 insertions(+), 49 deletions(-) diff --git a/ghcide/src/Development/IDE/Core/FileStore.hs b/ghcide/src/Development/IDE/Core/FileStore.hs index 6c0cb875b0..7e86edbc68 100644 --- a/ghcide/src/Development/IDE/Core/FileStore.hs +++ b/ghcide/src/Development/IDE/Core/FileStore.hs @@ -69,6 +69,7 @@ import Language.LSP.VFS import System.FilePath import System.IO.Error import System.IO.Unsafe +import Development.IDE.Core.InputPath (InputPath (InputPath, unInputPath)) data Log @@ -88,16 +89,16 @@ instance Pretty Log where <+> pretty (fmap (fmap show) reverseDepPaths) LogShake msg -> pretty msg -addWatchedFileRule :: Recorder (WithPriority Log) -> (NormalizedFilePath -> Action Bool) -> Rules () +addWatchedFileRule :: Recorder (WithPriority Log) -> (InputPath i -> Action Bool) -> Rules () addWatchedFileRule recorder isWatched = defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \AddWatchedFile f -> do isAlreadyWatched <- isWatched f - isWp <- isWorkspaceFile f + isWp <- isWorkspaceFile $ unInputPath f if isAlreadyWatched then pure (Just True) else if not isWp then pure (Just False) else do ShakeExtras{lspEnv} <- getShakeExtras case lspEnv of Just env -> fmap Just $ liftIO $ LSP.runLspT env $ - registerFileWatches [fromNormalizedFilePath f] + registerFileWatches [fromNormalizedFilePath (unInputPath f)] Nothing -> pure $ Just False @@ -107,12 +108,12 @@ getModificationTimeRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco getModificationTimeImpl :: Bool - -> NormalizedFilePath + -> InputPath i -> Action (Maybe BS.ByteString, ([FileDiagnostic], Maybe FileVersion)) getModificationTimeImpl missingFileDiags file = do - let file' = fromNormalizedFilePath file + let file' = fromNormalizedFilePath $ unInputPath file let wrap time = (Just $ LBS.toStrict $ B.encode $ toRational time, ([], Just $ ModificationTime time)) - mbVf <- getVirtualFile file + mbVf <- getVirtualFile $ unInputPath file case mbVf of Just (virtualFileVersion -> ver) -> do alwaysRerun @@ -124,7 +125,7 @@ getModificationTimeImpl missingFileDiags file = do -- but also need a dependency on IsFileOfInterest to reinstall -- alwaysRerun when the file becomes VFS void (use_ IsFileOfInterest file) - else if isInterface file + else if isInterface (unInputPath file) then -- interface files are tracked specially using the closed world assumption pure () else -- in all other cases we will need to freshly check the file system @@ -134,7 +135,7 @@ getModificationTimeImpl missingFileDiags file = do `catch` \(e :: IOException) -> do let err | isDoesNotExistError e = "File does not exist: " ++ file' | otherwise = "IO error while reading " ++ file' ++ ", " ++ displayException e - diag = ideErrorText file (T.pack err) + diag = ideErrorText (unInputPath file) (T.pack err) if isDoesNotExistError e && not missingFileDiags then return (Nothing, ([], Nothing)) else return (Nothing, ([diag], Nothing)) @@ -174,19 +175,19 @@ getFileContentsRule :: Recorder (WithPriority Log) -> Rules () getFileContentsRule recorder = define (cmapWithPrio LogShake recorder) $ \GetFileContents file -> getFileContentsImpl file getFileContentsImpl - :: NormalizedFilePath + :: InputPath i -> Action ([FileDiagnostic], Maybe (FileVersion, Maybe T.Text)) getFileContentsImpl file = do -- need to depend on modification time to introduce a dependency with Cutoff time <- use_ GetModificationTime file res <- do - mbVirtual <- getVirtualFile file + mbVirtual <- getVirtualFile $ unInputPath file pure $ virtualFileText <$> mbVirtual pure ([], Just (time, res)) -- | Returns the modification time and the contents. -- For VFS paths, the modification time is the current time. -getFileContents :: NormalizedFilePath -> Action (UTCTime, Maybe T.Text) +getFileContents :: InputPath i -> Action (UTCTime, Maybe T.Text) getFileContents f = do (fv, txt) <- use_ GetFileContents f modTime <- case modificationTime fv of @@ -196,11 +197,11 @@ getFileContents f = do liftIO $ case foi of IsFOI Modified{} -> getCurrentTime _ -> do - posix <- getModTime $ fromNormalizedFilePath f + posix <- getModTime $ fromNormalizedFilePath $ unInputPath f pure $ posixSecondsToUTCTime posix return (modTime, txt) -fileStoreRules :: Recorder (WithPriority Log) -> (NormalizedFilePath -> Action Bool) -> Rules () +fileStoreRules :: Recorder (WithPriority Log) -> (InputPath i -> Action Bool) -> Rules () fileStoreRules recorder isWatched = do getModificationTimeRule recorder getFileContentsRule recorder @@ -239,7 +240,7 @@ typecheckParentsAction recorder nfp = do Nothing -> logWith recorder Info $ LogCouldNotIdentifyReverseDeps nfp Just rs -> do logWith recorder Info $ LogTypeCheckingReverseDeps nfp revs - void $ uses GetModIface rs + void $ uses GetModIface (map InputPath rs) -- | Note that some keys have been modified and restart the session -- Only valid if the virtual file system was initialised by LSP, as that diff --git a/ghcide/src/Development/IDE/Core/Rules.hs b/ghcide/src/Development/IDE/Core/Rules.hs index b0d61579cc..c285ca7f19 100644 --- a/ghcide/src/Development/IDE/Core/Rules.hs +++ b/ghcide/src/Development/IDE/Core/Rules.hs @@ -101,6 +101,7 @@ import Development.IDE.Core.FileExists hiding (Log, import Development.IDE.Core.FileStore (getFileContents, getModTime) import Development.IDE.Core.IdeConfiguration +import Development.IDE.Core.InputPath import Development.IDE.Core.OfInterest hiding (Log, LogShake) import Development.IDE.Core.PositionMapping @@ -125,6 +126,7 @@ import Development.IDE.GHC.Error import Development.IDE.GHC.Util hiding (modifyDynFlags) import Development.IDE.Graph +import Development.IDE.Graph.Internal.RuleInput import Development.IDE.Import.DependencyInformation import Development.IDE.Import.FindImports import qualified Development.IDE.Spans.AtPoint as AtPoint @@ -226,12 +228,14 @@ getSourceFileSource nfp = do Just source -> pure $ T.encodeUtf8 source -- | Parse the contents of a haskell file. -getParsedModule :: NormalizedFilePath -> Action (Maybe ParsedModule) +getParsedModule :: IdeRule GetParsedModule i is ParsedModule + => InputPath i -> Action (Maybe ParsedModule) getParsedModule = use GetParsedModule -- | Parse the contents of a haskell file, -- ensuring comments are preserved in annotations -getParsedModuleWithComments :: NormalizedFilePath -> Action (Maybe ParsedModule) +getParsedModuleWithComments :: IdeRule GetParsedModuleWithComments i is ParsedModule + => InputPath i -> Action (Maybe ParsedModule) getParsedModuleWithComments = use GetParsedModuleWithComments ------------------------------------------------------------ @@ -259,7 +263,7 @@ getParsedModuleRule recorder = -- We still parse with Haddocks whether Opt_Haddock is True or False to collect information -- but we no longer need to parse with and without Haddocks separately for above GHC90. - liftIO $ (fmap.fmap.fmap) reset_ms $ getParsedModuleDefinition hsc opt file (withOptHaddock ms) + liftIO $ (fmap.fmap.fmap) reset_ms $ getParsedModuleDefinition hsc opt (unInputPath file) (withOptHaddock ms) withOptHaddock :: ModSummary -> ModSummary withOptHaddock = withOption Opt_Haddock @@ -286,7 +290,7 @@ getParsedModuleWithCommentsRule recorder = let ms'' = ms' { ms_hspp_opts = modify_dflags $ ms_hspp_opts ms' } reset_ms pm = pm { pm_mod_summary = ms' } - liftIO $ fmap (fmap reset_ms) $ snd <$> getParsedModuleDefinition hsc opt file ms'' + liftIO $ fmap (fmap reset_ms) $ snd <$> getParsedModuleDefinition hsc opt (unInputPath file) ms'' getModifyDynFlags :: (DynFlagsModifications -> a) -> Action a getModifyDynFlags f = do @@ -367,7 +371,9 @@ execRawDepM act = -- | Given a target file path, construct the raw dependency results by following -- imports recursively. -rawDependencyInformation :: [NormalizedFilePath] -> Action (RawDependencyInformation, BootIdMap) +rawDependencyInformation :: forall i is + . IdeRule GetModSummaryWithoutTimestamps i is ModSummaryResult + => [InputPath i] -> Action (RawDependencyInformation, BootIdMap) rawDependencyInformation fs = do (rdi, ss) <- execRawDepM (goPlural fs) let bm = IntMap.foldrWithKey (updateBootMap rdi) IntMap.empty ss @@ -377,15 +383,15 @@ rawDependencyInformation fs = do mss <- lift $ (fmap.fmap) msrModSummary <$> uses GetModSummaryWithoutTimestamps ff zipWithM go ff mss - go :: NormalizedFilePath -- ^ Current module being processed + go :: InputPath i -- ^ Current module being processed -> Maybe ModSummary -- ^ ModSummary of the module -> RawDepM FilePathId go f mbModSum = do -- First check to see if we have already processed the FilePath -- If we have, just return its Id but don't update any of the state. -- Otherwise, we need to process its imports. - checkAlreadyProcessed f $ do - let al = modSummaryToArtifactsLocation f mbModSum + checkAlreadyProcessed (unInputPath f) $ do + let al = modSummaryToArtifactsLocation (unInputPath f) mbModSum -- Get a fresh FilePathId for the new file fId <- getFreshFid al -- Record this module and its location @@ -412,7 +418,7 @@ rawDependencyInformation fs = do (mns, ls) = unzip with_file -- Recursively process all the imports we just learnt about -- and get back a list of their FilePathIds - fids <- goPlural $ map artifactFilePath ls + fids <- goPlural $ map (InputPath @i . artifactFilePath) ls -- Associate together the ModuleName with the FilePathId let moduleImports' = map (,Nothing) no_file ++ zip mns (map Just fids) -- Insert into the map the information about this modules @@ -468,7 +474,7 @@ reportImportCyclesRule :: Recorder (WithPriority Log) -> Rules () reportImportCyclesRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \ReportImportCycles file -> fmap (\errs -> if null errs then (Just "1",([], Just ())) else (Nothing, (errs, Nothing))) $ do DependencyInformation{..} <- useNoFile_ GetModuleGraph - case pathToId depPathIdMap file of + case pathToId depPathIdMap (unInputPath file) of -- The header of the file does not parse, so it can't be part of any import cycles. Nothing -> pure [] Just fileId -> @@ -479,7 +485,7 @@ reportImportCyclesRule recorder = -- Convert cycles of files into cycles of module names forM cycles $ \(imp, files) -> do modNames <- forM files $ - getModuleName . idToPath depPathIdMap + getModuleName . InputPath . idToPath depPathIdMap pure $ toDiag imp $ sort modNames where cycleErrorInFile f (PartOfCycle imp fs) | f `elem` fs = Just (imp, fs) @@ -521,7 +527,8 @@ persistentHieFileRule recorder = addPersistentRule GetHieAst $ \file -> runMaybe del = deltaFromDiff (T.decodeUtf8 $ Compat.hie_hs_src res) currentSource pure (HAR (Compat.hie_module res) (Compat.hie_asts res) refmap mempty (HieFromDisk res),del,ver) -getHieAstRuleDefinition :: NormalizedFilePath -> HscEnv -> TcModuleResult -> Action (IdeResult HieAstResult) +getHieAstRuleDefinition :: IdeRule IsFileOfInterest i is IsFileOfInterestResult + => InputPath i -> HscEnv -> TcModuleResult -> Action (IdeResult HieAstResult) getHieAstRuleDefinition f hsc tmr = do (diags, masts) <- liftIO $ generateHieAsts hsc tmr se <- getShakeExtras @@ -531,13 +538,13 @@ getHieAstRuleDefinition f hsc tmr = do IsFOI Modified{firstOpen = False} -> do when (coerce $ ideTesting se) $ liftIO $ mRunLspT (lspEnv se) $ LSP.sendNotification (SMethod_CustomMethod (Proxy @"ghcide/reference/ready")) $ - toJSON $ fromNormalizedFilePath f + toJSON $ fromNormalizedFilePath $ unInputPath f pure [] _ | Just asts <- masts -> do - source <- getSourceFileSource f + source <- getSourceFileSource $ unInputPath f let exports = tcg_exports $ tmrTypechecked tmr modSummary = tmrModSummary tmr - liftIO $ writeAndIndexHieFile hsc se modSummary f exports asts source + liftIO $ writeAndIndexHieFile hsc se modSummary (unInputPath f) exports asts source _ -> pure [] let refmap = Compat.generateReferencesMap . Compat.getAsts <$> masts @@ -605,7 +612,7 @@ typeCheckRule recorder = define (cmapWithPrio LogShake recorder) $ \TypeCheck fi -- Keeping typechecked modules in memory for other files is -- very expensive. when (foi == NotFOI) $ - logWith recorder Logger.Warning $ LogTypecheckedFOI file + logWith recorder Logger.Warning $ LogTypecheckedFOI $ unInputPath file typeCheckRuleDefinition hsc pm knownFilesRule :: Recorder (WithPriority Log) -> Rules () @@ -617,13 +624,15 @@ knownFilesRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake recorde getModuleGraphRule :: Recorder (WithPriority Log) -> Rules () getModuleGraphRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake recorder) $ \GetModuleGraph -> do fs <- toKnownFiles <$> useNoFile_ GetKnownTargets - dependencyInfoForFiles (HashSet.toList fs) + dependencyInfoForFiles (map (InputPath @ProjectHaskellFile) $ HashSet.toList fs) -dependencyInfoForFiles :: [NormalizedFilePath] -> Action (BS.ByteString, DependencyInformation) +dependencyInfoForFiles :: forall i is + . IdeRule GetModSummaryWithoutTimestamps i is ModSummaryResult + => [InputPath i] -> Action (BS.ByteString, DependencyInformation) dependencyInfoForFiles fs = do (rawDepInfo, bm) <- rawDependencyInformation fs let (all_fs, _all_ids) = unzip $ HM.toList $ pathToIdMap $ rawPathIdMap rawDepInfo - msrs <- uses GetModSummaryWithoutTimestamps all_fs + msrs <- uses GetModSummaryWithoutTimestamps $ map (InputPath @i) all_fs let mss = map (fmap msrModSummary) msrs let deps = map (\i -> IM.lookup (getFilePathId i) (rawImports rawDepInfo)) _all_ids nodeKeys = IM.fromList $ catMaybes $ zipWith (\fi mms -> (getFilePathId fi,) . NodeKey_Module . msKey <$> mms) _all_ids mss @@ -649,7 +658,7 @@ typeCheckRuleDefinition hsc pm = do unlift <- askUnliftIO let dets = TypecheckHelpers - { getLinkables = unliftIO unlift . uses_ GetLinkable + { getLinkables = unliftIO unlift . uses_ GetLinkable . map InputPath } addUsageDependencies $ liftIO $ typecheckModule defer hsc dets pm @@ -659,7 +668,7 @@ typeCheckRuleDefinition hsc pm = do r@(_, mtc) <- a forM_ mtc $ \tc -> do used_files <- liftIO $ readIORef $ tcg_dependent_files $ tmrTypechecked tc - void $ uses_ GetModificationTime (map toNormalizedFilePath' used_files) + void $ uses_ GetModificationTime (map (InputPath . toNormalizedFilePath') used_files) return r -- | Get all the linkables stored in the graph, i.e. the ones we *do not* need to unload. @@ -695,7 +704,7 @@ loadGhcSession recorder ghcSessionDepsConfig = do defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GhcSession file -> do IdeGhcSession{loadSessionFun} <- useNoFile_ GhcSessionIO -- loading is always returning a absolute path now - (val,deps) <- liftIO $ loadSessionFun $ fromNormalizedFilePath file + (val,deps) <- liftIO $ loadSessionFun $ fromNormalizedFilePath $ unInputPath file -- add the deps to the Shake graph let addDependency fp = do @@ -703,7 +712,7 @@ loadGhcSession recorder ghcSessionDepsConfig = do let nfp = toNormalizedFilePath' fp itExists <- getFileExists nfp when itExists $ void $ do - use_ GetModificationTime nfp + use_ GetModificationTime $ InputPath nfp mapM_ addDependency deps let cutoffHash = LBS.toStrict $ B.encode (hash (snd val)) @@ -730,7 +739,7 @@ instance Default GhcSessionDepsConfig where ghcSessionDepsDefinition :: -- | full mod summary Bool -> - GhcSessionDepsConfig -> HscEnvEq -> NormalizedFilePath -> Action (Maybe HscEnvEq) + GhcSessionDepsConfig -> HscEnvEq -> InputPath i -> Action (Maybe HscEnvEq) ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do let hsc = hscEnv env @@ -743,8 +752,8 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do then use_ GetModSummary file else use_ GetModSummaryWithoutTimestamps file - depSessions <- map hscEnv <$> uses_ (GhcSessionDeps_ fullModSummary) deps - ifaces <- uses_ GetModIface deps + depSessions <- map hscEnv <$> uses_ (GhcSessionDeps_ fullModSummary) (map InputPath deps) + ifaces <- uses_ GetModIface $ map InputPath deps let inLoadOrder = map (\HiFileResult{..} -> HomeModInfo hirModIface hirModDetails emptyHomeModInfoLinkable) ifaces mg <- do if fullModuleGraph @@ -755,7 +764,7 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do -- also points to all the direct descendants of the current module. To get the keys for the descendants -- we must get their `ModSummary`s !final_deps <- do - dep_mss <- map msrModSummary <$> uses_ GetModSummaryWithoutTimestamps deps + dep_mss <- map msrModSummary <$> uses_ GetModSummaryWithoutTimestamps (map InputPath deps) return $!! map (NodeKey_Module . msKey) dep_mss let module_graph_nodes = nubOrdOn mkNodeKey (ModuleNode final_deps ms : concatMap mgModSummaries' mgs) @@ -788,9 +797,9 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco recompInfo = RecompilationInfo { source_version = ver , old_value = m_old - , get_file_version = use GetModificationTime_{missingFileDiagnostics = False} - , get_linkable_hashes = \fs -> map (snd . fromJust . hirCoreFp) <$> uses_ GetModIface fs - , regenerate = regenerateHiFile session f ms + , get_file_version = use GetModificationTime_{missingFileDiagnostics = False} . InputPath + , get_linkable_hashes = \fs -> map (snd . fromJust . hirCoreFp) <$> uses_ GetModIface (map InputPath fs) + , regenerate = regenerateHiFile session (unInputPath f) ms } r <- loadInterface (hscEnv session) ms linkableType recompInfo case r of @@ -818,7 +827,7 @@ getModIfaceFromDiskAndIndexRule recorder = let ms = hirModSummary x hie_loc = Compat.ml_hie_file $ ms_location ms fileHash <- liftIO $ Util.getFileHash hie_loc - mrow <- liftIO $ withHieDb (\hieDb -> HieDb.lookupHieFileFromSource hieDb (fromNormalizedFilePath f)) + mrow <- liftIO $ withHieDb (\hieDb -> HieDb.lookupHieFileFromSource hieDb (fromNormalizedFilePath $ unInputPath f)) let hie_loc' = HieDb.hieModuleHieFile <$> mrow case mrow of Just row @@ -828,7 +837,7 @@ getModIfaceFromDiskAndIndexRule recorder = -- All good, the db has indexed the file when (coerce $ ideTesting se) $ liftIO $ mRunLspT (lspEnv se) $ LSP.sendNotification (SMethod_CustomMethod (Proxy @"ghcide/reference/ready")) $ - toJSON $ fromNormalizedFilePath f + toJSON $ fromNormalizedFilePath $ unInputPath f -- Not in db, must re-index _ -> do ehf <- liftIO $ runIdeAction "GetModIfaceFromDiskAndIndex" se $ runExceptT $ @@ -838,8 +847,8 @@ getModIfaceFromDiskAndIndexRule recorder = Left err -> fail $ "failed to read .hie file " ++ show hie_loc ++ ": " ++ displayException err -- can just re-index the file we read from disk Right hf -> liftIO $ do - logWith recorder Logger.Debug $ LogReindexingHieFile f - indexHieFile se ms f fileHash hf + logWith recorder Logger.Debug $ LogReindexingHieFile $ unInputPath f + indexHieFile se ms (unInputPath f) fileHash hf return (Just x) @@ -1089,7 +1098,7 @@ getLinkableRule recorder = return (fileHash <$ hmi, (warns, LinkableResult <$> hmi <*> pure fileHash)) -- | For now we always use bytecode unless something uses unboxed sums and tuples along with TH -getLinkableType :: NormalizedFilePath -> Action (Maybe LinkableType) +getLinkableType :: InputPath i -> Action (Maybe LinkableType) getLinkableType f = use_ NeedsCompilation f needsCompilationRule :: NormalizedFilePath -> Action (IdeResultNoDiagnosticsEarlyCutoff (Maybe LinkableType)) From 506e9584d369ee57a8ec5ede1a0bb312b924dc39 Mon Sep 17 00:00:00 2001 From: Elodie Lander Date: Sun, 15 Sep 2024 11:19:35 -0500 Subject: [PATCH 6/6] Try enumerating all instances --- ghcide/src/Development/IDE/Core/RuleTypes.hs | 58 +++++++++---------- .../IDE/Graph/Internal/RuleInput.hs | 14 +++-- 2 files changed, 39 insertions(+), 33 deletions(-) diff --git a/ghcide/src/Development/IDE/Core/RuleTypes.hs b/ghcide/src/Development/IDE/Core/RuleTypes.hs index 6b46130be5..c48e7f3feb 100644 --- a/ghcide/src/Development/IDE/Core/RuleTypes.hs +++ b/ghcide/src/Development/IDE/Core/RuleTypes.hs @@ -29,7 +29,7 @@ import Development.IDE.GHC.Compat.Util import Development.IDE.GHC.CoreFile import Development.IDE.GHC.Util import Development.IDE.Graph -import Development.IDE.Graph.Internal.RuleInput (Input(ProjectHaskellFile, DependencyHaskellFile, NoFile), RuleInput) +import Development.IDE.Graph.Internal.RuleInput (Input(ProjectHaskellFile, DependencyHaskellFile, NoFile), RuleInput, ValidInputs(ProjectHaskellFilesOnly, AllHaskellFiles, NoFiles)) import Development.IDE.Import.DependencyInformation import Development.IDE.Types.HscEnvEq (HscEnvEq) import Development.IDE.Types.KnownTargets @@ -66,26 +66,26 @@ encodeLinkableType (Just ObjectLinkable) = "2" -- | The parse tree for the file using GetFileContents type instance RuleResult GetParsedModule = ParsedModule -type instance RuleInput GetParsedModule = '[ProjectHaskellFile, DependencyHaskellFile] +type instance RuleInput GetParsedModule = AllHaskellFiles -- | The parse tree for the file using GetFileContents, -- all comments included using Opt_KeepRawTokenStream type instance RuleResult GetParsedModuleWithComments = ParsedModule -type instance RuleInput GetParsedModuleWithComments = '[ProjectHaskellFile, DependencyHaskellFile] +type instance RuleInput GetParsedModuleWithComments = AllHaskellFiles type instance RuleResult GetModuleGraph = DependencyInformation -type instance RuleInput GetModuleGraph = '[ProjectHaskellFile] +type instance RuleInput GetModuleGraph = ProjectHaskellFilesOnly data GetKnownTargets = GetKnownTargets deriving (Show, Generic, Eq, Ord) instance Hashable GetKnownTargets instance NFData GetKnownTargets type instance RuleResult GetKnownTargets = KnownTargets -type instance RuleInput GetKnownTargets = '[NoFile] +type instance RuleInput GetKnownTargets = NoFiles -- | Convert to Core, requires TypeCheck* type instance RuleResult GenerateCore = ModGuts -type instance RuleInput GenerateCore = '[ProjectHaskellFile] +type instance RuleInput GenerateCore = ProjectHaskellFilesOnly data GenerateCore = GenerateCore deriving (Eq, Show, Typeable, Generic) @@ -93,7 +93,7 @@ instance Hashable GenerateCore instance NFData GenerateCore type instance RuleResult GetLinkable = LinkableResult -type instance RuleInput GetLinkable = '[ProjectHaskellFile] +type instance RuleInput GetLinkable = ProjectHaskellFilesOnly data LinkableResult = LinkableResult @@ -119,7 +119,7 @@ instance Hashable GetImportMap instance NFData GetImportMap type instance RuleResult GetImportMap = ImportMap -type instance RuleInput GetImportMap = '[ProjectHaskellFile] +type instance RuleInput GetImportMap = ProjectHaskellFilesOnly newtype ImportMap = ImportMap { importMap :: M.Map ModuleName NormalizedFilePath -- ^ Where are the modules imported by this file located? } deriving stock Show @@ -240,15 +240,15 @@ instance Show HieAstResult where -- | The type checked version of this file, requires TypeCheck+ type instance RuleResult TypeCheck = TcModuleResult -type instance RuleInput TypeCheck = '[ProjectHaskellFile] +type instance RuleInput TypeCheck = ProjectHaskellFilesOnly -- | The uncompressed HieAST type instance RuleResult GetHieAst = HieAstResult -type instance RuleInput GetHieAst = '[ProjectHaskellFile, DependencyHaskellFile] +type instance RuleInput GetHieAst = AllHaskellFiles -- | A IntervalMap telling us what is in scope at each point type instance RuleResult GetBindings = Bindings -type instance RuleInput GetBindings = '[ProjectHaskellFile] +type instance RuleInput GetBindings = ProjectHaskellFilesOnly data DocAndTyThingMap = DKMap {getDocMap :: !DocMap, getTyThingMap :: !TyThingMap} instance NFData DocAndTyThingMap where @@ -258,50 +258,50 @@ instance Show DocAndTyThingMap where show = const "docmap" type instance RuleResult GetDocMap = DocAndTyThingMap -type instance RuleInput GetDocMap = '[ProjectHaskellFile] +type instance RuleInput GetDocMap = ProjectHaskellFilesOnly -- | A GHC session that we reuse. type instance RuleResult GhcSession = HscEnvEq -type instance RuleInput GhcSession = '[ProjectHaskellFile] +type instance RuleInput GhcSession = ProjectHaskellFilesOnly -- | A GHC session preloaded with all the dependencies -- This rule is also responsible for calling ReportImportCycles for the direct dependencies type instance RuleResult GhcSessionDeps = HscEnvEq -type instance RuleInput GhcSessionDeps = '[ProjectHaskellFile] +type instance RuleInput GhcSessionDeps = ProjectHaskellFilesOnly -- | Resolve the imports in a module to the file path of a module in the same package type instance RuleResult GetLocatedImports = [(Located ModuleName, Maybe ArtifactsLocation)] -type instance RuleInput GetLocatedImports = '[ProjectHaskellFile] +type instance RuleInput GetLocatedImports = ProjectHaskellFilesOnly -- | This rule is used to report import cycles. It depends on GetModuleGraph. -- We cannot report the cycles directly from GetModuleGraph since -- we can only report diagnostics for the current file. type instance RuleResult ReportImportCycles = () -type instance RuleInput ReportImportCycles = '[ProjectHaskellFile] +type instance RuleInput ReportImportCycles = ProjectHaskellFilesOnly -- | Read the module interface file from disk. Throws an error for VFS files. -- This is an internal rule, use 'GetModIface' instead. type instance RuleResult GetModIfaceFromDisk = HiFileResult -type instance RuleInput GetModIfaceFromDisk = '[ProjectHaskellFile] +type instance RuleInput GetModIfaceFromDisk = ProjectHaskellFilesOnly -- | GetModIfaceFromDisk and index the `.hie` file into the database. -- This is an internal rule, use 'GetModIface' instead. type instance RuleResult GetModIfaceFromDiskAndIndex = HiFileResult -type instance RuleInput GetModIfaceFromDiskAndIndex = '[ProjectHaskellFile] +type instance RuleInput GetModIfaceFromDiskAndIndex = ProjectHaskellFilesOnly -- | Get a module interface details, either from an interface file or a typechecked module type instance RuleResult GetModIface = HiFileResult -type instance RuleInput GetModIface = '[ProjectHaskellFile, DependencyHaskellFile] +type instance RuleInput GetModIface = AllHaskellFiles -- | Get the contents of a file, either dirty (if the buffer is modified) or Nothing to mean use from disk. type instance RuleResult GetFileContents = (FileVersion, Maybe Text) -type instance RuleInput GetFileContents = '[ProjectHaskellFile, DependencyHaskellFile] +type instance RuleInput GetFileContents = AllHaskellFiles type instance RuleResult GetFileExists = Bool -type instance RuleInput GetFileExists = '[ProjectHaskellFile, DependencyHaskellFile] +type instance RuleInput GetFileExists = AllHaskellFiles type instance RuleResult AddWatchedFile = Bool -type instance RuleInput AddWatchedFile = '[ProjectHaskellFile] +type instance RuleInput AddWatchedFile = ProjectHaskellFilesOnly -- The Shake key type for getModificationTime queries @@ -331,7 +331,7 @@ pattern GetModificationTime = GetModificationTime_ {missingFileDiagnostics=True} -- | Get the modification time of a file. type instance RuleResult GetModificationTime = FileVersion -type instance RuleInput GetModificationTime = '[ProjectHaskellFile, DependencyHaskellFile] +type instance RuleInput GetModificationTime = AllHaskellFiles -- | Either the mtime from disk or an LSP version -- LSP versions always compare as greater than on disk versions @@ -374,7 +374,7 @@ instance Hashable IsFileOfInterestResult instance NFData IsFileOfInterestResult type instance RuleResult IsFileOfInterest = IsFileOfInterestResult -type instance RuleInput IsFileOfInterest = '[ProjectHaskellFile, DependencyHaskellFile] +type instance RuleInput IsFileOfInterest = AllHaskellFiles data ModSummaryResult = ModSummaryResult { msrModSummary :: !ModSummary @@ -397,11 +397,11 @@ instance NFData ModSummaryResult where -- | Generate a ModSummary that has enough information to be used to get .hi and .hie files. -- without needing to parse the entire source type instance RuleResult GetModSummary = ModSummaryResult -type instance RuleInput GetModSummary = '[ProjectHaskellFile, DependencyHaskellFile] +type instance RuleInput GetModSummary = AllHaskellFiles -- | Generate a ModSummary with the timestamps and preprocessed content elided, for more successful early cutoff type instance RuleResult GetModSummaryWithoutTimestamps = ModSummaryResult -type instance RuleInput GetModSummaryWithoutTimestamps = '[ProjectHaskellFile, DependencyHaskellFile] +type instance RuleInput GetModSummaryWithoutTimestamps = AllHaskellFiles data GetParsedModule = GetParsedModule deriving (Eq, Show, Typeable, Generic) @@ -420,7 +420,7 @@ instance NFData GetLocatedImports -- | Does this module need to be compiled? type instance RuleResult NeedsCompilation = Maybe LinkableType -type instance RuleInput NeedsCompilation = '[ProjectHaskellFile] +type instance RuleInput NeedsCompilation = ProjectHaskellFilesOnly data NeedsCompilation = NeedsCompilation deriving (Eq, Show, Typeable, Generic) @@ -514,7 +514,7 @@ instance Hashable GetClientSettings instance NFData GetClientSettings type instance RuleResult GetClientSettings = Hashed (Maybe Value) -type instance RuleInput GetClientSettings = '[NoFile] +type instance RuleInput GetClientSettings = NoFiles data AddWatchedFile = AddWatchedFile deriving (Eq, Show, Typeable, Generic) instance Hashable AddWatchedFile @@ -525,7 +525,7 @@ instance NFData AddWatchedFile -- thread killed exception issues, so we lift it to a full rule. -- https://github.com/digital-asset/daml/pull/2808#issuecomment-529639547 type instance RuleResult GhcSessionIO = IdeGhcSession -type instance RuleInput GhcSessionIO = '[ProjectHaskellFile] +type instance RuleInput GhcSessionIO = ProjectHaskellFilesOnly data IdeGhcSession = IdeGhcSession { loadSessionFun :: FilePath -> IO (IdeResult HscEnvEq, [FilePath]) diff --git a/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs b/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs index ff531760e8..9b77f2f777 100644 --- a/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs +++ b/hls-graph/src/Development/IDE/Graph/Internal/RuleInput.hs @@ -1,7 +1,10 @@ {-# LANGUAGE TypeFamilies #-} module Development.IDE.Graph.Internal.RuleInput where -type ValidInputs = [Input] +data ValidInputs + = ProjectHaskellFilesOnly + | AllHaskellFiles + | NoFiles data Input = ProjectHaskellFile @@ -12,7 +15,10 @@ type family RuleInput k :: ValidInputs class HasInput (i :: Input) (is :: ValidInputs) -instance HasInput i (i : is) +instance HasInput ProjectHaskellFile ProjectHaskellFilesOnly -instance {-# OVERLAPPABLE #-} - HasInput i is => HasInput i (j : is) +instance HasInput ProjectHaskellFile AllHaskellFiles + +instance HasInput DependencyHaskellFile AllHaskellFiles + +instance HasInput NoFile NoFiles