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)
4342import Data.List
4443import Data.Maybe
4544import Data.Proxy
46- import Data.Row hiding (switch )
4745import Data.Text (Text )
4846import qualified Data.Text as T
4947import Data.Version
5048import Development.IDE.Plugin.Test
5149import Development.IDE.Test.Diagnostic
52- import Development.Shake (CmdOption (Cwd , FileStdout ),
53- cmd_ )
50+ import Development.Shake (CmdOption (Cwd ), cmd_ )
5451import Experiments.Types
5552import Language.LSP.Protocol.Capabilities
5653import qualified Language.LSP.Protocol.Lens as L
@@ -72,15 +69,19 @@ import Text.Printf
7269
7370charEdit :: Position -> TextDocumentContentChangeEvent
7471charEdit 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
7978headerEdit :: TextDocumentContentChangeEvent
8079headerEdit =
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
8586data 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
558565showMs :: 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
0 commit comments