1
1
{-# LANGUAGE OverloadedStrings #-}
2
- {-# OPTIONS_GHC -Wno-incomplete-patterns #-}
2
+
3
3
module Main
4
4
( main
5
5
) where
@@ -12,7 +12,6 @@ import Ide.Plugin.Pragmas
12
12
import qualified Language.LSP.Protocol.Lens as L
13
13
import System.FilePath
14
14
import Test.Hls
15
- import Test.Hls.Util (onlyWorkForGhcVersions )
16
15
17
16
main :: IO ()
18
17
main = defaultTestRunner tests
@@ -80,9 +79,6 @@ codeActionTests =
80
79
, codeActionTestWithDisableWarning " before doc comments" " UnusedImports" [(" Disable \" unused-imports\" warnings" , " Contains unused-imports code action" )]
81
80
]
82
81
83
- ghc94regression :: String
84
- ghc94regression = " to be reported"
85
-
86
82
codeActionTestWithPragmasSuggest :: String -> FilePath -> [(T. Text , String )] -> TestTree
87
83
codeActionTestWithPragmasSuggest = codeActionTestWith pragmasSuggestPlugin
88
84
@@ -105,8 +101,7 @@ codeActionTestWith descriptor testComment fp actions =
105
101
codeActionTests' :: TestTree
106
102
codeActionTests' =
107
103
testGroup " additional code actions"
108
- [
109
- goldenWithPragmas pragmasSuggestPlugin " no duplication" " NamedFieldPuns" $ \ doc -> do
104
+ [ goldenWithPragmas pragmasSuggestPlugin " no duplication" " NamedFieldPuns" $ \ doc -> do
110
105
_ <- waitForDiagnosticsFrom doc
111
106
cas <- map fromAction <$> getCodeActions doc (Range (Position 8 9 ) (Position 8 9 ))
112
107
ca <- liftIO $ case cas of
@@ -124,18 +119,17 @@ codeActionTests' =
124
119
completionTests :: TestTree
125
120
completionTests =
126
121
testGroup " completions"
127
- [ completionTest " completes pragmas" " Completion.hs" " " " LANGUAGE" (Just InsertTextFormat_Snippet ) (Just " LANGUAGE ${1:extension} #-}" ) (Just " {-# LANGUAGE #-}" ) [0 , 4 , 0 , 34 , 0 , 4 ]
128
- , completionTest " completes pragmas with existing closing pragma bracket" " Completion.hs" " " " LANGUAGE" (Just InsertTextFormat_Snippet ) (Just " LANGUAGE ${1:extension}" ) (Just " {-# LANGUAGE #-}" ) [0 , 4 , 0 , 31 , 0 , 4 ]
129
- , completionTest " completes pragmas with existing closing comment bracket" " Completion.hs" " " " LANGUAGE" (Just InsertTextFormat_Snippet ) (Just " LANGUAGE ${1:extension} #" ) (Just " {-# LANGUAGE #-}" ) [0 , 4 , 0 , 32 , 0 , 4 ]
130
- , completionTest " completes pragmas with existing closing bracket" " Completion.hs" " " " LANGUAGE" (Just InsertTextFormat_Snippet ) (Just " LANGUAGE ${1:extension} #-" ) (Just " {-# LANGUAGE #-}" ) [0 , 4 , 0 , 33 , 0 , 4 ]
131
- , completionTest " completes options pragma" " Completion.hs" " OPTIONS" " OPTIONS_GHC" (Just InsertTextFormat_Snippet ) (Just " OPTIONS_GHC -${1:option} #-}" ) (Just " {-# OPTIONS_GHC #-}" ) [0 , 4 , 0 , 34 , 0 , 4 ]
132
- , completionTest " completes ghc options pragma values" " Completion.hs" " {-# OPTIONS_GHC -Wno-red #-}\n " " Wno-redundant-constraints" Nothing Nothing Nothing [0 , 0 , 0 , 0 , 0 , 24 ]
133
- , completionTest " completes language extensions" " Completion.hs" " " " OverloadedStrings" Nothing Nothing Nothing [0 , 24 , 0 , 31 , 0 , 24 ]
134
- , completionTest " completes language extensions case insensitive" " Completion.hs" " lAnGuaGe Overloaded" " OverloadedStrings" Nothing Nothing Nothing [0 , 4 , 0 , 34 , 0 , 24 ]
135
- , completionTest " completes the Strict language extension" " Completion.hs" " Str" " Strict" Nothing Nothing Nothing [0 , 13 , 0 , 31 , 0 , 16 ]
136
- , completionTest " completes No- language extensions" " Completion.hs" " NoOverload" " NoOverloadedStrings" Nothing Nothing Nothing [0 , 13 , 0 , 31 , 0 , 23 ]
137
- , onlyWorkForGhcVersions (>= GHC92 ) " GHC2021 flag introduced since ghc9.2" $
138
- completionTest " completes GHC2021 extensions" " Completion.hs" " ghc" " GHC2021" Nothing Nothing Nothing [0 , 13 , 0 , 31 , 0 , 16 ]
122
+ [ completionTest " completes pragmas" " Completion.hs" " " " LANGUAGE" (Just InsertTextFormat_Snippet ) (Just " LANGUAGE ${1:extension} #-}" ) (Just " {-# LANGUAGE #-}" ) (0 , 4 , 0 , 34 , 0 , 4 )
123
+ , completionTest " completes pragmas with existing closing pragma bracket" " Completion.hs" " " " LANGUAGE" (Just InsertTextFormat_Snippet ) (Just " LANGUAGE ${1:extension}" ) (Just " {-# LANGUAGE #-}" ) (0 , 4 , 0 , 31 , 0 , 4 )
124
+ , completionTest " completes pragmas with existing closing comment bracket" " Completion.hs" " " " LANGUAGE" (Just InsertTextFormat_Snippet ) (Just " LANGUAGE ${1:extension} #" ) (Just " {-# LANGUAGE #-}" ) (0 , 4 , 0 , 32 , 0 , 4 )
125
+ , completionTest " completes pragmas with existing closing bracket" " Completion.hs" " " " LANGUAGE" (Just InsertTextFormat_Snippet ) (Just " LANGUAGE ${1:extension} #-" ) (Just " {-# LANGUAGE #-}" ) (0 , 4 , 0 , 33 , 0 , 4 )
126
+ , completionTest " completes options pragma" " Completion.hs" " OPTIONS" " OPTIONS_GHC" (Just InsertTextFormat_Snippet ) (Just " OPTIONS_GHC -${1:option} #-}" ) (Just " {-# OPTIONS_GHC #-}" ) (0 , 4 , 0 , 34 , 0 , 4 )
127
+ , completionTest " completes ghc options pragma values" " Completion.hs" " {-# OPTIONS_GHC -Wno-red #-}\n " " Wno-redundant-constraints" Nothing Nothing Nothing (0 , 0 , 0 , 0 , 0 , 24 )
128
+ , completionTest " completes language extensions" " Completion.hs" " " " OverloadedStrings" Nothing Nothing Nothing (0 , 24 , 0 , 31 , 0 , 24 )
129
+ , completionTest " completes language extensions case insensitive" " Completion.hs" " lAnGuaGe Overloaded" " OverloadedStrings" Nothing Nothing Nothing (0 , 4 , 0 , 34 , 0 , 24 )
130
+ , completionTest " completes the Strict language extension" " Completion.hs" " Str" " Strict" Nothing Nothing Nothing (0 , 13 , 0 , 31 , 0 , 16 )
131
+ , completionTest " completes No- language extensions" " Completion.hs" " NoOverload" " NoOverloadedStrings" Nothing Nothing Nothing (0 , 13 , 0 , 31 , 0 , 23 )
132
+ , completionTest " completes GHC2021 extensions" " Completion.hs" " ghc" " GHC2021" Nothing Nothing Nothing (0 , 13 , 0 , 31 , 0 , 16 )
139
133
]
140
134
141
135
completionSnippetTests :: TestTree
@@ -151,7 +145,7 @@ completionSnippetTests =
151
145
in completionTest (T. unpack label)
152
146
" Completion.hs" input label (Just InsertTextFormat_Snippet )
153
147
(Just $ " {-# " <> insertText <> " #-}" ) (Just detail)
154
- [ 0 , 0 , 0 , 34 , 0 , fromIntegral $ T. length input] )
148
+ ( 0 , 0 , 0 , 34 , 0 , fromIntegral $ T. length input) )
155
149
156
150
dontSuggestCompletionTests :: TestTree
157
151
dontSuggestCompletionTests =
@@ -162,7 +156,7 @@ dontSuggestCompletionTests =
162
156
, provideNoCompletionsTest " when no word has been typed" " Completion.hs" Nothing (Position 3 0 )
163
157
, provideNoCompletionsTest " when expecting auto complete on modules" " Completion.hs" (Just $ mkEdit (8 ,6 ) (8 ,8 ) " Data.Maybe.WA" ) (Position 8 19 )
164
158
]
165
- individualPragmaTests = validPragmas <&> \ (insertText ,label,detail ,appearWhere) ->
159
+ individualPragmaTests = validPragmas <&> \ (_insertText ,label,_detail ,appearWhere) ->
166
160
let completionPrompt = T. toLower $ T. init label
167
161
promptLen = fromIntegral (T. length completionPrompt)
168
162
in case appearWhere of
@@ -176,8 +170,8 @@ mkEdit :: (UInt,UInt) -> (UInt,UInt) -> T.Text -> TextEdit
176
170
mkEdit (startLine, startCol) (endLine, endCol) newText =
177
171
TextEdit (Range (Position startLine startCol) (Position endLine endCol)) newText
178
172
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] =
173
+ completionTest :: String -> FilePath -> T. Text -> T. Text -> Maybe InsertTextFormat -> Maybe T. Text -> Maybe T. Text -> ( UInt , UInt , UInt , UInt , UInt , UInt ) -> TestTree
174
+ completionTest testComment fileName replacementText expectedLabel expectedFormat expectedInsertText detail ( delFromLine, delFromCol, delToLine, delToCol, completeAtLine, completeAtCol) =
181
175
testCase testComment $ runSessionWithServer def pragmasCompletionPlugin testDataDir $ do
182
176
doc <- openDoc fileName " haskell"
183
177
_ <- waitForDiagnostics
0 commit comments