diff --git a/cabal.project b/cabal.project index e2b5c04dc1..7ac27d87fe 100644 --- a/cabal.project +++ b/cabal.project @@ -42,3 +42,11 @@ constraints: -- We want to be able to benefit from the performance optimisations -- in the future, thus: TODO: remove this flag. bitvec -simd + +source-repository-package + type:git + location: https://github.com/jhrcek/lsp + tag: 618e5d5955595518b85cf7234f8bb8fe994fab92 + subdir: lsp + subdir: lsp-test + subdir: lsp-types diff --git a/ghcide-bench/src/Experiments.hs b/ghcide-bench/src/Experiments.hs index 10d79ac75f..a1ecdccf7c 100644 --- a/ghcide-bench/src/Experiments.hs +++ b/ghcide-bench/src/Experiments.hs @@ -2,7 +2,6 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE ImplicitParams #-} {-# LANGUAGE ImpredicativeTypes #-} -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -Wno-deprecations -Wno-unticked-promoted-constructors #-} @@ -43,13 +42,12 @@ import Data.Either (fromRight) import Data.List import Data.Maybe import Data.Proxy -import Data.Row hiding (switch) import Data.Text (Text) import qualified Data.Text as T import Data.Version import Development.IDE.Plugin.Test import Development.IDE.Test.Diagnostic -import Development.Shake (CmdOption (Cwd, FileStdout), +import Development.Shake (CmdOption (Cwd), cmd_) import Experiments.Types import Language.LSP.Protocol.Capabilities @@ -72,15 +70,19 @@ import Text.Printf charEdit :: Position -> TextDocumentContentChangeEvent charEdit p = - TextDocumentContentChangeEvent $ InL $ #range .== Range p p - .+ #rangeLength .== Nothing - .+ #text .== "a" + TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range p p + , _rangeLength = Nothing + , _text = "a" + } headerEdit :: TextDocumentContentChangeEvent headerEdit = - TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 0 0) (Position 0 0) - .+ #rangeLength .== Nothing - .+ #text .== "-- header comment \n" + TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range (Position 0 0) (Position 0 0) + , _rangeLength = Nothing + , _text = "-- header comment \n" + } data DocumentPositions = DocumentPositions { -- | A position that can be used to generate non null goto-def and completion responses @@ -241,9 +243,11 @@ experiments = benchWithSetup "hole fit suggestions" ( mapM_ $ \DocumentPositions{..} -> do - let edit = TextDocumentContentChangeEvent $ InL $ #range .== Range bottom bottom - .+ #rangeLength .== Nothing - .+ #text .== t + let edit = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range bottom bottom + , _rangeLength = Nothing + , _text = t + } bottom = Position maxBound 0 t = T.unlines ["" @@ -271,9 +275,11 @@ experiments = benchWithSetup "eval execute single-line code lens" ( mapM_ $ \DocumentPositions{..} -> do - let edit = TextDocumentContentChangeEvent $ InL $ #range .== Range bottom bottom - .+ #rangeLength .== Nothing - .+ #text .== t + let edit = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range bottom bottom + , _rangeLength = Nothing + , _text = t + } bottom = Position maxBound 0 t = T.unlines [ "" @@ -296,9 +302,11 @@ experiments = benchWithSetup "eval execute multi-line code lens" ( mapM_ $ \DocumentPositions{..} -> do - let edit = TextDocumentContentChangeEvent $ InL $ #range .== Range bottom bottom - .+ #rangeLength .== Nothing - .+ #text .== t + let edit = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range bottom bottom + , _rangeLength = Nothing + , _text = t + } bottom = Position maxBound 0 t = T.unlines [ "" @@ -552,7 +560,7 @@ runBenchmarksFun dir allBenchmarks = do lspTestCaps = fullCaps & (L.window . _Just) .~ WindowClientCapabilities (Just True) Nothing Nothing - & (L.textDocument . _Just . L.codeAction . _Just . L.resolveSupport . _Just) .~ (#properties .== ["edit"]) + & (L.textDocument . _Just . L.codeAction . _Just . L.resolveSupport . _Just) .~ (ClientCodeActionResolveOptions ["edit"]) & (L.textDocument . _Just . L.codeAction . _Just . L.dataSupport . _Just) .~ True showMs :: Seconds -> String @@ -756,10 +764,12 @@ setupDocumentContents config = -- Setup the special positions used by the experiments lastLine <- fromIntegral . length . T.lines <$> documentContents doc - changeDoc doc [TextDocumentContentChangeEvent $ InL - $ #range .== Range (Position lastLine 0) (Position lastLine 0) - .+ #rangeLength .== Nothing - .+ #text .== T.unlines [ "_hygienic = \"hygienic\"" ]] + changeDoc doc [TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range (Position lastLine 0) (Position lastLine 0) + , _rangeLength = Nothing + , _text = T.unlines [ "_hygienic = \"hygienic\"" ] + } + ] let -- Points to a string in the target file, -- convenient for hygienic edits diff --git a/ghcide/ghcide.cabal b/ghcide/ghcide.cabal index 16aeaa06de..5586a8a4ad 100644 --- a/ghcide/ghcide.cabal +++ b/ghcide/ghcide.cabal @@ -332,7 +332,6 @@ test-suite ghcide-tests , QuickCheck , random , regex-tdfa ^>=1.3.1 - , row-types , shake , sqlite-simple , stm diff --git a/ghcide/src/Development/IDE/Core/PositionMapping.hs b/ghcide/src/Development/IDE/Core/PositionMapping.hs index d04856389c..95e3a30cae 100644 --- a/ghcide/src/Development/IDE/Core/PositionMapping.hs +++ b/ghcide/src/Development/IDE/Core/PositionMapping.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE OverloadedLabels #-} -- Copyright (c) 2019 The DAML Authors. All rights reserved. -- SPDX-License-Identifier: Apache-2.0 module Development.IDE.Core.PositionMapping @@ -25,6 +24,7 @@ module Development.IDE.Core.PositionMapping ) where import Control.DeepSeq +import Control.Lens ((^.)) import Control.Monad import Data.Algorithm.Diff import Data.Bifunctor @@ -32,6 +32,7 @@ import Data.List import Data.Row import qualified Data.Text as T import qualified Data.Vector.Unboxed as V +import qualified Language.LSP.Protocol.Lens as L import Language.LSP.Protocol.Types (Position (Position), Range (Range), TextDocumentContentChangeEvent (TextDocumentContentChangeEvent), @@ -131,8 +132,8 @@ addOldDelta delta (PositionMapping pm) = PositionMapping (composeDelta pm delta) -- that was what was done with lsp* 1.6 packages applyChange :: PositionDelta -> TextDocumentContentChangeEvent -> PositionDelta applyChange PositionDelta{..} (TextDocumentContentChangeEvent (InL x)) = PositionDelta - { toDelta = toCurrent (x .! #range) (x .! #text) <=< toDelta - , fromDelta = fromDelta <=< fromCurrent (x .! #range) (x .! #text) + { toDelta = toCurrent (x ^. L.range) (x ^. L.text) <=< toDelta + , fromDelta = fromDelta <=< fromCurrent (x ^. L.range) (x ^. L.text) } applyChange posMapping _ = posMapping diff --git a/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs b/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs index 204bd4d388..99fe6e6294 100644 --- a/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs +++ b/ghcide/src/Development/IDE/Plugin/Completions/Logic.hs @@ -2,7 +2,6 @@ {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiWayIf #-} -{-# LANGUAGE OverloadedLabels #-} -- Mostly taken from "haskell-ide-engine" module Development.IDE.Plugin.Completions.Logic ( @@ -530,7 +529,7 @@ toggleSnippets ClientCapabilities {_textDocument} CompletionsConfig{..} = removeSnippetsWhen (not $ enableSnippets && supported) where supported = - Just True == (_textDocument >>= _completion >>= view L.completionItem >>= (\x -> x .! #snippetSupport)) + Just True == (_textDocument >>= _completion >>= view L.completionItem >>= view L.snippetSupport) toggleAutoExtend :: CompletionsConfig -> CompItem -> CompItem toggleAutoExtend CompletionsConfig{enableAutoExtend=False} x = x {additionalTextEdits = Nothing} diff --git a/ghcide/test/exe/CompletionTests.hs b/ghcide/test/exe/CompletionTests.hs index cf3198e74d..430d42686f 100644 --- a/ghcide/test/exe/CompletionTests.hs +++ b/ghcide/test/exe/CompletionTests.hs @@ -1,6 +1,5 @@ -{-# LANGUAGE GADTs #-} -{-# LANGUAGE OverloadedLabels #-} +{-# LANGUAGE GADTs #-} module CompletionTests (tests) where @@ -11,7 +10,6 @@ import Control.Monad.IO.Class (liftIO) import Data.Default import Data.List.Extra import Data.Maybe -import Data.Row import qualified Data.Text as T import Development.IDE.GHC.Compat (GhcVersion (..), ghcVersion) import Development.IDE.Test (waitForTypecheck) @@ -190,7 +188,7 @@ localCompletionTests = [ doc <- createDoc "A.hs" "haskell" $ src "AAA" void $ waitForTypecheck doc let editA rhs = - changeDoc doc [TextDocumentContentChangeEvent . InR . (.==) #text $ src rhs] + changeDoc doc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ src rhs] editA "AAAA" void $ waitForTypecheck doc editA "AAAAA" diff --git a/ghcide/test/exe/CradleTests.hs b/ghcide/test/exe/CradleTests.hs index a0a6cc364b..db71fb38f0 100644 --- a/ghcide/test/exe/CradleTests.hs +++ b/ghcide/test/exe/CradleTests.hs @@ -1,12 +1,10 @@ -{-# LANGUAGE GADTs #-} -{-# LANGUAGE OverloadedLabels #-} +{-# LANGUAGE GADTs #-} module CradleTests (tests) where import Control.Applicative.Combinators import Control.Monad.IO.Class (liftIO) -import Data.Row import qualified Data.Text as T import Development.IDE.GHC.Compat (GhcVersion (..)) import Development.IDE.GHC.Util @@ -63,7 +61,7 @@ loadCradleOnlyonce = testGroup "load cradle only once" doc <- createDoc "B.hs" "haskell" "module B where\nimport Data.Foo" msgs <- someTill (skipManyTill anyMessage cradleLoadedMessage) (skipManyTill anyMessage (message SMethod_TextDocumentPublishDiagnostics)) liftIO $ length msgs @?= 1 - changeDoc doc [TextDocumentContentChangeEvent . InR . (.==) #text $ "module B where\nimport Data.Maybe"] + changeDoc doc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ "module B where\nimport Data.Maybe"] msgs <- manyTill (skipManyTill anyMessage cradleLoadedMessage) (skipManyTill anyMessage (message SMethod_TextDocumentPublishDiagnostics)) liftIO $ length msgs @?= 0 _ <- createDoc "A.hs" "haskell" "module A where\nimport LoadCradleBar" @@ -222,9 +220,11 @@ sessionDepsArePickedUp = testSession' [FileEvent (filePathToUri $ dir "hie.yaml") FileChangeType_Changed ] -- Send change event. let change = - TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 4 0) (Position 4 0) - .+ #rangeLength .== Nothing - .+ #text .== "\n" + TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range (Position 4 0) (Position 4 0) + , _rangeLength = Nothing + , _text = "\n" + } changeDoc doc [change] -- Now no errors. expectDiagnostics [("Foo.hs", [])] diff --git a/ghcide/test/exe/DependentFileTest.hs b/ghcide/test/exe/DependentFileTest.hs index d5fff45bea..7b07bb38c2 100644 --- a/ghcide/test/exe/DependentFileTest.hs +++ b/ghcide/test/exe/DependentFileTest.hs @@ -1,11 +1,9 @@ -{-# LANGUAGE GADTs #-} -{-# LANGUAGE OverloadedLabels #-} +{-# LANGUAGE GADTs #-} module DependentFileTest (tests) where import Control.Monad.IO.Class (liftIO) -import Data.Row import qualified Data.Text as T import Development.IDE.Test (expectDiagnostics) import Development.IDE.Types.Location @@ -51,8 +49,10 @@ tests = testGroup "addDependentFile" [FileEvent (filePathToUri "dep-file.txt") FileChangeType_Changed ] -- Modifying Baz will now trigger Foo to be rebuilt as well - let change = TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 2 0) (Position 2 6) - .+ #rangeLength .== Nothing - .+ #text .== "f = ()" + let change = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range (Position 2 0) (Position 2 6) + , _rangeLength = Nothing + , _text = "f = ()" + } changeDoc doc [change] expectDiagnostics [("Foo.hs", [])] diff --git a/ghcide/test/exe/DiagnosticTests.hs b/ghcide/test/exe/DiagnosticTests.hs index 4daab55efb..8f56d820ea 100644 --- a/ghcide/test/exe/DiagnosticTests.hs +++ b/ghcide/test/exe/DiagnosticTests.hs @@ -1,6 +1,4 @@ - -{-# LANGUAGE GADTs #-} -{-# LANGUAGE OverloadedLabels #-} +{-# LANGUAGE GADTs #-} module DiagnosticTests (tests) where @@ -9,7 +7,6 @@ import qualified Control.Lens as Lens import Control.Monad import Control.Monad.IO.Class (liftIO) import Data.List.Extra -import Data.Row import qualified Data.Text as T import Development.IDE.GHC.Compat (GhcVersion (..), ghcVersion) import Development.IDE.GHC.Util @@ -46,9 +43,11 @@ tests = testGroup "diagnostics" let content = T.unlines [ "module Testing wher" ] doc <- createDoc "Testing.hs" "haskell" content expectDiagnostics [("Testing.hs", [(DiagnosticSeverity_Error, (0, 15), "parse error")])] - let change = TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 0 15) (Position 0 19) - .+ #rangeLength .== Nothing - .+ #text .== "where" + let change = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range (Position 0 15) (Position 0 19) + , _rangeLength = Nothing + , _text = "where" + } changeDoc doc [change] expectDiagnostics [("Testing.hs", [])] , testSessionWait "introduce syntax error" $ do @@ -56,18 +55,22 @@ tests = testGroup "diagnostics" doc <- createDoc "Testing.hs" "haskell" content void $ skipManyTill anyMessage (message SMethod_WindowWorkDoneProgressCreate) waitForProgressBegin - let change = TextDocumentContentChangeEvent$ InL $ #range .== Range (Position 0 15) (Position 0 18) - .+ #rangeLength .== Nothing - .+ #text .== "wher" + let change = TextDocumentContentChangeEvent$ InL TextDocumentContentChangePartial + { _range = Range (Position 0 15) (Position 0 18) + , _rangeLength = Nothing + , _text = "wher" + } changeDoc doc [change] expectDiagnostics [("Testing.hs", [(DiagnosticSeverity_Error, (0, 15), "parse error")])] , testSessionWait "update syntax error" $ do let content = T.unlines [ "module Testing(missing) where" ] doc <- createDoc "Testing.hs" "haskell" content expectDiagnostics [("Testing.hs", [(DiagnosticSeverity_Error, (0, 15), "Not in scope: 'missing'")])] - let change = TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 0 15) (Position 0 16) - .+ #rangeLength .== Nothing - .+ #text .== "l" + let change = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range (Position 0 15) (Position 0 16) + , _rangeLength = Nothing + , _text = "l" + } changeDoc doc [change] expectDiagnostics [("Testing.hs", [(DiagnosticSeverity_Error, (0, 15), "Not in scope: 'lissing'")])] , testSessionWait "variable not in scope" $ do @@ -143,9 +146,11 @@ tests = testGroup "diagnostics" , "import ModuleA" ] _ <- createDoc "ModuleB.hs" "haskell" contentB - let change = TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 0 0) (Position 0 20) - .+ #rangeLength .== Nothing - .+ #text .== "" + let change = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range (Position 0 0) (Position 0 20) + , _rangeLength = Nothing + , _text = "" + } changeDoc docA [change] expectDiagnostics [("ModuleB.hs", [(DiagnosticSeverity_Error, (1, 0), "Could not find module")])] , testSessionWait "add missing module" $ do @@ -397,7 +402,7 @@ tests = testGroup "diagnostics" -- Check that if we put a lower-case drive in for A.A -- the diagnostics for A.B will also be lower-case. liftIO $ fileUri @?= uriB - let msg :: T.Text = (head diags) ^. L.message + let msg :: T.Text = head diags ^. L.message liftIO $ unless ("redundant" `T.isInfixOf` msg) $ assertFailure ("Expected redundant import but got " <> T.unpack msg) closeDoc a @@ -463,7 +468,7 @@ tests = testGroup "diagnostics" [("P.hs", [(DiagnosticSeverity_Warning,(4,0), "Top-level binding")])] -- So that we know P has been loaded -- Change y from Int to B which introduces a type error in A (imported from P) - changeDoc bdoc [TextDocumentContentChangeEvent . InR . (.==) #text $ + changeDoc bdoc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ T.unlines ["module B where", "y :: Bool", "y = undefined"]] expectDiagnostics [("A.hs", [(DiagnosticSeverity_Error, (5, 4), "Couldn't match expected type 'Int' with actual type 'Bool'")]) @@ -471,7 +476,7 @@ tests = testGroup "diagnostics" -- Open A and edit to fix the type error adoc <- createDoc aPath "haskell" aSource - changeDoc adoc [TextDocumentContentChangeEvent . InR . (.==) #text $ + changeDoc adoc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ T.unlines ["module A where", "import B", "x :: Bool", "x = y"]] expectDiagnostics @@ -489,10 +494,10 @@ tests = testGroup "diagnostics" doc <- createDoc "Foo.hs" "haskell" fooContent expectDiagnostics [("Foo.hs", [(DiagnosticSeverity_Error, (1,7), "Could not find module 'MissingModule'")])] - changeDoc doc [TextDocumentContentChangeEvent . InR . (.==) #text $ "module Foo() where" ] + changeDoc doc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ "module Foo() where" ] expectDiagnostics [] - changeDoc doc [TextDocumentContentChangeEvent . InR . (.==) #text $ T.unlines + changeDoc doc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ T.unlines [ "module Foo() where" , "import MissingModule" ] ] expectDiagnostics [("Foo.hs", [(DiagnosticSeverity_Error, (1,7), "Could not find module 'MissingModule'")])] @@ -504,12 +509,18 @@ tests = testGroup "diagnostics" ] where editPair x y = let p = Position x y ; p' = Position x (y+2) in - (TextDocumentContentChangeEvent $ InL $ #range .== Range p p - .+ #rangeLength .== Nothing - .+ #text .== "fd" - ,TextDocumentContentChangeEvent $ InL $ #range .== Range p p' - .+ #rangeLength .== Nothing - .+ #text .== "") + (TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range p p + , _rangeLength = Nothing + , _text = "fd" + } + + ,TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range p' p' + , _rangeLength = Nothing + , _text = "" + } + ) editHeader = editPair 0 0 editImport = editPair 2 10 editBody = editPair 3 10 diff --git a/ghcide/test/exe/GarbageCollectionTests.hs b/ghcide/test/exe/GarbageCollectionTests.hs index d7033a8439..31b705c0f3 100644 --- a/ghcide/test/exe/GarbageCollectionTests.hs +++ b/ghcide/test/exe/GarbageCollectionTests.hs @@ -1,10 +1,6 @@ - -{-# LANGUAGE OverloadedLabels #-} - module GarbageCollectionTests (tests) where import Control.Monad.IO.Class (liftIO) -import Data.Row import qualified Data.Set as Set import qualified Data.Text as T import Development.IDE.Test (expectCurrentDiagnostics, @@ -15,7 +11,6 @@ import Language.LSP.Protocol.Types hiding (SemanticTokenAbsolute (..), SemanticTokensEdit (..), mkRange) import Language.LSP.Test import System.FilePath --- import Test.QuickCheck.Instances () import Test.Tasty import Test.Tasty.HUnit import TestUtils @@ -74,14 +69,14 @@ tests = testGroup "garbage collection" , "a = ()" ] doc <- generateGarbage "A" dir - changeDoc doc [TextDocumentContentChangeEvent . InR . (.==) #text $ edit] + changeDoc doc [TextDocumentContentChangeEvent . InR $ TextDocumentContentChangeWholeDocument edit] builds <- waitForTypecheck doc liftIO $ assertBool "it still builds" builds expectCurrentDiagnostics doc [(DiagnosticSeverity_Error, (2,4), "Couldn't match expected type")] ] ] where - isExpected k = any (`T.isPrefixOf` k) ["GhcSessionIO"] + isExpected k = "GhcSessionIO" `T.isPrefixOf` k generateGarbage :: String -> FilePath -> Session TextDocumentIdentifier generateGarbage modName dir = do diff --git a/ghcide/test/exe/IfaceTests.hs b/ghcide/test/exe/IfaceTests.hs index f4967a2656..7731100a3b 100644 --- a/ghcide/test/exe/IfaceTests.hs +++ b/ghcide/test/exe/IfaceTests.hs @@ -1,10 +1,6 @@ - -{-# LANGUAGE OverloadedLabels #-} - module IfaceTests (tests) where import Control.Monad.IO.Class (liftIO) -import Data.Row import qualified Data.Text as T import Development.IDE.GHC.Util import Development.IDE.Test (configureCheckProject, @@ -52,7 +48,7 @@ ifaceTHTest = testCase "iface-th-test" $ runWithExtraFiles "TH" $ \dir -> do liftIO $ writeFileUTF8 aPath (unlines $ init (lines $ T.unpack aSource) ++ ["th_a = [d| a = False|]"]) -- Check that the change propagates to C - changeDoc cdoc [TextDocumentContentChangeEvent . InR . (.==) #text $ cSource] + changeDoc cdoc [TextDocumentContentChangeEvent . InR $ TextDocumentContentChangeWholeDocument cSource] expectDiagnostics [("THC.hs", [(DiagnosticSeverity_Error, (4, 4), "Couldn't match expected type '()' with actual type 'Bool'")]) ,("THB.hs", [(DiagnosticSeverity_Warning, (4,1), "Top-level binding")])] @@ -72,7 +68,9 @@ ifaceErrorTest = testCase "iface-error-test-1" $ runWithExtraFiles "recomp" $ \d [("P.hs", [(DiagnosticSeverity_Warning,(4,0), "Top-level binding")])] -- So what we know P has been loaded -- Change y from Int to B - changeDoc bdoc [TextDocumentContentChangeEvent . InR . (.==) #text $ T.unlines ["module B where", "y :: Bool", "y = undefined"]] + changeDoc bdoc [ TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ + T.unlines [ "module B where", "y :: Bool", "y = undefined"] + ] -- save so that we can that the error propagates to A sendNotification SMethod_TextDocumentDidSave (DidSaveTextDocumentParams bdoc Nothing) @@ -90,7 +88,7 @@ ifaceErrorTest = testCase "iface-error-test-1" $ runWithExtraFiles "recomp" $ \d expectDiagnostics [("P.hs", [(DiagnosticSeverity_Warning,(4,0), "Top-level binding")]) ] - changeDoc pdoc [TextDocumentContentChangeEvent . InR . (.==) #text $ pSource <> "\nfoo = y :: Bool" ] + changeDoc pdoc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ pSource <> "\nfoo = y :: Bool" ] -- Now in P we have -- bar = x :: Int -- foo = y :: Bool @@ -119,10 +117,11 @@ ifaceErrorTest2 = testCase "iface-error-test-2" $ runWithExtraFiles "recomp" $ \ [("P.hs", [(DiagnosticSeverity_Warning,(4,0), "Top-level binding")])] -- So that we know P has been loaded -- Change y from Int to B - changeDoc bdoc [TextDocumentContentChangeEvent . InR . (.==) #text $ T.unlines ["module B where", "y :: Bool", "y = undefined"]] + changeDoc bdoc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ + T.unlines ["module B where", "y :: Bool", "y = undefined"]] -- Add a new definition to P - changeDoc pdoc [TextDocumentContentChangeEvent . InR . (.==) #text $ pSource <> "\nfoo = y :: Bool" ] + changeDoc pdoc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ pSource <> "\nfoo = y :: Bool" ] -- Now in P we have -- bar = x :: Int -- foo = y :: Bool @@ -149,7 +148,7 @@ ifaceErrorTest3 = testCase "iface-error-test-3" $ runWithExtraFiles "recomp" $ \ bdoc <- createDoc bPath "haskell" bSource -- Change y from Int to B - changeDoc bdoc [TextDocumentContentChangeEvent . InR . (.==) #text $ T.unlines ["module B where", "y :: Bool", "y = undefined"]] + changeDoc bdoc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ T.unlines ["module B where", "y :: Bool", "y = undefined"]] -- P should not typecheck, as there are no last valid artifacts for A _pdoc <- createDoc pPath "haskell" pSource diff --git a/ghcide/test/exe/InitializeResponseTests.hs b/ghcide/test/exe/InitializeResponseTests.hs index a980efc12d..aef0bf5666 100644 --- a/ghcide/test/exe/InitializeResponseTests.hs +++ b/ghcide/test/exe/InitializeResponseTests.hs @@ -1,12 +1,10 @@ -{-# LANGUAGE DataKinds #-} -{-# LANGUAGE OverloadedLabels #-} +{-# LANGUAGE DataKinds #-} module InitializeResponseTests (tests) where import Control.Monad import Data.List.Extra -import Data.Row import qualified Data.Text as T import Development.IDE.Plugin.TypeLenses (typeLensCommandId) import qualified Language.LSP.Protocol.Lens as L @@ -60,8 +58,13 @@ tests = withResource acquire release tests where , chk "NO color" (^. L.colorProvider) Nothing , chk "NO folding range" _foldingRangeProvider Nothing , che " execute command" _executeCommandProvider [typeLensCommandId, blockCommandId] - , chk " workspace" (^. L.workspace) (Just $ #workspaceFolders .== Just WorkspaceFoldersServerCapabilities{_supported = Just True, _changeNotifications = Just ( InR True )} - .+ #fileOperations .== Nothing) + , chk " workspace" (^. L.workspace) (Just $ WorkspaceOptions + { _workspaceFolders = Just WorkspaceFoldersServerCapabilities + { _supported = Just True + , _changeNotifications = Just (InR True) + } + , _fileOperations = Nothing + }) , chk "NO experimental" (^. L.experimental) Nothing ] where diff --git a/ghcide/test/exe/PositionMappingTests.hs b/ghcide/test/exe/PositionMappingTests.hs index c48c2fdf8f..dfd9b0374b 100644 --- a/ghcide/test/exe/PositionMappingTests.hs +++ b/ghcide/test/exe/PositionMappingTests.hs @@ -1,10 +1,8 @@ {-# LANGUAGE AllowAmbiguousTypes #-} -{-# LANGUAGE OverloadedLabels #-} module PositionMappingTests (tests) where import qualified Data.EnumMap.Strict as EM -import Data.Row import qualified Data.Text as T import Data.Text.Utf16.Rope.Mixed (Rope) import qualified Data.Text.Utf16.Rope.Mixed as Rope @@ -32,8 +30,7 @@ import Test.Tasty.QuickCheck enumMapMappingTest :: TestTree enumMapMappingTest = testCase "enumMapMappingTest" $ do - let mkChangeEvent :: Range -> Text -> TextDocumentContentChangeEvent - mkChangeEvent r t = TextDocumentContentChangeEvent $ InL $ #range .== r .+ #rangeLength .== Nothing .+ #text .== t + let mkCE :: UInt -> UInt -> UInt -> UInt -> Text -> TextDocumentContentChangeEvent mkCE l1 c1 l2 c2 = mkChangeEvent (Range (Position l1 c1) (Position l2 c2)) events :: [(Int32, [TextDocumentContentChangeEvent])] @@ -45,6 +42,9 @@ enumMapMappingTest = testCase "enumMapMappingTest" $ do updatePose (Position 0 4) @?= Just (Position 0 9) updatePose (Position 0 5) @?= Just (Position 0 10) +mkChangeEvent :: Range -> Text -> TextDocumentContentChangeEvent +mkChangeEvent r t = TextDocumentContentChangeEvent $ InL + TextDocumentContentChangePartial {_range = r, _rangeLength = Nothing, _text = t} tests :: TestTree tests = @@ -167,10 +167,7 @@ tests = rope <- genRope range <- genRange rope PrintableText replacement <- arbitrary - let newRope = runIdentity $ applyChange mempty rope - (TextDocumentContentChangeEvent $ InL $ #range .== range - .+ #rangeLength .== Nothing - .+ #text .== replacement) + let newRope = runIdentity $ applyChange mempty rope $ mkChangeEvent range replacement newPos <- genPosition newRope pure (range, replacement, newPos) forAll diff --git a/ghcide/test/exe/THTests.hs b/ghcide/test/exe/THTests.hs index 975b674549..dc781d90d2 100644 --- a/ghcide/test/exe/THTests.hs +++ b/ghcide/test/exe/THTests.hs @@ -1,10 +1,7 @@ -{-# LANGUAGE OverloadedLabels #-} - module THTests (tests) where import Control.Monad.IO.Class (liftIO) -import Data.Row import qualified Data.Text as T import Development.IDE.GHC.Util import Development.IDE.Test (expectCurrentDiagnostics, @@ -142,9 +139,9 @@ thReloadingTest unboxed = testCase name $ runWithExtraFiles dir $ \dir -> do -- Change th from () to Bool let aSource' = T.unlines $ init (T.lines aSource) ++ ["th_a = [d| a = False|]"] - changeDoc adoc [TextDocumentContentChangeEvent . InR . (.==) #text $ aSource'] + changeDoc adoc [TextDocumentContentChangeEvent . InR $ TextDocumentContentChangeWholeDocument aSource'] -- generate an artificial warning to avoid timing out if the TH change does not propagate - changeDoc cdoc [TextDocumentContentChangeEvent . InR . (.==) #text $ cSource <> "\nfoo=()"] + changeDoc cdoc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ cSource <> "\nfoo=()"] -- Check that the change propagates to C expectDiagnostics @@ -176,11 +173,11 @@ thLinkingTest unboxed = testCase name $ runWithExtraFiles dir $ \dir -> do expectDiagnostics [("THB.hs", [(DiagnosticSeverity_Warning, (4,1), "Top-level binding")])] let aSource' = T.unlines $ init (init (T.lines aSource)) ++ ["th :: DecsQ", "th = [d| a = False|]"] - changeDoc adoc [TextDocumentContentChangeEvent . InR . (.==) #text $ aSource'] + changeDoc adoc [TextDocumentContentChangeEvent . InR $ TextDocumentContentChangeWholeDocument aSource'] -- modify b too let bSource' = T.unlines $ init (T.lines bSource) ++ ["$th"] - changeDoc bdoc [TextDocumentContentChangeEvent . InR . (.==) #text $ bSource'] + changeDoc bdoc [TextDocumentContentChangeEvent . InR $ TextDocumentContentChangeWholeDocument bSource'] waitForProgressBegin waitForAllProgressDone diff --git a/haskell-language-server.cabal b/haskell-language-server.cabal index ad3b6ea097..971171bcbf 100644 --- a/haskell-language-server.cabal +++ b/haskell-language-server.cabal @@ -290,7 +290,6 @@ test-suite hls-cabal-plugin-tests , text , text-rope , transformers - , row-types ----------------------------- -- class plugin @@ -352,7 +351,6 @@ test-suite hls-class-plugin-tests , hls-test-utils == 2.7.0.0 , lens , lsp-types - , row-types , text ----------------------------- @@ -498,7 +496,6 @@ test-suite hls-eval-plugin-tests , lens , lsp-types , text - , row-types ----------------------------- -- import lens plugin @@ -553,7 +550,6 @@ test-suite hls-explicit-imports-plugin-tests , hls-test-utils == 2.7.0.0 , lens , lsp-types - , row-types , text ----------------------------- @@ -591,7 +587,6 @@ library hls-rename-plugin , mtl , mod , syb - , row-types , text , transformers , unordered-containers @@ -758,7 +753,6 @@ test-suite hls-hlint-plugin-tests , hls-test-utils == 2.7.0.0 , lens , lsp-types - , row-types , text ----------------------------- @@ -976,7 +970,6 @@ test-suite hls-splice-plugin-tests , haskell-language-server:hls-splice-plugin , hls-test-utils == 2.7.0.0 , text - , row-types ----------------------------- -- alternate number format plugin @@ -1786,7 +1779,6 @@ test-suite hls-semantic-tokens-plugin-tests , ghcide == 2.7.0.0 , hls-plugin-api == 2.7.0.0 , data-default - , row-types ----------------------------- -- notes plugin diff --git a/hls-graph/src/Development/IDE/Graph/Internal/Database.hs b/hls-graph/src/Development/IDE/Graph/Internal/Database.hs index 76004c0e7f..63e874c87d 100644 --- a/hls-graph/src/Development/IDE/Graph/Internal/Database.hs +++ b/hls-graph/src/Development/IDE/Graph/Internal/Database.hs @@ -25,7 +25,7 @@ import Control.Monad.Trans.Reader import qualified Control.Monad.Trans.State.Strict as State import Data.Dynamic import Data.Either -import Data.Foldable (fold, for_, traverse_) +import Data.Foldable (for_, traverse_) import Data.IORef.Extra import Data.List.NonEmpty (unzip) import Data.Maybe diff --git a/hls-plugin-api/hls-plugin-api.cabal b/hls-plugin-api/hls-plugin-api.cabal index da88df28a0..fd8d968c04 100644 --- a/hls-plugin-api/hls-plugin-api.cabal +++ b/hls-plugin-api/hls-plugin-api.cabal @@ -76,7 +76,6 @@ library , optparse-applicative , prettyprinter , regex-tdfa >=1.3.1.0 - , row-types , stm , text , time diff --git a/hls-plugin-api/src/Ide/Plugin/Resolve.hs b/hls-plugin-api/src/Ide/Plugin/Resolve.hs index c8d448a49e..0657d750ac 100644 --- a/hls-plugin-api/src/Ide/Plugin/Resolve.hs +++ b/hls-plugin-api/src/Ide/Plugin/Resolve.hs @@ -1,6 +1,5 @@ {-# LANGUAGE DisambiguateRecordFields #-} {-# LANGUAGE LambdaCase #-} -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} {-| This module currently includes helper functions to provide fallback support to code actions that use resolve in HLS. The difference between the two @@ -26,7 +25,6 @@ import Control.Monad.Trans.Except (ExceptT (..)) import qualified Data.Aeson as A import Data.Maybe (catMaybes) -import Data.Row ((.!)) import qualified Data.Text as T import GHC.Generics (Generic) import Ide.Logger @@ -190,7 +188,7 @@ supportsCodeActionResolve :: ClientCapabilities -> Bool supportsCodeActionResolve caps = caps ^? L.textDocument . _Just . L.codeAction . _Just . L.dataSupport . _Just == Just True && case caps ^? L.textDocument . _Just . L.codeAction . _Just . L.resolveSupport . _Just of - Just row -> "edit" `elem` row .! #properties + Just ClientCodeActionResolveOptions{_properties} -> "edit" `elem` _properties _ -> False internalError :: T.Text -> PluginError diff --git a/hls-test-utils/hls-test-utils.cabal b/hls-test-utils/hls-test-utils.cabal index a5288da92f..e5b42d128c 100644 --- a/hls-test-utils/hls-test-utils.cabal +++ b/hls-test-utils/hls-test-utils.cabal @@ -54,7 +54,7 @@ library , tasty-rerun , temporary , text - , row-types + ghc-options: -Wall -Wunused-packages if flag(pedantic) diff --git a/hls-test-utils/src/Test/Hls.hs b/hls-test-utils/src/Test/Hls.hs index 38c4b9b7ae..8264cf90e0 100644 --- a/hls-test-utils/src/Test/Hls.hs +++ b/hls-test-utils/src/Test/Hls.hs @@ -167,7 +167,7 @@ goldenWithHaskellDoc -> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree -goldenWithHaskellDoc = goldenWithDoc "haskell" +goldenWithHaskellDoc = goldenWithDoc LanguageKind_Haskell goldenWithHaskellDocInTmpDir :: Pretty b @@ -180,7 +180,7 @@ goldenWithHaskellDocInTmpDir -> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree -goldenWithHaskellDocInTmpDir = goldenWithDocInTmpDir "haskell" +goldenWithHaskellDocInTmpDir = goldenWithDocInTmpDir LanguageKind_Haskell goldenWithHaskellAndCaps :: Pretty b @@ -237,11 +237,11 @@ goldenWithCabalDoc -> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree -goldenWithCabalDoc = goldenWithDoc "cabal" +goldenWithCabalDoc = goldenWithDoc (LanguageKind_Custom "cabal") goldenWithDoc :: Pretty b - => T.Text + => LanguageKind -> Config -> PluginTestDescriptor b -> TestName @@ -251,19 +251,19 @@ goldenWithDoc -> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree -goldenWithDoc fileType config plugin title testDataDir path desc ext act = +goldenWithDoc languageKind config plugin title testDataDir path desc ext act = goldenGitDiff title (testDataDir path <.> desc <.> ext) $ runSessionWithServer config plugin testDataDir $ TL.encodeUtf8 . TL.fromStrict <$> do - doc <- openDoc (path <.> ext) fileType + doc <- openDoc (path <.> ext) languageKind void waitForBuildQueue act doc documentContents doc goldenWithDocInTmpDir :: Pretty b - => T.Text + => LanguageKind -> Config -> PluginTestDescriptor b -> TestName @@ -273,12 +273,12 @@ goldenWithDocInTmpDir -> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree -goldenWithDocInTmpDir fileType config plugin title tree path desc ext act = +goldenWithDocInTmpDir languageKind config plugin title tree path desc ext act = goldenGitDiff title (vftOriginalRoot tree path <.> desc <.> ext) $ runSessionWithServerInTmpDir config plugin tree $ TL.encodeUtf8 . TL.fromStrict <$> do - doc <- openDoc (path <.> ext) fileType + doc <- openDoc (path <.> ext) languageKind void waitForBuildQueue act doc documentContents doc diff --git a/hls-test-utils/src/Test/Hls/Util.hs b/hls-test-utils/src/Test/Hls/Util.hs index 74148be32c..90ec2f07f9 100644 --- a/hls-test-utils/src/Test/Hls/Util.hs +++ b/hls-test-utils/src/Test/Hls/Util.hs @@ -2,7 +2,6 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE GADTs #-} -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} module Test.Hls.Util ( -- * Test Capabilities @@ -58,7 +57,6 @@ import Data.Bool (bool) import Data.Default import Data.List.Extra (find) import Data.Proxy -import Data.Row import qualified Data.Set as Set import qualified Data.Text as T import Development.IDE (GhcVersion (..), ghcVersion) @@ -89,11 +87,11 @@ codeActionSupportCaps = def & L.textDocument ?~ textDocumentCaps where textDocumentCaps = def { _codeAction = Just codeActionCaps } codeActionCaps = CodeActionClientCapabilities (Just True) (Just literalSupport) (Just True) Nothing Nothing Nothing Nothing - literalSupport = #codeActionKind .== (#valueSet .== []) + literalSupport = ClientCodeActionLiteralOptions (ClientCodeActionKindOptions []) codeActionResolveCaps :: ClientCapabilities codeActionResolveCaps = Test.fullCaps - & (L.textDocument . _Just . L.codeAction . _Just . L.resolveSupport . _Just) .~ (#properties .== ["edit"]) + & (L.textDocument . _Just . L.codeAction . _Just . L.resolveSupport . _Just) .~ ClientCodeActionResolveOptions {_properties= ["edit"]} & (L.textDocument . _Just . L.codeAction . _Just . L.dataSupport . _Just) .~ True codeActionNoResolveCaps :: ClientCapabilities diff --git a/plugins/hls-cabal-plugin/test/Main.hs b/plugins/hls-cabal-plugin/test/Main.hs index 3af77d269b..5cf09247ea 100644 --- a/plugins/hls-cabal-plugin/test/Main.hs +++ b/plugins/hls-cabal-plugin/test/Main.hs @@ -1,5 +1,4 @@ {-# LANGUAGE DisambiguateRecordFields #-} -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} module Main ( @@ -12,7 +11,6 @@ import Control.Lens ((^.)) import Control.Monad (guard) import qualified Data.ByteString as BS import Data.Either (isRight) -import Data.Row import qualified Data.Text as T import qualified Data.Text as Text import Ide.Plugin.Cabal.LicenseSuggest (licenseErrorSuggestion) @@ -117,13 +115,11 @@ pluginTests = changeDoc cabalDoc [ TextDocumentContentChangeEvent $ - InL $ - #range - .== theRange - .+ #rangeLength - .== Nothing - .+ #text - .== "MIT3" + InL TextDocumentContentChangePartial + { _range = theRange + , _rangeLength = Nothing + , _text = "MIT3" + } ] cabalDiags <- waitForDiagnosticsFrom cabalDoc unknownLicenseDiag <- liftIO $ inspectDiagnostic cabalDiags ["Unknown SPDX license identifier: 'MIT3'"] diff --git a/plugins/hls-class-plugin/test/Main.hs b/plugins/hls-class-plugin/test/Main.hs index ee5d57ced1..93b23b4aee 100644 --- a/plugins/hls-class-plugin/test/Main.hs +++ b/plugins/hls-class-plugin/test/Main.hs @@ -13,7 +13,6 @@ import Control.Lens (Prism', prism', view, (^.), import Control.Monad (void) import Data.Foldable (find) import Data.Maybe -import Data.Row ((.==)) import qualified Data.Text as T import qualified Ide.Plugin.Class as Class import qualified Language.LSP.Protocol.Lens as L @@ -86,7 +85,7 @@ codeActionTests = testGroup -- Change the doc to ensure the version is not 0 changeDoc doc - [ TextDocumentContentChangeEvent . InR . (.==) #text $ + [ TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ T.unlines ["module Version where", "data A a = A a", "instance Functor A where"] ] ver2 <- (^. L.version) <$> getVersionedDoc doc diff --git a/plugins/hls-eval-plugin/test/Main.hs b/plugins/hls-eval-plugin/test/Main.hs index a7f2524f98..ceb1620bac 100644 --- a/plugins/hls-eval-plugin/test/Main.hs +++ b/plugins/hls-eval-plugin/test/Main.hs @@ -1,5 +1,4 @@ {-# LANGUAGE MultiWayIf #-} -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ViewPatterns #-} @@ -15,7 +14,6 @@ import Data.Aeson.Types (Pair, Result (Success)) import Data.List (isInfixOf) import Data.List.Extra (nubOrdOn) import qualified Data.Map as Map -import Data.Row import qualified Data.Text as T import Ide.Plugin.Config (Config) import qualified Ide.Plugin.Config as Plugin @@ -303,7 +301,7 @@ evalInFile fp e expected = runSessionWithServerInTmpDir def evalPlugin (mkFs $ F doc <- openDoc fp "haskell" origin <- documentContents doc let withEval = origin <> e - changeDoc doc [TextDocumentContentChangeEvent . InR . (.==) #text $ withEval] + changeDoc doc [TextDocumentContentChangeEvent . InR . TextDocumentContentChangeWholeDocument $ withEval] executeLensesBackwards doc result <- fmap T.strip . T.stripPrefix withEval <$> documentContents doc liftIO $ result @?= Just (T.strip expected) diff --git a/plugins/hls-explicit-imports-plugin/test/Main.hs b/plugins/hls-explicit-imports-plugin/test/Main.hs index 667714315b..0fd94a807c 100644 --- a/plugins/hls-explicit-imports-plugin/test/Main.hs +++ b/plugins/hls-explicit-imports-plugin/test/Main.hs @@ -1,6 +1,5 @@ {-# LANGUAGE DisambiguateRecordFields #-} {-# LANGUAGE LambdaCase #-} -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ViewPatterns #-} module Main @@ -10,7 +9,6 @@ module Main import Control.Lens ((^.)) import Data.Either.Extra import Data.Foldable (find) -import Data.Row ((.+), (.==)) import Data.Text (Text) import qualified Data.Text as T import Data.Traversable (for) @@ -93,9 +91,12 @@ codeActionBreakFile fp l c = goldenWithImportActions " code action" fp codeActio case find ((== Just "Make all imports explicit") . caTitle) actions of Just (InR x) -> executeCodeAction x _ -> liftIO $ assertFailure "Unable to find CodeAction" - where edit = TextDocumentContentChangeEvent $ InL $ #range .== pointRange 2 29 - .+ #rangeLength .== Nothing - .+ #text .== "x" + where edit = TextDocumentContentChangeEvent $ InL + TextDocumentContentChangePartial + { _range = pointRange 2 29 + , _rangeLength = Nothing + , _text = "x" + } codeActionStaleAction :: FilePath -> Int -> Int -> TestTree codeActionStaleAction fp l c = goldenWithImportActions " code action" fp codeActionResolveCaps $ \doc -> do @@ -109,9 +110,12 @@ codeActionStaleAction fp l c = goldenWithImportActions " code action" fp codeAct \case Just _ -> liftIO $ assertFailure "Code action still valid" Nothing -> pure () _ -> liftIO $ assertFailure "Unable to find CodeAction" - where edit = TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 6 0) (Position 6 0) - .+ #rangeLength .== Nothing - .+ #text .== "\ntesting = undefined" + where edit = TextDocumentContentChangeEvent $ InL + TextDocumentContentChangePartial + { _range = Range (Position 6 0) (Position 6 0) + , _rangeLength = Nothing + , _text = "\ntesting = undefined" + } codeActionAllResolveGoldenTest :: FilePath -> Int -> Int -> TestTree codeActionAllResolveGoldenTest fp l c = goldenWithImportActions " code action resolve" fp codeActionResolveCaps $ \doc -> do diff --git a/plugins/hls-hlint-plugin/test/Main.hs b/plugins/hls-hlint-plugin/test/Main.hs index 5838b22bf3..4cd15f9dac 100644 --- a/plugins/hls-hlint-plugin/test/Main.hs +++ b/plugins/hls-hlint-plugin/test/Main.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} module Main @@ -12,7 +11,6 @@ import Data.Functor (void) import Data.List (find) import qualified Data.Map as Map import Data.Maybe (fromJust, isJust) -import Data.Row ((.+), (.==)) import qualified Data.Text as T import Ide.Plugin.Config (Config (..)) import qualified Ide.Plugin.Config as Plugin @@ -139,16 +137,22 @@ suggestionsTests = doc <- openDoc "Base.hs" "haskell" testHlintDiagnostics doc - let change = TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 1 8) (Position 1 12) - .+ #rangeLength .== Nothing - .+ #text .== "x" + let change = TextDocumentContentChangeEvent $ InL + TextDocumentContentChangePartial + { _range = Range (Position 1 8) (Position 1 12) + , _rangeLength = Nothing + , _text = "x" + } + changeDoc doc [change] expectNoMoreDiagnostics 3 doc "hlint" - let change' = TextDocumentContentChangeEvent $ InL $ #range .== Range (Position 1 8) (Position 1 12) - .+ #rangeLength .== Nothing - .+ #text .== "id x" - + let change' = TextDocumentContentChangeEvent $ InL + TextDocumentContentChangePartial + { _range = Range (Position 1 8) (Position 1 12) + , _rangeLength = Nothing + , _text = "id x" + } changeDoc doc [change'] testHlintDiagnostics doc diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 757ae5fd26..1b5b27f601 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -25,7 +25,6 @@ import Data.List.NonEmpty (NonEmpty ((:|)), import qualified Data.Map as M import Data.Maybe import Data.Mod.Word -import Data.Row import qualified Data.Set as S import qualified Data.Text as T import Development.IDE (Recorder, WithPriority, @@ -80,7 +79,7 @@ prepareRenameProvider state _pluginId (PrepareRenameParams (TextDocumentIdentifi -- In particular it allows some cases through (e.g. cross-module renames), -- so that the full rename handler can give more informative error about them. let renameValid = not $ null namesUnderCursor - pure $ InL $ PrepareRenameResult $ InR $ InR $ #defaultBehavior .== renameValid + pure $ InL $ PrepareRenameResult $ InR $ InR $ PrepareRenameDefaultBehavior renameValid renameProvider :: PluginMethodHandler IdeState Method_TextDocumentRename renameProvider state pluginId (RenameParams _prog (TextDocumentIdentifier uri) pos newNameText) = do diff --git a/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs b/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs index e8a21396ee..aee10867ab 100644 --- a/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs +++ b/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs @@ -1,6 +1,6 @@ -{-# LANGUAGE DataKinds #-} -{-# LANGUAGE OverloadedLabels #-} -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DisambiguateRecordFields #-} +{-# LANGUAGE OverloadedStrings #-} import Control.Lens ((^.), (^?)) import Control.Monad.IO.Class (liftIO) @@ -15,9 +15,6 @@ import Data.Text hiding (length, map, import qualified Data.Text as Text import qualified Data.Text.Utf16.Rope.Mixed as Rope import Development.IDE (Pretty) - -import Data.Row ((.==)) -import Data.Row.Records ((.+)) import Development.IDE.GHC.Compat (GhcVersion (..), ghcVersion) import Development.IDE.Plugin.Test (WaitForIdeRuleResult (..)) @@ -176,7 +173,7 @@ semanticTokensConfigTest = testGroup "semantic token config test" [ semanticTokensFullDeltaTests :: TestTree semanticTokensFullDeltaTests = - testGroup "semanticTokensFullDeltaTests" $ + testGroup "semanticTokensFullDeltaTests" [ testCase "null delta since unchanged" $ do let file1 = "TModuleA.hs" let expectDelta = InR (InL (SemanticTokensDelta (Just "1") [])) @@ -197,10 +194,11 @@ semanticTokensFullDeltaTests = _ <- waitForAction "TypeCheck" doc1 _ <- Test.getSemanticTokens doc1 -- open the file and append a line to it - let change = TextDocumentContentChangeEvent - $ InL $ #range .== Range (Position 4 0) (Position 4 6) - .+ #rangeLength .== Nothing - .+ #text .== "foo = 1" + let change = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range (Position 4 0) (Position 4 6) + , _rangeLength = Nothing + , _text = "foo = 1" + } changeDoc doc1 [change] _ <- waitForAction "TypeCheck" doc1 delta <- getSemanticTokensFullDelta doc1 "0" @@ -215,10 +213,11 @@ semanticTokensFullDeltaTests = _ <- waitForAction "TypeCheck" doc1 _ <- Test.getSemanticTokens doc1 -- open the file and append a line to it - let change = TextDocumentContentChangeEvent - $ InL $ #range .== Range (Position 2 0) (Position 2 28) - .+ #rangeLength .== Nothing - .+ #text .== Text.replicate 28 " " + let change = TextDocumentContentChangeEvent $ InL TextDocumentContentChangePartial + { _range = Range (Position 2 0) (Position 2 28) + , _rangeLength = Nothing + , _text = Text.replicate 28 " " + } changeDoc doc1 [change] _ <- waitForAction "TypeCheck" doc1 delta <- getSemanticTokensFullDelta doc1 "0" diff --git a/plugins/hls-splice-plugin/test/Main.hs b/plugins/hls-splice-plugin/test/Main.hs index 037c80f1de..96f73ea4fb 100644 --- a/plugins/hls-splice-plugin/test/Main.hs +++ b/plugins/hls-splice-plugin/test/Main.hs @@ -1,5 +1,4 @@ {-# LANGUAGE DuplicateRecordFields #-} -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ViewPatterns #-} module Main @@ -8,7 +7,6 @@ module Main import Control.Monad (void) import Data.List (find) -import Data.Row import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.IO as T @@ -93,9 +91,10 @@ goldenTestWithEdit fp expect tc line col = waitForAllProgressDone alt <- liftIO $ T.readFile (fp <.> "error.hs") void $ applyEdit doc $ TextEdit theRange alt - changeDoc doc [TextDocumentContentChangeEvent $ InL $ #range .== theRange - .+ #rangeLength .== Nothing - .+ #text .== alt] + changeDoc doc [TextDocumentContentChangeEvent $ InL + TextDocumentContentChangePartial {_range = theRange, _rangeLength = Nothing, _text = alt} + ] + void waitForDiagnostics -- wait for the entire build to finish void waitForBuildQueue