Skip to content

Commit b77596d

Browse files
committed
Upgrade to latest lsp/lsp-types/lsp-test
1 parent 1dd54a5 commit b77596d

File tree

29 files changed

+192
-190
lines changed

29 files changed

+192
-190
lines changed

cabal.project

+8
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,14 @@ source-repository-package
5656
tag: 7a0af7a8fd38045fd15fb13445bdcc7085325460
5757
-- END DELETE
5858

59+
source-repository-package
60+
type:git
61+
location: https://github.com/haskell/lsp
62+
tag: 1e5940b4c85d53f01831bca487f3cd0a9466d3de
63+
subdir: lsp
64+
subdir: lsp-test
65+
subdir: lsp-types
66+
5967
if impl(ghc >= 9.1)
6068
-- ekg packagess are old and unmaintained, but we
6169
-- don't rely on them for the mainline build, so

ghcide-bench/src/Experiments.hs

+33-24
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
{-# LANGUAGE GADTs #-}
33
{-# LANGUAGE ImplicitParams #-}
44
{-# LANGUAGE ImpredicativeTypes #-}
5-
{-# LANGUAGE OverloadedLabels #-}
65
{-# LANGUAGE OverloadedStrings #-}
76
{-# OPTIONS_GHC -Wno-deprecations -Wno-unticked-promoted-constructors #-}
87

@@ -43,14 +42,12 @@ import Data.Either (fromRight)
4342
import Data.List
4443
import Data.Maybe
4544
import Data.Proxy
46-
import Data.Row hiding (switch)
4745
import Data.Text (Text)
4846
import qualified Data.Text as T
4947
import Data.Version
5048
import Development.IDE.Plugin.Test
5149
import Development.IDE.Test.Diagnostic
52-
import Development.Shake (CmdOption (Cwd, FileStdout),
53-
cmd_)
50+
import Development.Shake (CmdOption (Cwd), cmd_)
5451
import Experiments.Types
5552
import Language.LSP.Protocol.Capabilities
5653
import qualified Language.LSP.Protocol.Lens as L
@@ -72,15 +69,19 @@ import Text.Printf
7269

7370
charEdit :: Position -> TextDocumentContentChangeEvent
7471
charEdit p =
75-
TextDocumentContentChangeEvent $ InL $ #range .== Range p p
76-
.+ #rangeLength .== Nothing
77-
.+ #text .== "a"
72+
TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
73+
{ _range = Range p p
74+
, _rangeLength = Nothing
75+
, _text = "a"
76+
}
7877

7978
headerEdit :: TextDocumentContentChangeEvent
8079
headerEdit =
81-
TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 0 0) (Position 0 0)
82-
.+ #rangeLength .== Nothing
83-
.+ #text .== "-- header comment \n"
80+
TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
81+
{ _range = Range (Position 0 0) (Position 0 0)
82+
, _rangeLength = Nothing
83+
, _text = "-- header comment \n"
84+
}
8485

8586
data DocumentPositions = DocumentPositions {
8687
-- | A position that can be used to generate non null goto-def and completion responses
@@ -241,9 +242,11 @@ experiments =
241242
benchWithSetup
242243
"hole fit suggestions"
243244
( mapM_ $ \DocumentPositions{..} -> do
244-
let edit = TextDocumentContentChangeEvent $ InL $ #range .== Range bottom bottom
245-
.+ #rangeLength .== Nothing
246-
.+ #text .== t
245+
let edit = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
246+
{ _range = Range bottom bottom
247+
, _rangeLength = Nothing
248+
, _text = t
249+
}
247250
bottom = Position maxBound 0
248251
t = T.unlines
249252
[""
@@ -271,9 +274,11 @@ experiments =
271274
benchWithSetup
272275
"eval execute single-line code lens"
273276
( mapM_ $ \DocumentPositions{..} -> do
274-
let edit = TextDocumentContentChangeEvent $ InL $ #range .== Range bottom bottom
275-
.+ #rangeLength .== Nothing
276-
.+ #text .== t
277+
let edit = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
278+
{ _range = Range bottom bottom
279+
, _rangeLength = Nothing
280+
, _text = t
281+
}
277282
bottom = Position maxBound 0
278283
t = T.unlines
279284
[ ""
@@ -296,9 +301,11 @@ experiments =
296301
benchWithSetup
297302
"eval execute multi-line code lens"
298303
( mapM_ $ \DocumentPositions{..} -> do
299-
let edit = TextDocumentContentChangeEvent $ InL $ #range .== Range bottom bottom
300-
.+ #rangeLength .== Nothing
301-
.+ #text .== t
304+
let edit = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
305+
{ _range = Range bottom bottom
306+
, _rangeLength = Nothing
307+
, _text = t
308+
}
302309
bottom = Position maxBound 0
303310
t = T.unlines
304311
[ ""
@@ -552,7 +559,7 @@ runBenchmarksFun dir allBenchmarks = do
552559
lspTestCaps =
553560
fullCaps
554561
& (L.window . _Just) .~ WindowClientCapabilities (Just True) Nothing Nothing
555-
& (L.textDocument . _Just . L.codeAction . _Just . L.resolveSupport . _Just) .~ (#properties .== ["edit"])
562+
& (L.textDocument . _Just . L.codeAction . _Just . L.resolveSupport . _Just) .~ (ClientCodeActionResolveOptions ["edit"])
556563
& (L.textDocument . _Just . L.codeAction . _Just . L.dataSupport . _Just) .~ True
557564

558565
showMs :: Seconds -> String
@@ -756,10 +763,12 @@ setupDocumentContents config =
756763

757764
-- Setup the special positions used by the experiments
758765
lastLine <- fromIntegral . length . T.lines <$> documentContents doc
759-
changeDoc doc [TextDocumentContentChangeEvent $ InL
760-
$ #range .== Range (Position lastLine 0) (Position lastLine 0)
761-
.+ #rangeLength .== Nothing
762-
.+ #text .== T.unlines [ "_hygienic = \"hygienic\"" ]]
766+
changeDoc doc [TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
767+
{ _range = Range (Position lastLine 0) (Position lastLine 0)
768+
, _rangeLength = Nothing
769+
, _text = T.unlines [ "_hygienic = \"hygienic\"" ]
770+
}
771+
]
763772
let
764773
-- Points to a string in the target file,
765774
-- convenient for hygienic edits

ghcide/ghcide.cabal

-1
Original file line numberDiff line numberDiff line change
@@ -347,7 +347,6 @@ test-suite ghcide-tests
347347
, QuickCheck
348348
, random
349349
, regex-tdfa ^>=1.3.1
350-
, row-types
351350
, shake
352351
, sqlite-simple
353352
, stm

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

+4-3
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# LANGUAGE OverloadedLabels #-}
21
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
32
-- SPDX-License-Identifier: Apache-2.0
43
module Development.IDE.Core.PositionMapping
@@ -25,13 +24,15 @@ module Development.IDE.Core.PositionMapping
2524
) where
2625

2726
import Control.DeepSeq
27+
import Control.Lens ((^.))
2828
import Control.Monad
2929
import Data.Algorithm.Diff
3030
import Data.Bifunctor
3131
import Data.List
3232
import Data.Row
3333
import qualified Data.Text as T
3434
import qualified Data.Vector.Unboxed as V
35+
import qualified Language.LSP.Protocol.Lens as L
3536
import Language.LSP.Protocol.Types (Position (Position),
3637
Range (Range),
3738
TextDocumentContentChangeEvent (TextDocumentContentChangeEvent),
@@ -131,8 +132,8 @@ addOldDelta delta (PositionMapping pm) = PositionMapping (composeDelta pm delta)
131132
-- that was what was done with lsp* 1.6 packages
132133
applyChange :: PositionDelta -> TextDocumentContentChangeEvent -> PositionDelta
133134
applyChange PositionDelta{..} (TextDocumentContentChangeEvent (InL x)) = PositionDelta
134-
{ toDelta = toCurrent (x .! #range) (x .! #text) <=< toDelta
135-
, fromDelta = fromDelta <=< fromCurrent (x .! #range) (x .! #text)
135+
{ toDelta = toCurrent (x ^. L.range) (x ^. L.text) <=< toDelta
136+
, fromDelta = fromDelta <=< fromCurrent (x ^. L.range) (x ^. L.text)
136137
}
137138
applyChange posMapping _ = posMapping
138139

ghcide/src/Development/IDE/Plugin/Completions/Logic.hs

+1-2
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
{-# LANGUAGE DuplicateRecordFields #-}
33
{-# LANGUAGE GADTs #-}
44
{-# LANGUAGE MultiWayIf #-}
5-
{-# LANGUAGE OverloadedLabels #-}
65

76
-- Mostly taken from "haskell-ide-engine"
87
module Development.IDE.Plugin.Completions.Logic (
@@ -530,7 +529,7 @@ toggleSnippets ClientCapabilities {_textDocument} CompletionsConfig{..} =
530529
removeSnippetsWhen (not $ enableSnippets && supported)
531530
where
532531
supported =
533-
Just True == (_textDocument >>= _completion >>= view L.completionItem >>= (\x -> x .! #snippetSupport))
532+
Just True == (_textDocument >>= _completion >>= view L.completionItem >>= view L.snippetSupport)
534533

535534
toggleAutoExtend :: CompletionsConfig -> CompItem -> CompItem
536535
toggleAutoExtend CompletionsConfig{enableAutoExtend=False} x = x {additionalTextEdits = Nothing}

ghcide/test/exe/CompletionTests.hs

+2-4
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11

2-
{-# LANGUAGE GADTs #-}
3-
{-# LANGUAGE OverloadedLabels #-}
2+
{-# LANGUAGE GADTs #-}
43

54
module CompletionTests (tests) where
65

@@ -11,7 +10,6 @@ import Control.Monad.IO.Class (liftIO)
1110
import Data.Default
1211
import Data.List.Extra
1312
import Data.Maybe
14-
import Data.Row
1513
import qualified Data.Text as T
1614
import Development.IDE.GHC.Compat (GhcVersion (..), ghcVersion)
1715
import Development.IDE.Test (waitForTypecheck)
@@ -190,7 +188,7 @@ localCompletionTests = [
190188
doc <- createDoc "A.hs" "haskell" $ src "AAA"
191189
void $ waitForTypecheck doc
192190
let editA rhs =
193-
changeDoc doc [TextDocumentContentChangeEvent . InR . (.==) #text $ src rhs]
191+
changeDoc doc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ src rhs]
194192
editA "AAAA"
195193
void $ waitForTypecheck doc
196194
editA "AAAAA"

ghcide/test/exe/CradleTests.hs

+7-7
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,10 @@
11

2-
{-# LANGUAGE GADTs #-}
3-
{-# LANGUAGE OverloadedLabels #-}
2+
{-# LANGUAGE GADTs #-}
43

54
module CradleTests (tests) where
65

76
import Control.Applicative.Combinators
87
import Control.Monad.IO.Class (liftIO)
9-
import Data.Row
108
import qualified Data.Text as T
119
import Development.IDE.GHC.Compat (GhcVersion (..))
1210
import Development.IDE.GHC.Util
@@ -63,7 +61,7 @@ loadCradleOnlyonce = testGroup "load cradle only once"
6361
doc <- createDoc "B.hs" "haskell" "module B where\nimport Data.Foo"
6462
msgs <- someTill (skipManyTill anyMessage cradleLoadedMessage) (skipManyTill anyMessage (message SMethod_TextDocumentPublishDiagnostics))
6563
liftIO $ length msgs @?= 1
66-
changeDoc doc [TextDocumentContentChangeEvent . InR . (.==) #text $ "module B where\nimport Data.Maybe"]
64+
changeDoc doc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ "module B where\nimport Data.Maybe"]
6765
msgs <- manyTill (skipManyTill anyMessage cradleLoadedMessage) (skipManyTill anyMessage (message SMethod_TextDocumentPublishDiagnostics))
6866
liftIO $ length msgs @?= 0
6967
_ <- createDoc "A.hs" "haskell" "module A where\nimport LoadCradleBar"
@@ -222,9 +220,11 @@ sessionDepsArePickedUp = testSession'
222220
[FileEvent (filePathToUri $ dir </> "hie.yaml") FileChangeType_Changed ]
223221
-- Send change event.
224222
let change =
225-
TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 4 0) (Position 4 0)
226-
.+ #rangeLength .== Nothing
227-
.+ #text .== "\n"
223+
TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
224+
{ _range = Range (Position 4 0) (Position 4 0)
225+
, _rangeLength = Nothing
226+
, _text = "\n"
227+
}
228228
changeDoc doc [change]
229229
-- Now no errors.
230230
expectDiagnostics [("Foo.hs", [])]

ghcide/test/exe/DependentFileTest.hs

+6-6
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,9 @@
11

2-
{-# LANGUAGE GADTs #-}
3-
{-# LANGUAGE OverloadedLabels #-}
2+
{-# LANGUAGE GADTs #-}
43

54
module DependentFileTest (tests) where
65

76
import Control.Monad.IO.Class (liftIO)
8-
import Data.Row
97
import qualified Data.Text as T
108
import Development.IDE.Test (expectDiagnostics)
119
import Development.IDE.Types.Location
@@ -51,8 +49,10 @@ tests = testGroup "addDependentFile"
5149
[FileEvent (filePathToUri "dep-file.txt") FileChangeType_Changed ]
5250

5351
-- Modifying Baz will now trigger Foo to be rebuilt as well
54-
let change = TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 2 0) (Position 2 6)
55-
.+ #rangeLength .== Nothing
56-
.+ #text .== "f = ()"
52+
let change = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
53+
{ _range = Range (Position 2 0) (Position 2 6)
54+
, _rangeLength = Nothing
55+
, _text = "f = ()"
56+
}
5757
changeDoc doc [change]
5858
expectDiagnostics [("Foo.hs", [])]

0 commit comments

Comments
 (0)