Skip to content

Commit 50923e5

Browse files
authored
Remove more workarounds for GHCs < 9.0 (#4092)
* Remove more workarounds for GHCs < 9.0 * String, not [String] * Remove GHC810 and GHC90 enum constants * Fix logic mistake in windows tests * Inline thDollarIdx * Troubleshoot wrapper-test * Troubleshoot * Try free disk space action * Run free-space in individual test jobs * Only run the disk cleanup on ubuntu * Revert troubleshooting code * Revert free-disk-space workaround * Reintroduce workaround * Revert "Reintroduce workaround" This reverts commit ec6e8da. * Don't install stack in tests? * Revert "Don't install stack in tests?" This reverts commit f53e993. * Make the test use ghcup-managed stack * More maintainable version of stack test
1 parent b57c093 commit 50923e5

File tree

21 files changed

+117
-202
lines changed

21 files changed

+117
-202
lines changed

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 59 additions & 98 deletions
Large diffs are not rendered by default.

ghcide/src/Development/IDE/GHC/Compat.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -504,9 +504,7 @@ generatedNodeInfo :: HieAST a -> Maybe (NodeInfo a)
504504
generatedNodeInfo = Map.lookup GeneratedInfo . getSourcedNodeInfo . sourcedNodeInfo
505505

506506
data GhcVersion
507-
= GHC810
508-
| GHC90
509-
| GHC92
507+
= GHC92
510508
| GHC94
511509
| GHC96
512510
| GHC98

ghcide/test/exe/CodeLensTests.hs

Lines changed: 1 addition & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -83,7 +83,7 @@ addSigLensesTests =
8383
, ("pattern MkT1' b <- MkT1 42 b\n where MkT1' b = MkT1 42 b", "pattern MkT1' :: (Eq a, Num a) => Show b => b -> T1 a")
8484
, ("qualifiedSigTest= C.realPart", "qualifiedSigTest :: C.Complex a -> a")
8585
, ("head = 233", "head :: Integer")
86-
, ("rank2Test (k :: forall a . a -> a) = (k 233 :: Int, k \"QAQ\")", "rank2Test :: (forall a. a -> a) -> (Int, " <> listOfChar <> ")")
86+
, ("rank2Test (k :: forall a . a -> a) = (k 233 :: Int, k \"QAQ\")", "rank2Test :: (forall a. a -> a) -> (Int, String)")
8787
, ("symbolKindTest = Proxy @\"qwq\"", "symbolKindTest :: Proxy \"qwq\"")
8888
, ("promotedKindTest = Proxy @Nothing", if ghcVersion >= GHC96 then "promotedKindTest :: Proxy Nothing" else "promotedKindTest :: Proxy 'Nothing")
8989
, ("typeOperatorTest = Refl", if ghcVersion >= GHC92 then "typeOperatorTest :: forall {k} {a :: k}. a :~: a" else "typeOperatorTest :: a :~: a")
@@ -112,10 +112,3 @@ addSigLensesTests =
112112
newLens <- getCodeLenses doc
113113
liftIO $ newLens @?= oldLens
114114
]
115-
116-
-- | Before ghc9, lists of Char is displayed as [Char], but with ghc9 and up, it's displayed as String
117-
listOfChar :: T.Text
118-
listOfChar | ghcVersion >= GHC90 = "String"
119-
| otherwise = "[Char]"
120-
121-

ghcide/test/exe/CompletionTests.hs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -261,7 +261,7 @@ nonLocalCompletionTests =
261261
[]
262262
]
263263
where
264-
brokenForWinGhc = knownBrokenFor (BrokenSpecific Windows [GHC90, GHC92, GHC94, GHC96, GHC98]) "Windows has strange things in scope for some reason"
264+
brokenForWinGhc = knownBrokenFor (BrokenSpecific Windows [GHC92, GHC94, GHC96, GHC98]) "Windows has strange things in scope for some reason"
265265

266266
otherCompletionTests :: [TestTree]
267267
otherCompletionTests = [
@@ -527,14 +527,14 @@ completionDocTests =
527527
]
528528
let expected = "*Imported from 'Prelude'*\n"
529529
test doc (Position 1 8) "odd" (Just $ T.length expected) [expected]
530-
, brokenForMacGhc9 $ brokenForWinGhc90 $ testSession "extern single line doc without '\\n'" $ do
530+
, brokenForMacGhc9 $ testSession "extern single line doc without '\\n'" $ do
531531
doc <- createDoc "A.hs" "haskell" $ T.unlines
532532
[ "module A where"
533533
, "foo = no"
534534
]
535535
let expected = "*Imported from 'Prelude'*\n* * *\n\n\nBoolean \"not\"\n"
536536
test doc (Position 1 8) "not" (Just $ T.length expected) [expected]
537-
, brokenForMacGhc9 $ brokenForWinGhc90 $ testSession "extern mulit line doc" $ do
537+
, brokenForMacGhc9 $ testSession "extern mulit line doc" $ do
538538
doc <- createDoc "A.hs" "haskell" $ T.unlines
539539
[ "module A where"
540540
, "foo = i"
@@ -550,9 +550,8 @@ completionDocTests =
550550
test doc (Position 1 7) "id" (Just $ T.length expected) [expected]
551551
]
552552
where
553-
brokenForWinGhc90 = knownBrokenFor (BrokenSpecific Windows [GHC90]) "Extern doc doesn't support Windows for ghc9.2"
554553
-- https://gitlab.haskell.org/ghc/ghc/-/issues/20903
555-
brokenForMacGhc9 = knownBrokenFor (BrokenSpecific MacOS [GHC90, GHC92, GHC94, GHC96]) "Extern doc doesn't support MacOS for ghc9"
554+
brokenForMacGhc9 = knownBrokenFor (BrokenSpecific MacOS [GHC92, GHC94, GHC96]) "Extern doc doesn't support MacOS for ghc9"
556555
test doc pos label mn expected = do
557556
_ <- waitForDiagnostics
558557
compls <- getCompletions doc pos

