1
1
{-# LANGUAGE PatternSynonyms #-}
2
2
3
- module Config where
4
-
3
+ module Config (
4
+ -- * basic config for ghcIde testing
5
+ mkIdeTestFs
6
+ , dummyPlugin
7
+
8
+ -- * runners for testing with dummy plugin
9
+ , runWithDummyPlugin
10
+ , testWithDummyPlugin
11
+ , testWithDummyPluginEmpty
12
+ , testWithDummyPlugin'
13
+ , testWithDummyPluginEmpty'
14
+ , testWithDummyPluginAndCap'
15
+ , runWithExtraFiles
16
+ , testWithExtraFiles
17
+
18
+ -- * utilities for testing definition and hover
19
+ , Expect (.. )
20
+ , pattern R
21
+ , mkR
22
+ , checkDefs
23
+ , mkL
24
+ , lspTestCaps
25
+ , lspTestCapsNoFileWatches
26
+ ) where
27
+
28
+ import Control.Lens.Setter ((.~) )
5
29
import Data.Foldable (traverse_ )
30
+ import Data.Function ((&) )
6
31
import qualified Data.Text as T
7
32
import Development.IDE.Test (canonicalizeUri )
8
33
import Ide.Types (defaultPluginDescriptor )
34
+ import qualified Language.LSP.Protocol.Lens as L
9
35
import Language.LSP.Protocol.Types (Null (.. ))
10
36
import System.FilePath ((</>) )
11
37
import Test.Hls
@@ -28,22 +54,18 @@ runWithDummyPlugin = runSessionWithServerInTmpDir def dummyPlugin
28
54
runWithDummyPlugin' :: FS. VirtualFileTree -> (FileSystem -> Session a ) -> IO a
29
55
runWithDummyPlugin' = runSessionWithServerInTmpDirCont' def dummyPlugin
30
56
31
- runWithDummyPluginAndCap :: ClientCapabilities -> Session () -> IO ()
32
- runWithDummyPluginAndCap cap = runSessionWithServerAndCapsInTmpDir def dummyPlugin cap (mkIdeTestFs [] )
57
+ runWithDummyPluginAndCap' :: ClientCapabilities -> ( FileSystem -> Session () ) -> IO ()
58
+ runWithDummyPluginAndCap' cap = runSessionWithServerAndCapsInTmpDirCont def dummyPlugin cap (mkIdeTestFs [] )
33
59
34
- testWithDummyPluginAndCap :: String -> ClientCapabilities -> Session () -> TestTree
35
- testWithDummyPluginAndCap caseName cap = testCase caseName . runWithDummyPluginAndCap cap
60
+ testWithDummyPluginAndCap' :: String -> ClientCapabilities -> ( FileSystem -> Session () ) -> TestTree
61
+ testWithDummyPluginAndCap' caseName cap = testCase caseName . runWithDummyPluginAndCap' cap
36
62
37
- -- testSessionWithCorePlugin ::(TestRunner cont ()) => TestName -> FS.VirtualFileTree -> cont -> TestTree
38
63
testWithDummyPlugin :: String -> FS. VirtualFileTree -> Session () -> TestTree
39
- testWithDummyPlugin caseName vfs = testCase caseName . runWithDummyPlugin vfs
64
+ testWithDummyPlugin caseName vfs = testWithDummyPlugin' caseName vfs . const
40
65
41
66
testWithDummyPlugin' :: String -> FS. VirtualFileTree -> (FileSystem -> Session () ) -> TestTree
42
67
testWithDummyPlugin' caseName vfs = testCase caseName . runWithDummyPlugin' vfs
43
68
44
- runWithDummyPluginEmpty :: Session a -> IO a
45
- runWithDummyPluginEmpty = runWithDummyPlugin $ mkIdeTestFs []
46
-
47
69
testWithDummyPluginEmpty :: String -> Session () -> TestTree
48
70
testWithDummyPluginEmpty caseName = testWithDummyPlugin caseName $ mkIdeTestFs []
49
71
@@ -114,3 +136,9 @@ defToLocation (InL (Definition (InL l))) = [l]
114
136
defToLocation (InL (Definition (InR ls))) = ls
115
137
defToLocation (InR (InL defLink)) = (\ (DefinitionLink LocationLink {_targetUri,_targetRange}) -> Location _targetUri _targetRange) <$> defLink
116
138
defToLocation (InR (InR Null )) = []
139
+
140
+ lspTestCaps :: ClientCapabilities
141
+ lspTestCaps = fullCaps { _window = Just $ WindowClientCapabilities (Just True ) Nothing Nothing }
142
+
143
+ lspTestCapsNoFileWatches :: ClientCapabilities
144
+ lspTestCapsNoFileWatches = lspTestCaps & L. workspace . traverse . L. didChangeWatchedFiles .~ Nothing
0 commit comments