1
- {-# LANGUAGE CPP #-}
2
1
{-# LANGUAGE DataKinds #-}
3
2
{-# LANGUAGE OverloadedStrings #-}
4
3
5
4
import Control.Lens ((^?) )
6
5
import Control.Monad.IO.Class (liftIO )
7
- import Data.Aeson (KeyValue (.. ), Value ( .. ),
8
- object )
6
+ import Data.Aeson (KeyValue (.. ), Object )
7
+ import qualified Data.Aeson.KeyMap as KV
9
8
import Data.Default
10
9
import Data.Functor (void )
11
10
import Data.Map.Strict as Map hiding (map )
@@ -14,6 +13,9 @@ import Data.Text hiding (length, map,
14
13
unlines )
15
14
import qualified Data.Text as Text
16
15
import qualified Data.Text.Utf16.Rope as Rope
16
+ import Development.IDE (Pretty )
17
+ import Development.IDE.GHC.Compat (GhcVersion (.. ),
18
+ ghcVersion )
17
19
import Development.IDE.Plugin.Test (WaitForIdeRuleResult (.. ))
18
20
import Development.IDE.Test (waitForBuildQueue )
19
21
import Ide.Plugin.SemanticTokens
@@ -22,13 +24,12 @@ import Ide.Plugin.SemanticTokens.Types
22
24
import Ide.Types
23
25
import Language.LSP.Protocol.Types (SemanticTokenTypes (.. ),
24
26
_L )
25
- import Language.LSP.Test (Session ( .. ) ,
27
+ import Language.LSP.Test (Session ,
26
28
SessionConfig (ignoreConfigurationRequests ),
27
29
openDoc )
28
30
import qualified Language.LSP.Test as Test
29
31
import Language.LSP.VFS (VirtualFile (.. ))
30
32
import System.FilePath
31
- import qualified Test.Hls as Test
32
33
import Test.Hls (PluginTestDescriptor ,
33
34
TestName , TestTree ,
34
35
TextDocumentIdentifier ,
@@ -65,6 +66,7 @@ semanticTokensPlugin = Test.Hls.mkPluginTestDescriptor enabledSemanticDescriptor
65
66
}
66
67
}
67
68
69
+ goldenWithHaskellAndCapsOutPut :: Pretty b => Config -> PluginTestDescriptor b -> TestName -> FS. VirtualFileTree -> FilePath -> String -> (TextDocumentIdentifier -> Session String ) -> TestTree
68
70
goldenWithHaskellAndCapsOutPut config plugin title tree path desc act =
69
71
goldenGitDiff title (FS. vftOriginalRoot tree </> path <.> desc) $
70
72
runSessionWithServerInTmpDir config plugin tree $
@@ -118,13 +120,11 @@ semanticTokensValuePatternTests =
118
120
goldenWithSemanticTokensWithDefaultConfig " pattern bind" " TPatternbind"
119
121
]
120
122
121
- mkSemanticConfig :: Value -> Config
123
+ mkSemanticConfig :: Object -> Config
122
124
mkSemanticConfig setting = def{plugins = Map. insert " SemanticTokens" conf (plugins def)}
123
125
where
124
- conf = def{plcConfig = ( \ ( Object obj) -> obj) setting }
126
+ conf = def{plcConfig = setting }
125
127
126
- modifySemantic :: Value -> Session ()
127
- modifySemantic setting = Test. setHlsConfig $ mkSemanticConfig setting
128
128
129
129
130
130
directFile :: FilePath -> Text -> [FS. FileTree ]
@@ -138,7 +138,7 @@ semanticTokensConfigTest = testGroup "semantic token config test" [
138
138
testCase " function to variable" $ do
139
139
let content = Text. unlines [" module Hello where" , " go _ = 1" ]
140
140
let fs = mkFs $ directFile " Hello.hs" content
141
- let funcVar = object [" functionToken" .= var]
141
+ let funcVar = KV. fromList [" functionToken" .= var]
142
142
var :: String
143
143
var = " variable"
144
144
do
@@ -158,8 +158,7 @@ semanticTokensConfigTest = testGroup "semantic token config test" [
158
158
159
159
semanticTokensTests :: TestTree
160
160
semanticTokensTests =
161
- testGroup
162
- " other semantic Token test"
161
+ testGroup " other semantic Token test" $
163
162
[ testCase " module import test" $ do
164
163
let file1 = " TModula𐐀bA.hs"
165
164
let file2 = " TModuleB.hs"
@@ -194,11 +193,9 @@ semanticTokensTests =
194
193
goldenWithSemanticTokensWithDefaultConfig " type family" " TTypefamily" ,
195
194
goldenWithSemanticTokensWithDefaultConfig " TUnicodeSyntax" " TUnicodeSyntax" ,
196
195
goldenWithSemanticTokensWithDefaultConfig " TQualifiedName" " TQualifiedName"
197
- -- it is not supported in ghc92
198
- #if MIN_VERSION_ghc(9,4,0)
199
- , goldenWithSemanticTokensWithDefaultConfig " TDoc" " TDoc"
200
- #endif
201
196
]
197
+ -- not supported in ghc92
198
+ ++ [goldenWithSemanticTokensWithDefaultConfig " TDoc" " TDoc" | ghcVersion > GHC92 ]
202
199
203
200
semanticTokensDataTypeTests :: TestTree
204
201
semanticTokensDataTypeTests =
0 commit comments