ghcide/test/exe/CradleTests.hs

Lines changed: 5 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ import Control.Applicative.Combinators
88
import Control.Monad.IO.Class (liftIO)
99
import Data.Row
1010
import qualified Data.Text as T
11-
import Development.IDE.GHC.Compat (GhcVersion (..), ghcVersion)
11+
import Development.IDE.GHC.Compat (GhcVersion (..))
1212
import Development.IDE.GHC.Util
1313
import Development.IDE.Test (expectDiagnostics,
1414
expectDiagnosticsWithTags,
@@ -84,7 +84,7 @@ retryFailedCradle = testSession' "retry failed" $ \dir -> do
8484
-- Fix the cradle and typecheck again
8585
let validCradle = "cradle: {bios: {shell: \"echo A.hs\"}}"
8686
liftIO $ writeFileUTF8 hiePath $ T.unpack validCradle
87-
sendNotification SMethod_WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $
87+
sendNotification SMethod_WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams
8888
[FileEvent (filePathToUri $ dir </> "hie.yaml") FileChangeType_Changed ]
8989

9090
WaitForIdeRuleResult {..} <- waitForAction "TypeCheck" doc
@@ -211,17 +211,14 @@ sessionDepsArePickedUp = testSession'
211211
"cradle: {direct: {arguments: []}}"
212212
-- Open without OverloadedStrings and expect an error.
213213
doc <- createDoc "Foo.hs" "haskell" fooContent
214-
expectDiagnostics $
215-
if ghcVersion >= GHC90
216-
-- String vs [Char] causes this change in error message
217-
then [("Foo.hs", [(DiagnosticSeverity_Error, (3, 6), "Couldn't match type")])]
218-
else [("Foo.hs", [(DiagnosticSeverity_Error, (3, 6), "Couldn't match expected type")])]
214+
expectDiagnostics [("Foo.hs", [(DiagnosticSeverity_Error, (3, 6), "Couldn't match type")])]
215+
219216
-- Update hie.yaml to enable OverloadedStrings.
220217
liftIO $
221218
writeFileUTF8
222219
(dir </> "hie.yaml")
223220
"cradle: {direct: {arguments: [-XOverloadedStrings]}}"
224-
sendNotification SMethod_WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $
221+
sendNotification SMethod_WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams
225222
[FileEvent (filePathToUri $ dir </> "hie.yaml") FileChangeType_Changed ]
226223
-- Send change event.
227224
let change =

ghcide/test/exe/DependentFileTest.hs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -44,14 +44,11 @@ tests = testGroup "addDependentFile"
4444
let bazContent = T.unlines ["module Baz where", "import Foo ()"]
4545
_ <- createDoc "Foo.hs" "haskell" fooContent
4646
doc <- createDoc "Baz.hs" "haskell" bazContent
47-
expectDiagnostics $
48-
if ghcVersion >= GHC90
49-
-- String vs [Char] causes this change in error message
50-
then [("Foo.hs", [(DiagnosticSeverity_Error, if ghcVersion >= GHC92 then (4,11) else (4, 6), "Couldn't match type")])]
51-
else [("Foo.hs", [(DiagnosticSeverity_Error, (4, 6), "Couldn't match expected type")])]
47+
expectDiagnostics
48+
[("Foo.hs", [(DiagnosticSeverity_Error, if ghcVersion >= GHC92 then (4,11) else (4, 6), "Couldn't match type")])]
5249
-- Now modify the dependent file
5350
liftIO $ writeFile depFilePath "B"
54-
sendNotification SMethod_WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $
51+
sendNotification SMethod_WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams
5552
[FileEvent (filePathToUri "dep-file.txt") FileChangeType_Changed ]
5653

5754
-- Modifying Baz will now trigger Foo to be rebuilt as well

ghcide/test/exe/DiagnosticTests.hs

Lines changed: 0 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -401,22 +401,6 @@ tests = testGroup "diagnostics"
401401
liftIO $ unless ("redundant" `T.isInfixOf` msg) $
402402
assertFailure ("Expected redundant import but got " <> T.unpack msg)
403403
closeDoc a
404-
, testSessionWait "haddock parse error" $ do
405-
let fooContent = T.unlines
406-
[ "module Foo where"
407-
, "foo :: Int"
408-
, "foo = 1 {-|-}"
409-
]
410-
_ <- createDoc "Foo.hs" "haskell" fooContent
411-
if ghcVersion >= GHC90 then
412-
-- Haddock parse errors are ignored on ghc-9.0
413-
pure ()
414-
else
415-
expectDiagnostics
416-
[ ( "Foo.hs"
417-
, [(DiagnosticSeverity_Warning, (2, 8), "Haddock parse error on input")]
418-
)
419-
]
420404
, testSessionWait "strip file path" $ do
421405
let
422406
name = "Testing"

ghcide/test/exe/FindDefinitionAndHoverTests.hs

Lines changed: 6 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -177,12 +177,8 @@ tests = let
177177
in
178178
mkFindTests
179179
-- def hover look expect
180-
[
181-
if ghcVersion >= GHC90 then
182-
-- It suggests either going to the constructor or to the field
183-
test broken yes fffL4 fff "field in record definition"
184-
else
185-
test yes yes fffL4 fff "field in record definition"
180+
[ -- It suggests either going to the constructor or to the field
181+
test broken yes fffL4 fff "field in record definition"
186182
, test yes yes fffL8 fff "field in record construction #1102"
187183
, test yes yes fffL14 fff "field name used as accessor" -- https://github.com/haskell/ghcide/pull/120 in Calculate.hs
188184
, test yes yes aaaL14 aaa "top-level name" -- https://github.com/haskell/ghcide/pull/120
@@ -215,25 +211,19 @@ tests = let
215211
, test no broken txtL8 litT "literal Text in hover info #1016"
216212
, test no broken lstL43 litL "literal List in hover info #1016"
217213
, test yes yes cmtL68 lackOfdEq "no Core symbols #3280"
218-
, if ghcVersion >= GHC90 then
219-
test no yes docL41 constr "type constraint in hover info #1012"
220-
else
221-
test no broken docL41 constr "type constraint in hover info #1012"
214+
, test no yes docL41 constr "type constraint in hover info #1012"
222215
, test no yes outL45 outSig "top-level signature #767"
223216
, test broken broken innL48 innSig "inner signature #767"
224217
, test no yes holeL60 hleInfo "hole without internal name #831"
225218
, test no yes holeL65 hleInfo2 "hole with variable"
226219
, test no yes cccL17 docLink "Haddock html links"
227220
, testM yes yes imported importedSig "Imported symbol"
228-
, if | isWindows ->
221+
, if isWindows then
229222
-- Flaky on Windows: https://github.com/haskell/haskell-language-server/issues/2997
230223
testM no yes reexported reexportedSig "Imported symbol (reexported)"
231-
| otherwise ->
224+
else
232225
testM yes yes reexported reexportedSig "Imported symbol (reexported)"
233-
, if | ghcVersion == GHC90 && isWindows ->
234-
test no broken thLocL57 thLoc "TH Splice Hover"
235-
| otherwise ->
236-
test no yes thLocL57 thLoc "TH Splice Hover"
226+
, test no yes thLocL57 thLoc "TH Splice Hover"
237227
, test yes yes import310 pkgTxt "show package name and its version"
238228
]
239229
where yes, broken :: (TestTree -> Maybe TestTree)

ghcide/test/exe/HighlightTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ tests = testGroup "highlight"
4444
, DocumentHighlight (R 6 10 6 13) (Just DocumentHighlightKind_Read)
4545
, DocumentHighlight (R 7 12 7 15) (Just DocumentHighlightKind_Read)
4646
]
47-
, knownBrokenForGhcVersions [GHC90, GHC92, GHC94, GHC96, GHC98] "Ghc9 highlights the constructor and not just this field" $
47+
, knownBrokenForGhcVersions [GHC92, GHC94, GHC96, GHC98] "Ghc9 highlights the constructor and not just this field" $
4848
testSessionWait "record" $ do
4949
doc <- createDoc "A.hs" "haskell" recsource
5050
_ <- waitForDiagnostics

ghcide/test/exe/IfaceTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ ifaceTHTest = testCase "iface-th-test" $ runWithExtraFiles "TH" $ \dir -> do
5555
changeDoc cdoc [TextDocumentContentChangeEvent . InR . (.==) #text $ cSource]
5656
expectDiagnostics
5757
[("THC.hs", [(DiagnosticSeverity_Error, (4, 4), "Couldn't match expected type '()' with actual type 'Bool'")])
58-
,("THB.hs", [(DiagnosticSeverity_Warning, (4,thDollarIdx), "Top-level binding")])]
58+
,("THB.hs", [(DiagnosticSeverity_Warning, (4,1), "Top-level binding")])]
5959
closeDoc cdoc
6060

6161
ifaceErrorTest :: TestTree

0 commit comments

Comments
 (0)