Skip to content

Commit 4a3ea7a

Browse files
committed
move outline test to core plugin
1 parent 0f0f918 commit 4a3ea7a

File tree

2 files changed

+89
-147
lines changed

2 files changed

+89
-147
lines changed

plugins/hls-core-plugin/test/exe/OutlineTests.hs

Lines changed: 71 additions & 145 deletions
Original file line numberDiff line numberDiff line change
@@ -30,155 +30,81 @@ import Util
3030
pattern R :: UInt -> UInt -> UInt -> UInt -> Range
3131
pattern R x y x' y' = Range (Position x y) (Position x' y')
3232

33+
testSymbols :: (HasCallStack) => TestName -> FilePath -> [Text] -> [DocumentSymbol] -> TestTree
34+
testSymbols testName path content expectedSymbols =
35+
testSessionWithCorePluginSingleFile testName path (T.unlines content) $ do
36+
docId <- openDoc path "haskell"
37+
symbols <- getDocumentSymbols docId
38+
liftIO $ symbols @?= Right expectedSymbols
39+
40+
testSymbolsA :: (HasCallStack) => TestName -> [Text] -> [DocumentSymbol] -> TestTree
41+
testSymbolsA testName content expectedSymbols =
42+
testSymbols testName "A.hs" content expectedSymbols
43+
3344
tests :: TestTree
3445
tests = testGroup
3546
"outline"
3647
[
37-
-- runSessionWithServerInTmpDir def "type class" $ do
38-
-- let source = T.unlines ["module A where", "class A a where a :: a -> Bool"]
39-
-- docId <- createDoc "A.hs" "haskell" source
40-
-- symbols <- getDocumentSymbols docId
41-
-- liftIO $ symbols @?= Right
42-
-- [ moduleSymbol
43-
-- "A"
44-
-- (R 0 7 0 8)
45-
-- [ classSymbol "A a"
46-
-- (R 1 0 1 30)
47-
-- [docSymbol' "a" SymbolKind_Method (R 1 16 1 30) (R 1 16 1 17)]
48-
-- ]
49-
-- ]
50-
-- , testSessionWait "type class instance " $ do
51-
-- let source = T.unlines ["class A a where", "instance A () where"]
52-
-- docId <- createDoc "A.hs" "haskell" source
53-
-- symbols <- getDocumentSymbols docId
54-
-- liftIO $ symbols @?= Right
55-
-- [ classSymbol "A a" (R 0 0 0 15) []
56-
-- , docSymbol "A ()" SymbolKind_Interface (R 1 0 1 19)
57-
-- ]
58-
-- , testSessionWait "type family" $ do
59-
-- let source = T.unlines ["{-# language TypeFamilies #-}", "type family A"]
60-
-- docId <- createDoc "A.hs" "haskell" source
61-
-- symbols <- getDocumentSymbols docId
62-
-- liftIO $ symbols @?= Right [docSymbolD "A" "type family" SymbolKind_Function (R 1 0 1 13)]
63-
-- , testSessionWait "type family instance " $ do
64-
-- let source = T.unlines
65-
-- [ "{-# language TypeFamilies #-}"
66-
-- , "type family A a"
67-
-- , "type instance A () = ()"
68-
-- ]
69-
-- docId <- createDoc "A.hs" "haskell" source
70-
-- symbols <- getDocumentSymbols docId
71-
-- liftIO $ symbols @?= Right
72-
-- [ docSymbolD "A a" "type family" SymbolKind_Function (R 1 0 1 15)
73-
-- , docSymbol "A ()" SymbolKind_Interface (R 2 0 2 23)
74-
-- ]
75-
-- , testSessionWait "data family" $ do
76-
-- let source = T.unlines ["{-# language TypeFamilies #-}", "data family A"]
77-
-- docId <- createDoc "A.hs" "haskell" source
78-
-- symbols <- getDocumentSymbols docId
79-
-- liftIO $ symbols @?= Right [docSymbolD "A" "data family" SymbolKind_Function (R 1 0 1 11)]
80-
-- , testSessionWait "data family instance " $ do
81-
-- let source = T.unlines
82-
-- [ "{-# language TypeFamilies #-}"
83-
-- , "data family A a"
84-
-- , "data instance A () = A ()"
85-
-- ]
86-
-- docId <- createDoc "A.hs" "haskell" source
87-
-- symbols <- getDocumentSymbols docId
88-
-- liftIO $ symbols @?= Right
89-
-- [ docSymbolD "A a" "data family" SymbolKind_Function (R 1 0 1 11)
90-
-- , docSymbol "A ()" SymbolKind_Interface (R 2 0 2 25)
91-
-- ]
92-
-- , testSessionWait "constant" $ do
93-
-- let source = T.unlines ["a = ()"]
94-
-- docId <- createDoc "A.hs" "haskell" source
95-
-- symbols <- getDocumentSymbols docId
96-
-- liftIO $ symbols @?= Right
97-
-- [docSymbol "a" SymbolKind_Function (R 0 0 0 6)]
98-
-- , testSessionWait "pattern" $ do
99-
-- let source = T.unlines ["Just foo = Just 21"]
100-
-- docId <- createDoc "A.hs" "haskell" source
101-
-- symbols <- getDocumentSymbols docId
102-
-- liftIO $ symbols @?= Right
103-
-- [docSymbol "Just foo" SymbolKind_Function (R 0 0 0 18)]
104-
-- , testSessionWait "pattern with type signature" $ do
105-
-- let source = T.unlines ["{-# language ScopedTypeVariables #-}", "a :: () = ()"]
106-
-- docId <- createDoc "A.hs" "haskell" source
107-
-- symbols <- getDocumentSymbols docId
108-
-- liftIO $ symbols @?= Right
109-
-- [docSymbol "a :: ()" SymbolKind_Function (R 1 0 1 12)]
110-
-- , testSessionWait "function" $ do
111-
-- let source = T.unlines ["a _x = ()"]
112-
-- docId <- createDoc "A.hs" "haskell" source
113-
-- symbols <- getDocumentSymbols docId
114-
-- liftIO $ symbols @?= Right [docSymbol "a" SymbolKind_Function (R 0 0 0 9)]
115-
-- , testSessionWait "type synonym" $ do
116-
-- let source = T.unlines ["type A = Bool"]
117-
-- docId <- createDoc "A.hs" "haskell" source
118-
-- symbols <- getDocumentSymbols docId
119-
-- liftIO $ symbols @?= Right
120-
-- [docSymbol' "A" SymbolKind_TypeParameter (R 0 0 0 13) (R 0 5 0 6)]
121-
-- , testSessionWait "datatype" $ do
122-
-- let source = T.unlines ["data A = C"]
123-
-- docId <- createDoc "A.hs" "haskell" source
124-
-- symbols <- getDocumentSymbols docId
125-
-- liftIO $ symbols @?= Right
126-
-- [ docSymbolWithChildren "A"
127-
-- SymbolKind_Struct
128-
-- (R 0 0 0 10)
129-
-- [docSymbol "C" SymbolKind_Constructor (R 0 9 0 10)]
130-
-- ]
131-
-- , testSessionWait "record fields" $ do
132-
-- let source = T.unlines ["data A = B {", " x :: Int", " , y :: Int}"]
133-
-- docId <- createDoc "A.hs" "haskell" source
134-
-- symbols <- getDocumentSymbols docId
135-
-- liftIO $ symbols @?= Right
136-
-- [ docSymbolWithChildren "A" SymbolKind_Struct (R 0 0 2 13)
137-
-- [ docSymbolWithChildren' "B" SymbolKind_Constructor (R 0 9 2 13) (R 0 9 0 10)
138-
-- [ docSymbol "x" SymbolKind_Field (R 1 2 1 3)
139-
-- , docSymbol "y" SymbolKind_Field (R 2 4 2 5)
140-
-- ]
141-
-- ]
142-
-- ]
143-
-- , testSessionWait "import" $ do
144-
-- let source = T.unlines ["import Data.Maybe ()"]
145-
-- docId <- createDoc "A.hs" "haskell" source
146-
-- symbols <- getDocumentSymbols docId
147-
-- liftIO $ symbols @?= Right
148-
-- [docSymbolWithChildren "imports"
149-
-- SymbolKind_Module
150-
-- (R 0 0 0 20)
151-
-- [ docSymbol "import Data.Maybe" SymbolKind_Module (R 0 0 0 20)
152-
-- ]
153-
-- ]
154-
-- , testSessionWait "multiple import" $ do
155-
-- let source = T.unlines ["", "import Data.Maybe ()", "", "import Control.Exception ()", ""]
156-
-- docId <- createDoc "A.hs" "haskell" source
157-
-- symbols <- getDocumentSymbols docId
158-
-- liftIO $ symbols @?= Right
159-
-- [docSymbolWithChildren "imports"
160-
-- SymbolKind_Module
161-
-- (R 1 0 3 27)
162-
-- [ docSymbol "import Data.Maybe" SymbolKind_Module (R 1 0 1 20)
163-
-- , docSymbol "import Control.Exception" SymbolKind_Module (R 3 0 3 27)
164-
-- ]
165-
-- ]
166-
-- , testSessionWait "foreign import" $ do
167-
-- let source = T.unlines
168-
-- [ "{-# language ForeignFunctionInterface #-}"
169-
-- , "foreign import ccall \"a\" a :: Int"
170-
-- ]
171-
-- docId <- createDoc "A.hs" "haskell" source
172-
-- symbols <- getDocumentSymbols docId
173-
-- liftIO $ symbols @?= Right [docSymbolD "a" "import" SymbolKind_Object (R 1 0 1 33)]
174-
-- , testSessionWait "foreign export" $ do
175-
-- let source = T.unlines
176-
-- [ "{-# language ForeignFunctionInterface #-}"
177-
-- , "foreign export ccall odd :: Int -> Bool"
178-
-- ]
179-
-- docId <- createDoc "A.hs" "haskell" source
180-
-- symbols <- getDocumentSymbols docId
181-
-- liftIO $ symbols @?= Right [docSymbolD "odd" "export" SymbolKind_Object (R 1 0 1 39)]
48+
testSymbolsA "module" ["module A where", "class A a where a :: a -> Bool"]
49+
[ moduleSymbol
50+
"A"
51+
(R 0 7 0 8)
52+
[ classSymbol "A a"
53+
(R 1 0 1 30)
54+
[docSymbol' "a" SymbolKind_Method (R 1 16 1 30) (R 1 16 1 17)]
55+
] ]
56+
, testSymbolsA "type class instance " ["class A a where", "instance A () where"]
57+
[ classSymbol "A a" (R 0 0 0 15) []
58+
, docSymbol "A ()" SymbolKind_Interface (R 1 0 1 19)
59+
]
60+
, testSymbolsA "type family" ["{-# language TypeFamilies #-}", "type family A"] [docSymbolD "A" "type family" SymbolKind_Function (R 1 0 1 13)]
61+
, testSymbolsA "type family instance " [ "{-# language TypeFamilies #-}" , "type family A a" , "type instance A () = ()"]
62+
[ docSymbolD "A a" "type family" SymbolKind_Function (R 1 0 1 15)
63+
, docSymbol "A ()" SymbolKind_Interface (R 2 0 2 23)
64+
]
65+
, testSymbolsA "data family" ["{-# language TypeFamilies #-}", "data family A"] [docSymbolD "A" "data family" SymbolKind_Function (R 1 0 1 11)]
66+
, testSymbolsA "data family instance " [ "{-# language TypeFamilies #-}" , "data family A a" , "data instance A () = A ()" ]
67+
[ docSymbolD "A a" "data family" SymbolKind_Function (R 1 0 1 11)
68+
, docSymbol "A ()" SymbolKind_Interface (R 2 0 2 25)
69+
]
70+
, testSymbolsA "constant" ["a = ()"] [docSymbol "a" SymbolKind_Function (R 0 0 0 6)]
71+
, testSymbolsA "pattern" ["Just foo = Just 21"] [docSymbol "Just foo" SymbolKind_Function (R 0 0 0 18)]
72+
, testSymbolsA "pattern with type signature" ["{-# language ScopedTypeVariables #-}", "a :: () = ()"] [docSymbol "a :: ()" SymbolKind_Function (R 1 0 1 12)]
73+
, testSymbolsA "function" ["a _x = ()"] [docSymbol "a" SymbolKind_Function (R 0 0 0 9)]
74+
, testSymbolsA "type synonym" ["type A = Bool"] [docSymbol' "A" SymbolKind_TypeParameter (R 0 0 0 13) (R 0 5 0 6)]
75+
, testSymbolsA "datatype" ["data A = C"] [ docSymbolWithChildren "A" SymbolKind_Struct (R 0 0 0 10) [docSymbol "C" SymbolKind_Constructor (R 0 9 0 10)] ]
76+
, testSymbolsA "record fields" ["data A = B {", " x :: Int", " , y :: Int}"]
77+
[ docSymbolWithChildren "A" SymbolKind_Struct (R 0 0 2 13)
78+
[ docSymbolWithChildren' "B" SymbolKind_Constructor (R 0 9 2 13) (R 0 9 0 10)
79+
[ docSymbol "x" SymbolKind_Field (R 1 2 1 3)
80+
, docSymbol "y" SymbolKind_Field (R 2 4 2 5)
81+
]
82+
]
83+
]
84+
, testSymbolsA "import" ["import Data.Maybe ()"]
85+
[docSymbolWithChildren "imports"
86+
SymbolKind_Module
87+
(R 0 0 0 20)
88+
[ docSymbol "import Data.Maybe" SymbolKind_Module (R 0 0 0 20)
89+
]
90+
]
91+
, testSymbolsA "multiple import" ["", "import Data.Maybe ()", "", "import Control.Exception ()", ""]
92+
[docSymbolWithChildren "imports"
93+
SymbolKind_Module
94+
(R 1 0 3 27)
95+
[ docSymbol "import Data.Maybe" SymbolKind_Module (R 1 0 1 20)
96+
, docSymbol "import Control.Exception" SymbolKind_Module (R 3 0 3 27)
97+
]
98+
]
99+
, testSymbolsA "foreign import"
100+
[ "{-# language ForeignFunctionInterface #-}"
101+
, "foreign import ccall \"a\" a :: Int"
102+
] [docSymbolD "a" "import" SymbolKind_Object (R 1 0 1 33)]
103+
, testSymbolsA "foreign export"
104+
[ "{-# language ForeignFunctionInterface #-}"
105+
, "foreign export ccall odd :: Int -> Bool"
106+
]
107+
[docSymbolD "odd" "export" SymbolKind_Object (R 1 0 1 39)]
182108
]
183109
where
184110
docSymbol name kind loc =

plugins/hls-core-plugin/test/exe/Util.hs

Lines changed: 18 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,18 +2,34 @@
22

33
module Util where
44

5+
import Data.Default (Default (..))
56
import Data.Text (Text)
67
import qualified Data.Text as Text
78
import qualified Ide.Plugin.Core as Core
9+
import Language.LSP.Test (Session)
810
import System.FilePath ((</>))
9-
import Test.Hls (PluginTestDescriptor,
10-
mkPluginTestDescriptor)
11+
import Test.Hls (Assertion, PluginTestDescriptor, TestName,
12+
TestTree, mkPluginTestDescriptor,
13+
runSessionWithServerInTmpDir, testCase)
1114
import qualified Test.Hls.FileSystem as FS
1215
import Test.Hls.FileSystem (file, text)
1316

17+
18+
runSessionWithCorePlugin :: FS.VirtualFileTree -> Session a -> IO a
19+
runSessionWithCorePlugin = runSessionWithServerInTmpDir def corePlugin
20+
21+
runSessionWithCorePluginSingleFile :: FilePath -> Text -> Session a -> IO a
22+
runSessionWithCorePluginSingleFile fp content = runSessionWithCorePlugin (mkSingleFileFs fp content)
23+
24+
testSessionWithCorePluginSingleFile :: TestName -> FilePath -> Text -> Session () -> TestTree
25+
testSessionWithCorePluginSingleFile caseName fp content = testCase caseName . runSessionWithCorePluginSingleFile fp content
26+
1427
corePlugin :: PluginTestDescriptor Core.CoreLog
1528
corePlugin = mkPluginTestDescriptor Core.descriptor "core"
1629

30+
mkSingleFileFs :: FilePath -> Text -> FS.VirtualFileTree
31+
mkSingleFileFs fp = mkFs . directFile fp
32+
1733
directFile :: FilePath -> Text -> [FS.FileTree]
1834
directFile fp content =
1935
[ FS.directCradle [Text.pack fp]

0 commit comments

Comments
 (0)