Skip to content

Commit c2fcaae

Browse files
authored
Fix positionMapping in stale data (#3920)
* Fix positionMapping in stale data * add test for updatePositionMapping * add comment to demonstrate addOldDelta
1 parent 133dcdc commit c2fcaae

File tree

4 files changed

+53
-18
lines changed

4 files changed

+53
-18
lines changed

ghcide/ghcide.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -336,6 +336,7 @@ test-suite ghcide-tests
336336
, containers
337337
, data-default
338338
, directory
339+
, enummapset
339340
, extra
340341
, filepath
341342
, fuzzy

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

+8-4
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ module Development.IDE.Core.PositionMapping
1010
, fromCurrentPosition
1111
, toCurrentPosition
1212
, PositionDelta(..)
13-
, addDelta
13+
, addOldDelta
1414
, idDelta
1515
, composeDelta
1616
, mkDelta
@@ -119,9 +119,13 @@ idDelta = PositionDelta pure pure
119119
mkDelta :: [TextDocumentContentChangeEvent] -> PositionDelta
120120
mkDelta cs = foldl' applyChange idDelta cs
121121

122-
-- | Add a new delta onto a Mapping k n to make a Mapping (k - 1) n
123-
addDelta :: PositionDelta -> PositionMapping -> PositionMapping
124-
addDelta delta (PositionMapping pm) = PositionMapping (composeDelta delta pm)
122+
-- | addOldDelta
123+
-- Add a old delta onto a Mapping k n to make a Mapping (k - 1) n
124+
addOldDelta ::
125+
PositionDelta -- ^ delta from version k - 1 to version k
126+
-> PositionMapping -- ^ The input mapping is from version k to version n
127+
-> PositionMapping -- ^ The output mapping is from version k - 1 to version n
128+
addOldDelta delta (PositionMapping pm) = PositionMapping (composeDelta pm delta)
125129

126130
-- TODO: We currently ignore the right hand side (if there is only text), as
127131
-- that was what was done with lsp* 1.6 packages

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

+19-12
Original file line numberDiff line numberDiff line change
@@ -62,6 +62,7 @@ module Development.IDE.Core.Shake(
6262
FileVersion(..),
6363
Priority(..),
6464
updatePositionMapping,
65+
updatePositionMappingHelper,
6566
deleteValue, recordDirtyKeys,
6667
WithProgressFunc, WithIndefiniteProgressFunc,
6768
ProgressEvent(..),
@@ -266,7 +267,7 @@ data ShakeExtras = ShakeExtras
266267
-- ^ Map from a text document version to a PositionMapping that describes how to map
267268
-- positions in a version of that document to positions in the latest version
268269
-- First mapping is delta from previous version and second one is an
269-
-- accumulation of all previous mappings.
270+
-- accumulation to the current version.
270271
,progress :: ProgressReporting
271272
,ideTesting :: IdeTesting
272273
-- ^ Whether to enable additional lsp messages used by the test suite for checking invariants
@@ -443,7 +444,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
443444
`catch` (\(_ :: IOException) -> pure Nothing)
444445
atomicallyNamed "lastValueIO 2" $ do
445446
STM.focus (Focus.alter (alterValue $ Stale (Just del) actual_version (toDyn v))) (toKey k file) state
446-
Just . (v,) . addDelta del <$> mappingForVersion positionMapping file actual_version
447+
Just . (v,) . addOldDelta del <$> mappingForVersion positionMapping file actual_version
447448

448449
-- We got a new stale value from the persistent rule, insert it in the map without affecting diagnostics
449450
alterValue new Nothing = Just (ValueWithDiagnostics new mempty) -- If it wasn't in the map, give it empty diagnostics
@@ -459,7 +460,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
459460
Succeeded ver (fromDynamic -> Just v) ->
460461
atomicallyNamed "lastValueIO 5" $ Just . (v,) <$> mappingForVersion positionMapping file ver
461462
Stale del ver (fromDynamic -> Just v) ->
462-
atomicallyNamed "lastValueIO 6" $ Just . (v,) . maybe id addDelta del <$> mappingForVersion positionMapping file ver
463+
atomicallyNamed "lastValueIO 6" $ Just . (v,) . maybe id addOldDelta del <$> mappingForVersion positionMapping file ver
463464
Failed p | not p -> readPersistent
464465
_ -> pure Nothing
465466

@@ -1352,12 +1353,18 @@ updatePositionMapping IdeState{shakeExtras = ShakeExtras{positionMapping}} Versi
13521353
STM.focus (Focus.alter f) uri positionMapping
13531354
where
13541355
uri = toNormalizedUri _uri
1355-
f = Just . f' . fromMaybe mempty
1356-
f' mappingForUri = snd $
1357-
-- Very important to use mapAccum here so that the tails of
1358-
-- each mapping can be shared, otherwise quadratic space is
1359-
-- used which is evident in long running sessions.
1360-
EM.mapAccumRWithKey (\acc _k (delta, _) -> let new = addDelta delta acc in (new, (delta, acc)))
1361-
zeroMapping
1362-
(EM.insert _version (shared_change, zeroMapping) mappingForUri)
1363-
shared_change = mkDelta changes
1356+
f = Just . updatePositionMappingHelper _version changes . fromMaybe mempty
1357+
1358+
1359+
updatePositionMappingHelper ::
1360+
Int32
1361+
-> [TextDocumentContentChangeEvent]
1362+
-> EnumMap Int32 (PositionDelta, PositionMapping)
1363+
-> EnumMap Int32 (PositionDelta, PositionMapping)
1364+
updatePositionMappingHelper ver changes mappingForUri = snd $
1365+
-- Very important to use mapAccum here so that the tails of
1366+
-- each mapping can be shared, otherwise quadratic space is
1367+
-- used which is evident in long running sessions.
1368+
EM.mapAccumRWithKey (\acc _k (delta, _) -> let new = addOldDelta delta acc in (new, (delta, acc)))
1369+
zeroMapping
1370+
(EM.insert ver (mkDelta changes, zeroMapping) mappingForUri)

ghcide/test/exe/PositionMappingTests.hs

+25-2
Original file line numberDiff line numberDiff line change
@@ -3,14 +3,16 @@
33

44
module PositionMappingTests (tests) where
55

6+
import qualified Data.EnumMap.Strict as EM
67
import Data.Row
78
import qualified Data.Text as T
89
import Data.Text.Utf16.Rope (Rope)
910
import qualified Data.Text.Utf16.Rope as Rope
1011
import Development.IDE.Core.PositionMapping (PositionResult (..),
1112
fromCurrent,
1213
positionResultToMaybe,
13-
toCurrent)
14+
toCurrent,
15+
toCurrentPosition)
1416
import Development.IDE.Types.Location
1517
import Language.LSP.Protocol.Types hiding
1618
(SemanticTokenAbsolute (..),
@@ -20,15 +22,36 @@ import Language.LSP.Protocol.Types hiding
2022
import Language.LSP.VFS (applyChange)
2123
import Test.QuickCheck
2224
-- import Test.QuickCheck.Instances ()
25+
import Control.Arrow (second)
2326
import Data.Functor.Identity (runIdentity)
27+
import Data.Text (Text)
28+
import Development.IDE.Core.Shake (updatePositionMappingHelper)
2429
import Test.Tasty
2530
import Test.Tasty.HUnit
2631
import Test.Tasty.QuickCheck
2732

33+
enumMapMappingTest :: TestTree
34+
enumMapMappingTest = testCase "enumMapMappingTest" $ do
35+
let mkChangeEvent :: Range -> Text -> TextDocumentContentChangeEvent
36+
mkChangeEvent r t = TextDocumentContentChangeEvent $ InL $ #range .== r .+ #rangeLength .== Nothing .+ #text .== t
37+
mkCE :: UInt -> UInt -> UInt -> UInt -> Text -> TextDocumentContentChangeEvent
38+
mkCE l1 c1 l2 c2 = mkChangeEvent (Range (Position l1 c1) (Position l2 c2))
39+
events :: [(Int32, [TextDocumentContentChangeEvent])]
40+
events = map (second return) [(0, mkCE 0 0 0 0 ""), (1, mkCE 0 1 0 1 " "), (2, mkCE 0 2 0 2 " "), (3, mkCE 0 3 0 3 " "), (4, mkCE 0 4 0 4 " "), (5, mkCE 0 5 0 5 " ")]
41+
finalMap = Prelude.foldl (\m (i, e) -> updatePositionMappingHelper i e m) mempty events
42+
let updatePose fromPos = do
43+
mapping <- snd <$> EM.lookup 0 finalMap
44+
toCurrentPosition mapping fromPos
45+
updatePose (Position 0 4) @?= Just (Position 0 9)
46+
updatePose (Position 0 5) @?= Just (Position 0 10)
47+
48+
2849
tests :: TestTree
2950
tests =
3051
testGroup "position mapping"
31-
[ testGroup "toCurrent"
52+
[
53+
enumMapMappingTest
54+
, testGroup "toCurrent"
3255
[ testCase "before" $
3356
toCurrent
3457
(Range (Position 0 1) (Position 0 3))

0 commit comments

Comments
 (0)