@@ -33,7 +33,6 @@ import Test.Hls.Util
3333import Test.Tasty
3434import Test.Tasty.HUnit
3535
36-
3736tests :: TestTree
3837tests
3938 = testGroup " completion"
@@ -61,6 +60,7 @@ completionTest :: HasCallStack => String -> [T.Text] -> Position -> [(T.Text, Co
6160completionTest name src pos expected = testSessionSingleFile name " A.hs" (T. unlines src) $ do
6261 docId <- openDoc " A.hs" " haskell"
6362 _ <- waitForDiagnostics
63+
6464 compls <- getAndResolveCompletions docId pos
6565 let compls' = [ (_label, _kind, _insertText, _additionalTextEdits) | CompletionItem {.. } <- compls]
6666 let emptyToMaybe x = if T. null x then Nothing else Just x
@@ -211,7 +211,38 @@ localCompletionTests = [
211211
212212 compls <- getCompletions doc (Position 0 15 )
213213 liftIO $ filter (" AAA" `T.isPrefixOf` ) (mapMaybe _insertText compls) @?= [" AAAAA" ]
214- pure ()
214+ pure () ,
215+ completionTest
216+ " polymorphic record dot completion"
217+ [ " {-# LANGUAGE OverloadedRecordDot #-}"
218+ , " module A () where"
219+ , " data Record = Record"
220+ , " { field1 :: Int"
221+ , " , field2 :: Int"
222+ , " }"
223+ , -- Without the following, this file doesn't trigger any diagnostics, so completionTest waits forever
224+ " triggerDiag :: UnknownType"
225+ , " foo record = record.f"
226+ ]
227+ (Position 7 21 )
228+ [(" field1" , CompletionItemKind_Function , " field1" , True , False , Nothing )
229+ ,(" field2" , CompletionItemKind_Function , " field2" , True , False , Nothing )
230+ ],
231+ completionTest
232+ " qualified polymorphic record dot completion"
233+ [ " {-# LANGUAGE OverloadedRecordDot #-}"
234+ , " module A () where"
235+ , " data Record = Record"
236+ , " { field1 :: Int"
237+ , " , field2 :: Int"
238+ , " }"
239+ , " someValue = undefined"
240+ , " foo = A.someValue.f"
241+ ]
242+ (Position 7 19 )
243+ [(" field1" , CompletionItemKind_Function , " field1" , True , False , Nothing )
244+ ,(" field2" , CompletionItemKind_Function , " field2" , True , False , Nothing )
245+ ]
215246 ]
216247
217248nonLocalCompletionTests :: [TestTree ]
0 commit comments