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,7 +42,6 @@ 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
@@ -71,15 +69,19 @@ import Text.Printf
7169
7270charEdit :: Position -> TextDocumentContentChangeEvent
7371charEdit p =
74- TextDocumentContentChangeEvent $ InL $ # range .== Range p p
75- .+ # rangeLength .== Nothing
76- .+ # text .== " a"
72+ TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
73+ { _range = Range p p
74+ , _rangeLength = Nothing
75+ , _text = " a"
76+ }
7777
7878headerEdit :: TextDocumentContentChangeEvent
7979headerEdit =
80- TextDocumentContentChangeEvent $ InL $ # range .== Range (Position 0 0 ) (Position 0 0 )
81- .+ # rangeLength .== Nothing
82- .+ # 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+ }
8385
8486data DocumentPositions = DocumentPositions {
8587 -- | A position that can be used to generate non null goto-def and completion responses
@@ -240,9 +242,11 @@ experiments =
240242 benchWithSetup
241243 " hole fit suggestions"
242244 ( mapM_ $ \ DocumentPositions {.. } -> do
243- let edit = TextDocumentContentChangeEvent $ InL $ # range .== Range bottom bottom
244- .+ # rangeLength .== Nothing
245- .+ # text .== t
245+ let edit = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
246+ { _range = Range bottom bottom
247+ , _rangeLength = Nothing
248+ , _text = t
249+ }
246250 bottom = Position maxBound 0
247251 t = T. unlines
248252 [" "
@@ -270,9 +274,11 @@ experiments =
270274 benchWithSetup
271275 " eval execute single-line code lens"
272276 ( mapM_ $ \ DocumentPositions {.. } -> do
273- let edit = TextDocumentContentChangeEvent $ InL $ # range .== Range bottom bottom
274- .+ # rangeLength .== Nothing
275- .+ # text .== t
277+ let edit = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
278+ { _range = Range bottom bottom
279+ , _rangeLength = Nothing
280+ , _text = t
281+ }
276282 bottom = Position maxBound 0
277283 t = T. unlines
278284 [ " "
@@ -295,9 +301,11 @@ experiments =
295301 benchWithSetup
296302 " eval execute multi-line code lens"
297303 ( mapM_ $ \ DocumentPositions {.. } -> do
298- let edit = TextDocumentContentChangeEvent $ InL $ # range .== Range bottom bottom
299- .+ # rangeLength .== Nothing
300- .+ # text .== t
304+ let edit = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial
305+ { _range = Range bottom bottom
306+ , _rangeLength = Nothing
307+ , _text = t
308+ }
301309 bottom = Position maxBound 0
302310 t = T. unlines
303311 [ " "
@@ -551,7 +559,7 @@ runBenchmarksFun dir allBenchmarks = do
551559 lspTestCaps =
552560 fullCaps
553561 & (L. window . _Just) .~ WindowClientCapabilities (Just True ) Nothing Nothing
554- & (L. textDocument . _Just . L. codeAction . _Just . L. resolveSupport . _Just) .~ (# properties .== [" edit" ])
562+ & (L. textDocument . _Just . L. codeAction . _Just . L. resolveSupport . _Just) .~ (ClientCodeActionResolveOptions [" edit" ])
555563 & (L. textDocument . _Just . L. codeAction . _Just . L. dataSupport . _Just) .~ True
556564
557565showMs :: Seconds -> String
@@ -755,10 +763,12 @@ setupDocumentContents config =
755763
756764 -- Setup the special positions used by the experiments
757765 lastLine <- fromIntegral . length . T. lines <$> documentContents doc
758- changeDoc doc [TextDocumentContentChangeEvent $ InL
759- $ # range .== Range (Position lastLine 0 ) (Position lastLine 0 )
760- .+ # rangeLength .== Nothing
761- .+ # 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+ ]
762772 let
763773 -- Points to a string in the target file,
764774 -- convenient for hygienic edits
0 commit comments