22{-# LANGUAGE DuplicateRecordFields #-}
33{-# LANGUAGE OverloadedStrings #-}
44
5+ {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
6+
57import Control.Monad.IO.Class (liftIO )
68import Data.Maybe (fromJust )
79import Language.LSP.Protocol.Types
8- ( CompletionItem (.. )
10+ ( ClientCapabilities
11+ , CompletionItem (.. )
912 , Diagnostic (.. )
1013 , DiagnosticSeverity (.. )
1114 , Hover (.. )
@@ -14,25 +17,38 @@ import Language.LSP.Protocol.Types
1417 , Range (.. )
1518 , toEither
1619 )
17- import Language.LSP.Test
1820import Test.Tasty
1921import Test.Tasty.Hspec
2022
23+ #if MIN_VERSION_lsp_types(2,3,0)
24+ import Language.LSP.Test hiding (fullLatestClientCaps )
25+ #else
26+ import Language.LSP.Test
27+ #endif
28+
2129#if MIN_VERSION_tasty_hspec(1,1,7)
2230import Test.Hspec
2331#endif
2432
2533import qualified Data.Text as T
2634import qualified GHC.IO.Encoding
35+ import qualified Language.LSP.Protocol.Capabilities
2736
2837baseDir :: FilePath -> FilePath
2938baseDir d = " tests/fixtures/" <> d
3039
40+ fullLatestClientCaps :: ClientCapabilities
41+ #if MIN_VERSION_lsp_types(2,3,0)
42+ fullLatestClientCaps = Language.LSP.Protocol.Capabilities. fullLatestClientCaps
43+ #else
44+ fullLatestClientCaps = Language.LSP.Protocol.Capabilities. fullCaps
45+ #endif
46+
3147hoveringSpec :: FilePath -> Spec
3248hoveringSpec dir =
3349 describe " Dhall.Hover"
3450 $ it " reports types on hover"
35- $ runSession " dhall-lsp-server" fullCaps dir
51+ $ runSession " dhall-lsp-server" fullLatestClientCaps dir
3652 $ do
3753 docId <- openDoc " Types.dhall" " dhall"
3854 let typePos = Position 0 5
@@ -53,7 +69,7 @@ lintingSpec :: FilePath -> Spec
5369lintingSpec fixtureDir =
5470 describe " Dhall.Lint" $ do
5571 it " reports unused bindings"
56- $ runSession " dhall-lsp-server" fullCaps fixtureDir
72+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
5773 $ do
5874 _ <- openDoc " UnusedBindings.dhall" " dhall"
5975
@@ -92,7 +108,7 @@ lintingSpec fixtureDir =
92108
93109 pure ()
94110 it " reports multiple hints"
95- $ runSession " dhall-lsp-server" fullCaps fixtureDir
111+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
96112 $ do
97113 _ <- openDoc " SuperfluousIn.dhall" " dhall"
98114 diags <- waitForDiagnosticsSource " Dhall.Lint"
@@ -109,7 +125,7 @@ codeCompletionSpec :: FilePath -> Spec
109125codeCompletionSpec fixtureDir =
110126 describe " Dhall.Completion" $ do
111127 it " suggests user defined types"
112- $ runSession " dhall-lsp-server" fullCaps fixtureDir
128+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
113129 $ do
114130 docId <- openDoc " CustomTypes.dhall" " dhall"
115131 cs <- getCompletions docId (Position {_line = 2 , _character = 35 })
@@ -118,7 +134,7 @@ codeCompletionSpec fixtureDir =
118134 _label firstItem `shouldBe` " Config"
119135 _detail firstItem `shouldBe` Just " Type"
120136 it " suggests user defined functions"
121- $ runSession " dhall-lsp-server" fullCaps fixtureDir
137+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
122138 $ do
123139 docId <- openDoc " CustomFunctions.dhall" " dhall"
124140 cs <- getCompletions docId (Position {_line = 6 , _character = 7 })
@@ -127,7 +143,7 @@ codeCompletionSpec fixtureDir =
127143 _label firstItem `shouldBe` " makeUser"
128144 _detail firstItem `shouldBe` Just " \8704(user : Text) \8594 { home : Text }"
129145 it " suggests user defined bindings"
130- $ runSession " dhall-lsp-server" fullCaps fixtureDir
146+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
131147 $ do
132148 docId <- openDoc " Bindings.dhall" " dhall"
133149 cs <- getCompletions docId (Position {_line = 0 , _character = 59 })
@@ -136,7 +152,7 @@ codeCompletionSpec fixtureDir =
136152 _label firstItem `shouldBe` " bob"
137153 _detail firstItem `shouldBe` Just " Text"
138154 it " suggests functions from imports"
139- $ runSession " dhall-lsp-server" fullCaps fixtureDir
155+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
140156 $ do
141157 docId <- openDoc " ImportedFunctions.dhall" " dhall"
142158 cs <- getCompletions docId (Position {_line = 0 , _character = 33 })
@@ -147,7 +163,7 @@ codeCompletionSpec fixtureDir =
147163 _detail firstItem `shouldBe` Just " \8704(user : Text) \8594 { home : Text }"
148164 _detail secondItem `shouldBe` Just " \8704(user : Text) \8594 { home : Text }"
149165 it " suggests union alternatives"
150- $ runSession " dhall-lsp-server" fullCaps fixtureDir
166+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
151167 $ do
152168 docId <- openDoc " Union.dhall" " dhall"
153169 cs <- getCompletions docId (Position {_line = 2 , _character = 10 })
@@ -162,15 +178,15 @@ diagnosticsSpec :: FilePath -> Spec
162178diagnosticsSpec fixtureDir = do
163179 describe " Dhall.TypeCheck" $ do
164180 it " reports unbound variables"
165- $ runSession " dhall-lsp-server" fullCaps fixtureDir
181+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
166182 $ do
167183 _ <- openDoc " UnboundVar.dhall" " dhall"
168184 [diag] <- waitForDiagnosticsSource " Dhall.TypeCheck"
169185 liftIO $ do
170186 _severity diag `shouldBe` Just DiagnosticSeverity_Error
171187 T. unpack (_message diag) `shouldContain` " Unbound variable"
172188 it " reports wrong type"
173- $ runSession " dhall-lsp-server" fullCaps fixtureDir
189+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
174190 $ do
175191 _ <- openDoc " WrongType.dhall" " dhall"
176192 [diag] <- waitForDiagnosticsSource " Dhall.TypeCheck"
@@ -179,15 +195,15 @@ diagnosticsSpec fixtureDir = do
179195 T. unpack (_message diag) `shouldContain` " Expression doesn't match annotation"
180196 describe " Dhall.Import" $ do
181197 it " reports invalid imports"
182- $ runSession " dhall-lsp-server" fullCaps fixtureDir
198+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
183199 $ do
184200 _ <- openDoc " InvalidImport.dhall" " dhall"
185201 [diag] <- waitForDiagnosticsSource " Dhall.Import"
186202 liftIO $ do
187203 _severity diag `shouldBe` Just DiagnosticSeverity_Error
188204 T. unpack (_message diag) `shouldContain` " Invalid input"
189205 it " reports missing imports"
190- $ runSession " dhall-lsp-server" fullCaps fixtureDir
206+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
191207 $ do
192208 _ <- openDoc " MissingImport.dhall" " dhall"
193209 [diag] <- waitForDiagnosticsSource " Dhall.Import"
@@ -196,7 +212,7 @@ diagnosticsSpec fixtureDir = do
196212 T. unpack (_message diag) `shouldContain` " Missing file"
197213 describe " Dhall.Parser"
198214 $ it " reports invalid syntax"
199- $ runSession " dhall-lsp-server" fullCaps fixtureDir
215+ $ runSession " dhall-lsp-server" fullLatestClientCaps fixtureDir
200216 $ do
201217 _ <- openDoc " InvalidSyntax.dhall" " dhall"
202218 [diag] <- waitForDiagnosticsSource " Dhall.Parser"
0 commit comments