Skip to content

Commit c6421fd

Browse files
isovectorwz1000pepeiborraberbermanjneira
authored
Fix a wingman bug caused by mismanaged stale data (haskell#1657)
* Start tracking provenance of stale data It's amazing how wrong this code used to be * Add some machinery for automagically updating the age * Add an applicative instance * Tracked ages makes everything much easier to reason about * Formatting * Haddock and small changes * Update haddock on IdeAction * Update to lsp-1.2 (haskell#1631) * Update to lsp-1.2 * fix stack * fix splice plugin tests * fix tactic plugin tests * fix some tests * fix some tests * fix outline tests * hlint * fix func-test * Avoid reordering plugins (haskell#1629) * Avoid reordering plugins Order of execution matters for notification plugins, so lets avoid unnecessary reorderings * remove duplicate plugins * fix tests * Civilized indexing progress reporting (haskell#1633) * Civilized indexing progress reporting * optProgressStyle * Consistency: Indexing references ==> Indexing * Fix progress tests * Do not override custom user commands (haskell#1650) Co-authored-by: Potato Hatsue <[email protected]> * Shut the Shake session on exit, instead of restarting it (haskell#1655) Restarting the session will result in progress reporting and other messages being sent to the client, which might have already closed the stream Co-authored-by: Potato Hatsue <[email protected]> * Fix importing type operators (haskell#1644) * Fix importing type operators * Update test * Add expected failure tests * log exceptions before killing the server (haskell#1651) * log hiedb exceptions before killing the server * This is not the hiedb thread - fix message * Fix handler - either an error or success * additional .gitignore entries (haskell#1659) * Fix ignore paths (haskell#1656) * Skip individual steps * Skip individual steps * And needs pre_job * Add bounds for Diff (haskell#1665) * Replace Barrier with MVar in lsp main (haskell#1668) * Port UseStale to ghcide * Use the new ghcide UseStale machinery * Fix hlint complaints Co-authored-by: wz1000 <[email protected]> Co-authored-by: Pepe Iborra <[email protected]> Co-authored-by: Potato Hatsue <[email protected]> Co-authored-by: Javier Neira <[email protected]> Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 334f185 commit c6421fd

File tree

11 files changed

+305
-97
lines changed

11 files changed

+305
-97
lines changed

ghcide/ghcide.cabal

+3
Original file line numberDiff line numberDiff line change
@@ -114,6 +114,8 @@ library
114114
BangPatterns
115115
DeriveFunctor
116116
DeriveGeneric
117+
DeriveFoldable
118+
DeriveTraversable
117119
FlexibleContexts
118120
GeneralizedNewtypeDeriving
119121
LambdaCase
@@ -149,6 +151,7 @@ library
149151
Development.IDE.Core.Service
150152
Development.IDE.Core.Shake
151153
Development.IDE.Core.Tracing
154+
Development.IDE.Core.UseStale
152155
Development.IDE.GHC.Compat
153156
Development.IDE.Core.Compile
154157
Development.IDE.GHC.Error

ghcide/src/Development/IDE/Core/PositionMapping.hs

+1
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module Development.IDE.Core.PositionMapping
1111
, PositionDelta(..)
1212
, addDelta
1313
, idDelta
14+
, composeDelta
1415
, mkDelta
1516
, toCurrentRange
1617
, fromCurrentRange

ghcide/src/Development/IDE/Core/Shake.hs

+5-3
Original file line numberDiff line numberDiff line change
@@ -838,12 +838,14 @@ usesWithStale_ key files = do
838838
Nothing -> liftIO $ throwIO $ BadDependency (show key)
839839
Just v -> return v
840840

841-
newtype IdeAction a = IdeAction { runIdeActionT :: (ReaderT ShakeExtras IO) a }
842-
deriving newtype (MonadReader ShakeExtras, MonadIO, Functor, Applicative, Monad)
843-
844841
-- | IdeActions are used when we want to return a result immediately, even if it
845842
-- is stale Useful for UI actions like hover, completion where we don't want to
846843
-- block.
844+
--
845+
-- Run via 'runIdeAction'.
846+
newtype IdeAction a = IdeAction { runIdeActionT :: (ReaderT ShakeExtras IO) a }
847+
deriving newtype (MonadReader ShakeExtras, MonadIO, Functor, Applicative, Monad)
848+
847849
runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a
848850
runIdeAction _herald s i = runReaderT (runIdeActionT i) s
849851

+153
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,153 @@
1+
{-# LANGUAGE DerivingVia #-}
2+
{-# LANGUAGE GADTs #-}
3+
{-# LANGUAGE KindSignatures #-}
4+
{-# LANGUAGE RankNTypes #-}
5+
6+
module Development.IDE.Core.UseStale
7+
( Age(..)
8+
, Tracked
9+
, unTrack
10+
, PositionMap
11+
, TrackedStale (..)
12+
, unsafeMkStale
13+
, unsafeMkCurrent
14+
, unsafeCopyAge
15+
, MapAge (..)
16+
, dualPositionMap
17+
, useWithStale
18+
, useWithStale_
19+
) where
20+
21+
import Control.Arrow
22+
import Control.Category (Category)
23+
import qualified Control.Category as C
24+
import Control.DeepSeq (NFData)
25+
import Data.Aeson
26+
import Data.Coerce (coerce)
27+
import Data.Functor ((<&>))
28+
import Data.Functor.Identity (Identity(Identity))
29+
import Data.Kind (Type)
30+
import Data.String (fromString)
31+
import Development.IDE (NormalizedFilePath, IdeRule, Action, Range, rangeToRealSrcSpan, realSrcSpanToRange)
32+
import qualified Development.IDE.Core.PositionMapping as P
33+
import qualified Development.IDE.Core.Shake as IDE
34+
import qualified FastString as FS
35+
import SrcLoc
36+
37+
38+
------------------------------------------------------------------------------
39+
-- | A data kind for 'Tracked'.
40+
data Age = Current | Stale Type
41+
42+
43+
------------------------------------------------------------------------------
44+
-- | Some value, tagged with its age. All 'Current' ages are considered to be
45+
-- the same thing, but 'Stale' values are protected by an untouchable variable
46+
-- to ensure they can't be unified.
47+
newtype Tracked (age :: Age) a = UnsafeTracked
48+
{ unTrack :: a
49+
}
50+
deriving stock (Functor, Foldable, Traversable)
51+
deriving newtype (Eq, Ord, Show, Read, ToJSON, FromJSON, NFData)
52+
deriving (Applicative, Monad) via Identity
53+
54+
55+
------------------------------------------------------------------------------
56+
-- | Like 'P.PositionMapping', but with annotated ages for how 'Tracked' values
57+
-- change. Use the 'Category' instance to compose 'PositionMapping's in order
58+
-- to transform between values of different stale ages.
59+
newtype PositionMap (from :: Age) (to :: Age) = PositionMap
60+
{ getPositionMapping :: P.PositionMapping
61+
}
62+
63+
instance Category PositionMap where
64+
id = coerce P.zeroMapping
65+
(.) = coerce P.composeDelta
66+
67+
68+
------------------------------------------------------------------------------
69+
-- | Get a 'PositionMap' that runs in the opposite direction.
70+
dualPositionMap :: PositionMap from to -> PositionMap to from
71+
dualPositionMap (PositionMap (P.PositionMapping (P.PositionDelta from to))) =
72+
PositionMap $ P.PositionMapping $ P.PositionDelta to from
73+
74+
75+
------------------------------------------------------------------------------
76+
-- | A pair containing a @'Tracked' 'Stale'@ value, as well as
77+
-- a 'PositionMapping' that will fast-forward values to the current age.
78+
data TrackedStale a where
79+
TrackedStale
80+
:: Tracked (Stale s) a
81+
-> PositionMap (Stale s) Current
82+
-> TrackedStale a
83+
84+
instance Functor TrackedStale where
85+
fmap f (TrackedStale t pm) = TrackedStale (fmap f t) pm
86+
87+
88+
------------------------------------------------------------------------------
89+
-- | A class for which 'Tracked' values can be run across a 'PositionMapping'
90+
-- to change their ages.
91+
class MapAge a where
92+
{-# MINIMAL mapAgeFrom | mapAgeTo #-}
93+
mapAgeFrom :: PositionMap from to -> Tracked to a -> Maybe (Tracked from a)
94+
mapAgeFrom = mapAgeTo . dualPositionMap
95+
96+
mapAgeTo :: PositionMap from to -> Tracked from a -> Maybe (Tracked to a)
97+
mapAgeTo = mapAgeFrom . dualPositionMap
98+
99+
100+
instance MapAge Range where
101+
mapAgeFrom = coerce P.fromCurrentRange
102+
mapAgeTo = coerce P.toCurrentRange
103+
104+
105+
instance MapAge RealSrcSpan where
106+
mapAgeFrom =
107+
invMapAge (\fs -> rangeToRealSrcSpan (fromString $ FS.unpackFS fs))
108+
(srcSpanFile &&& realSrcSpanToRange)
109+
. mapAgeFrom
110+
111+
112+
------------------------------------------------------------------------------
113+
-- | Helper function for deriving 'MapAge' for values in terms of other
114+
-- instances.
115+
invMapAge
116+
:: (c -> a -> b)
117+
-> (b -> (c, a))
118+
-> (Tracked from a -> Maybe (Tracked to a))
119+
-> Tracked from b
120+
-> Maybe (Tracked to b)
121+
invMapAge to from f t =
122+
let (c, t') = unTrack $ fmap from t
123+
in fmap (fmap $ to c) $ f $ UnsafeTracked t'
124+
125+
126+
unsafeMkCurrent :: age -> Tracked 'Current age
127+
unsafeMkCurrent = coerce
128+
129+
130+
unsafeMkStale :: age -> Tracked (Stale s) age
131+
unsafeMkStale = coerce
132+
133+
134+
unsafeCopyAge :: Tracked age a -> b -> Tracked age b
135+
unsafeCopyAge _ = coerce
136+
137+
138+
-- | Request a Rule result, it not available return the last computed result, if any, which may be stale
139+
useWithStale :: IdeRule k v
140+
=> k -> NormalizedFilePath -> Action (Maybe (TrackedStale v))
141+
useWithStale key file = do
142+
x <- IDE.useWithStale key file
143+
pure $ x <&> \(v, pm) ->
144+
TrackedStale (coerce v) (coerce pm)
145+
146+
-- | Request a Rule result, it not available return the last computed result which may be stale.
147+
-- Errors out if none available.
148+
useWithStale_ :: IdeRule k v
149+
=> k -> NormalizedFilePath -> Action (TrackedStale v)
150+
useWithStale_ key file = do
151+
(v, pm) <- IDE.useWithStale_ key file
152+
pure $ TrackedStale (coerce v) (coerce pm)
153+

plugins/hls-tactics-plugin/src/Wingman/Judgements.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ import qualified Data.Map as M
1212
import Data.Maybe
1313
import Data.Set (Set)
1414
import qualified Data.Set as S
15+
import Development.IDE.Core.UseStale (Tracked, unTrack)
1516
import Development.IDE.Spans.LocalBindings
1617
import OccName
1718
import SrcLoc
@@ -22,8 +23,8 @@ import Wingman.Types
2223

2324
------------------------------------------------------------------------------
2425
-- | Given a 'SrcSpan' and a 'Bindings', create a hypothesis.
25-
hypothesisFromBindings :: RealSrcSpan -> Bindings -> Hypothesis CType
26-
hypothesisFromBindings span bs = buildHypothesis $ getLocalScope bs span
26+
hypothesisFromBindings :: Tracked age RealSrcSpan -> Tracked age Bindings -> Hypothesis CType
27+
hypothesisFromBindings (unTrack -> span) (unTrack -> bs) = buildHypothesis $ getLocalScope bs span
2728

2829

2930
------------------------------------------------------------------------------

plugins/hls-tactics-plugin/src/Wingman/Judgements/Theta.hs

+4-2
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Wingman.Judgements.Theta
1212
import Data.Maybe (fromMaybe, mapMaybe)
1313
import Data.Set (Set)
1414
import qualified Data.Set as S
15+
import Development.IDE.Core.UseStale
1516
import Development.IDE.GHC.Compat
1617
import Generics.SYB hiding (tyConName)
1718
import GhcPlugins (mkVarOcc, splitTyConApp_maybe, getTyVar_maybe)
@@ -50,11 +51,12 @@ mkEvidence _ = Nothing
5051

5152
------------------------------------------------------------------------------
5253
-- | Compute all the 'Evidence' implicitly bound at the given 'SrcSpan'.
53-
getEvidenceAtHole :: SrcSpan -> LHsBinds GhcTc -> [Evidence]
54-
getEvidenceAtHole dst
54+
getEvidenceAtHole :: Tracked age SrcSpan -> Tracked age (LHsBinds GhcTc) -> [Evidence]
55+
getEvidenceAtHole (unTrack -> dst)
5556
= mapMaybe mkEvidence
5657
. (everything (<>) $
5758
mkQ mempty (absBinds dst) `extQ` wrapperBinds dst `extQ` matchBinds dst)
59+
. unTrack
5860

5961

6062
------------------------------------------------------------------------------

0 commit comments

Comments
 (0)