@@ -5,6 +5,8 @@ module Main
55 ) where
66
77import Control.Lens ((<&>) , (^.) )
8+ import Data.Aeson
9+ import Data.Foldable
810import qualified Data.Text as T
911import Ide.Plugin.Pragmas
1012import qualified Language.LSP.Types.Lens as L
@@ -31,6 +33,7 @@ tests =
3133 , codeActionTests'
3234 , completionTests
3335 , completionSnippetTests
36+ , dontSuggestCompletionTests
3437 ]
3538
3639codeActionTests :: TestTree
@@ -139,29 +142,80 @@ completionSnippetTests :: TestTree
139142completionSnippetTests =
140143 testGroup " expand snippet to pragma" $
141144 validPragmas <&>
142- (\ (insertText, label, detail, _) ->
143- let input = T. toLower $ T. init label
145+ (\ (insertText, label, detail, appearWhere) ->
146+ let inputPrefix =
147+ case appearWhere of
148+ NewLine -> " "
149+ CanInline -> " something "
150+ input = inputPrefix <> (T. toLower $ T. init label)
144151 in completionTest (T. unpack label)
145152 " Completion.hs" input label (Just Snippet )
146153 (Just $ " {-# " <> insertText <> " #-}" ) (Just detail)
147154 [0 , 0 , 0 , 34 , 0 , fromIntegral $ T. length input])
148155
149- completionTest :: String -> String -> T. Text -> T. Text -> Maybe InsertTextFormat -> Maybe T. Text -> Maybe T. Text -> [UInt ] -> TestTree
150- completionTest testComment fileName te' label textFormat insertText detail [a, b, c, d, x, y] =
156+ dontSuggestCompletionTests :: TestTree
157+ dontSuggestCompletionTests =
158+ testGroup " do not suggest pragmas" $
159+ let replaceFuncBody newBody = Just $ mkEdit (8 ,6 ) (8 ,8 ) newBody
160+ writeInEmptyLine txt = Just $ mkEdit (3 ,0 ) (3 ,0 ) txt
161+ generalTests = [ provideNoCompletionsTest " in imports" " Completion.hs" (Just $ mkEdit (3 ,0 ) (3 ,0 ) " import WA" ) (Position 3 8 )
162+ , provideNoCompletionsTest " when no word has been typed" " Completion.hs" Nothing (Position 3 0 )
163+ , provideNoCompletionsTest " when expecting auto complete on modules" " Completion.hs" (Just $ mkEdit (8 ,6 ) (8 ,8 ) " Data.Maybe.WA" ) (Position 8 19 )
164+ ]
165+ individualPragmaTests = validPragmas <&> \ (insertText,label,detail,appearWhere) ->
166+ let completionPrompt = T. toLower $ T. init label
167+ promptLen = fromIntegral (T. length completionPrompt)
168+ in case appearWhere of
169+ CanInline ->
170+ provideNoUndesiredCompletionsTest (" at new line: " <> T. unpack label) " Completion.hs" (Just label) (writeInEmptyLine completionPrompt) (Position 3 0 )
171+ NewLine ->
172+ provideNoUndesiredCompletionsTest (" inline: " <> T. unpack label) " Completion.hs" (Just label) (replaceFuncBody completionPrompt) (Position 8 (6 + promptLen))
173+ in generalTests ++ individualPragmaTests
174+
175+ mkEdit :: (UInt ,UInt ) -> (UInt ,UInt ) -> T. Text -> TextEdit
176+ mkEdit (startLine, startCol) (endLine, endCol) newText =
177+ TextEdit (Range (Position startLine startCol) (Position endLine endCol)) newText
178+
179+ completionTest :: String -> FilePath -> T. Text -> T. Text -> Maybe InsertTextFormat -> Maybe T. Text -> Maybe T. Text -> [UInt ] -> TestTree
180+ completionTest testComment fileName replacementText expectedLabel expectedFormat expectedInsertText detail [delFromLine, delFromCol, delToLine, delToCol, completeAtLine, completeAtCol] =
151181 testCase testComment $ runSessionWithServer pragmasCompletionPlugin testDataDir $ do
152182 doc <- openDoc fileName " haskell"
153183 _ <- waitForDiagnostics
154- let te = TextEdit (Range (Position a b ) (Position c d )) te'
184+ let te = TextEdit (Range (Position delFromLine delFromCol ) (Position delToLine delToCol )) replacementText
155185 _ <- applyEdit doc te
156- compls <- getCompletions doc (Position x y )
157- item <- getCompletionByLabel label compls
186+ compls <- getCompletions doc (Position completeAtLine completeAtCol )
187+ item <- getCompletionByLabel expectedLabel compls
158188 liftIO $ do
159- item ^. L. label @?= label
189+ item ^. L. label @?= expectedLabel
160190 item ^. L. kind @?= Just CiKeyword
161- item ^. L. insertTextFormat @?= textFormat
162- item ^. L. insertText @?= insertText
191+ item ^. L. insertTextFormat @?= expectedFormat
192+ item ^. L. insertText @?= expectedInsertText
163193 item ^. L. detail @?= detail
164194
195+ provideNoCompletionsTest :: String -> FilePath -> Maybe TextEdit -> Position -> TestTree
196+ provideNoCompletionsTest testComment fileName mTextEdit pos =
197+ provideNoUndesiredCompletionsTest testComment fileName Nothing mTextEdit pos
198+
199+ provideNoUndesiredCompletionsTest :: String -> FilePath -> Maybe T. Text -> Maybe TextEdit -> Position -> TestTree
200+ provideNoUndesiredCompletionsTest testComment fileName mUndesiredLabel mTextEdit pos =
201+ testCase testComment $ runSessionWithServer pragmasCompletionPlugin testDataDir $ do
202+ doc <- openDoc fileName " haskell"
203+ _ <- waitForDiagnostics
204+ _ <- sendConfigurationChanged disableGhcideCompletions
205+ mapM_ (applyEdit doc) mTextEdit
206+ compls <- getCompletions doc pos
207+ liftIO $ case mUndesiredLabel of
208+ Nothing -> compls @?= []
209+ Just undesiredLabel -> do
210+ case find (\ c -> c ^. L. label == undesiredLabel) compls of
211+ Just c -> assertFailure $
212+ " Did not expect a completion with label=" <> T. unpack undesiredLabel
213+ <> " , got completion: " <> show c
214+ Nothing -> pure ()
215+
216+ disableGhcideCompletions :: Value
217+ disableGhcideCompletions = object [ " haskell" .= object [" plugin" .= object [ " ghcide-completions" .= object [" globalOn" .= False ]]] ]
218+
165219goldenWithPragmas :: PluginTestDescriptor () -> TestName -> FilePath -> (TextDocumentIdentifier -> Session () ) -> TestTree
166220goldenWithPragmas descriptor title path = goldenWithHaskellDoc descriptor title testDataDir path " expected" " hs"
167221
0 commit comments