Skip to content

Commit 104c87f

Browse files
committed
Remove GLASGOW_HASKELL, and GHC94 from tests
1 parent 8a5ea73 commit 104c87f

File tree

10 files changed

+29
-100
lines changed

10 files changed

+29
-100
lines changed

ghcide-test/exe/CompletionTests.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -276,8 +276,7 @@ nonLocalCompletionTests =
276276
where
277277
brokenForWinGhc = knownBrokenOnWindows "Windows has strange things in scope for some reason"
278278
brokenForWinOldGhc =
279-
knownBrokenInSpecificEnv [HostOS Windows, GhcVer GHC94] "Windows (GHC == 9.4) has strange things in scope for some reason"
280-
. knownBrokenInSpecificEnv [HostOS Windows, GhcVer GHC96] "Windows (GHC == 9.6) has strange things in scope for some reason"
279+
knownBrokenInSpecificEnv [HostOS Windows, GhcVer GHC96] "Windows (GHC == 9.6) has strange things in scope for some reason"
281280
. knownBrokenInSpecificEnv [HostOS Windows, GhcVer GHC98] "Windows (GHC == 9.8) has strange things in scope for some reason"
282281

283282
otherCompletionTests :: [TestTree]
@@ -350,10 +349,11 @@ packageCompletionTests =
350349
, _label == "fromList"
351350
]
352351
liftIO $ take 3 (sort compls') @?=
353-
map ("Defined in "<>) (
354-
[ "'Data.List.NonEmpty"
352+
map ("Defined in "<>) [
353+
"'Data.List.NonEmpty"
355354
, "'GHC.Exts"
356-
] ++ (["'GHC.IsList" | ghcVersion >= GHC94]))
355+
, "'GHC.IsList"
356+
]
357357

358358
, testSessionEmptyWithCradle "Map" "cradle: {direct: {arguments: [-hide-all-packages, -package, base, -package, containers, A]}}" $ do
359359
doc <- createDoc "A.hs" "haskell" $ T.unlines

ghcide-test/exe/DiagnosticTests.hs

Lines changed: 3 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -343,19 +343,9 @@ tests = testGroup "diagnostics"
343343
expectDiagnostics
344344
[ ( "Main.hs"
345345
, [(DiagnosticSeverity_Error, (6, 9),
346-
if ghcVersion >= GHC96 then
347-
"Variable not in scope: ThisList.map"
348-
else if ghcVersion >= GHC94 then
349-
"Variable not in scope: map" -- See https://gitlab.haskell.org/ghc/ghc/-/issues/22130
350-
else
351-
"Not in scope: \8216ThisList.map\8217", Just "GHC-88464")
346+
"Variable not in scope: ThisList.map", Just "GHC-88464")
352347
,(DiagnosticSeverity_Error, (7, 9),
353-
if ghcVersion >= GHC96 then
354-
"Variable not in scope: BaseList.x"
355-
else if ghcVersion >= GHC94 then
356-
"Variable not in scope: x" -- See https://gitlab.haskell.org/ghc/ghc/-/issues/22130
357-
else
358-
"Not in scope: \8216BaseList.x\8217", Just "GHC-88464")
348+
"Variable not in scope: BaseList.x", Just "GHC-88464")
359349
]
360350
)
361351
]
@@ -373,7 +363,7 @@ tests = testGroup "diagnostics"
373363
-- where appropriate. The warning should use an unqualified name 'Ord', not
374364
-- something like 'GHC.Classes.Ord'. The choice of redundant-constraints to
375365
-- test this is fairly arbitrary.
376-
, [(DiagnosticSeverity_Warning, (2, if ghcVersion >= GHC94 then 7 else 0), "Redundant constraint: Ord a", Just "GHC-30606")
366+
, [(DiagnosticSeverity_Warning, (2, 7), "Redundant constraint: Ord a", Just "GHC-30606")
377367
]
378368
)
379369
]

ghcide-test/exe/FindDefinitionAndHoverTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -187,7 +187,7 @@ tests = let
187187
holeL65 = Position 65 8 ; hleInfo2 = [ExpectHoverText ["_ :: a -> Maybe a"]]
188188
cccL17 = Position 17 16 ; docLink = [ExpectHoverTextRegex "\\*Defined in 'GHC.Types'\\* \\*\\(ghc-prim-[0-9.]+\\)\\*\n\n"]
189189
imported = Position 56 13 ; importedSig = getDocUri "Foo.hs" >>= \foo -> return [ExpectHoverText ["foo", "Foo", "Haddock"], mkL foo 5 0 5 3]
190-
reexported = Position 55 14 ; reexportedSig = getDocUri "Bar.hs" >>= \bar -> return [ExpectHoverText ["Bar", "Bar", "Haddock"], if ghcVersion >= GHC94 && ghcVersion < GHC910 then mkL bar 3 5 3 8 else mkL bar 3 0 3 14]
190+
reexported = Position 55 14 ; reexportedSig = getDocUri "Bar.hs" >>= \bar -> return [ExpectHoverText ["Bar", "Bar", "Haddock"], if ghcVersion < GHC910 then mkL bar 3 5 3 8 else mkL bar 3 0 3 14]
191191
thLocL57 = Position 59 10 ; thLoc = [ExpectHoverText ["Identity"]]
192192
cmtL68 = Position 67 0 ; lackOfdEq = [ExpectHoverExcludeText ["$dEq"]]
193193
import310 = Position 3 10; pkgTxt = [ExpectHoverText ["Data.Text\n\ntext-"]]

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

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -409,8 +409,7 @@ generatedNodeInfo :: HieAST a -> Maybe (NodeInfo a)
409409
generatedNodeInfo = Map.lookup GeneratedInfo . getSourcedNodeInfo . sourcedNodeInfo
410410

411411
data GhcVersion
412-
= GHC94
413-
| GHC96
412+
= GHC96
414413
| GHC98
415414
| GHC910
416415
| GHC912
@@ -426,10 +425,8 @@ ghcVersion = GHC912
426425
ghcVersion = GHC910
427426
#elif MIN_VERSION_GLASGOW_HASKELL(9,8,0,0)
428427
ghcVersion = GHC98
429-
#elif MIN_VERSION_GLASGOW_HASKELL(9,6,0,0)
428+
#else
430429
ghcVersion = GHC96
431-
#elif MIN_VERSION_GLASGOW_HASKELL(9,4,0,0)
432-
ghcVersion = GHC94
433430
#endif
434431

435432
simpleNodeInfoCompat :: FastStringCompat -> FastStringCompat -> NodeInfo a

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

Lines changed: 0 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -616,21 +616,11 @@ pattern ExposePackage s a mr = DynFlags.ExposePackage s a mr
616616
#endif
617617

618618
isVisibleFunArg :: Development.IDE.GHC.Compat.Core.FunTyFlag -> Bool
619-
#if __GLASGOW_HASKELL__ >= 906
620619
isVisibleFunArg = TypesVar.isVisibleFunArg
621620
type FunTyFlag = TypesVar.FunTyFlag
622-
#else
623-
isVisibleFunArg VisArg = True
624-
isVisibleFunArg _ = False
625-
type FunTyFlag = TypesVar.AnonArgFlag
626-
#endif
627621
pattern FunTy :: Development.IDE.GHC.Compat.Core.FunTyFlag -> Type -> Type -> Type
628622
pattern FunTy af arg res <- TyCoRep.FunTy {ft_af = af, ft_arg = arg, ft_res = res}
629623

630-
631-
-- type HasSrcSpan x a = (GenLocated SrcSpan a ~ x)
632-
-- type HasSrcSpan x = () :: Constraint
633-
634624
class HasSrcSpan a where
635625
getLoc :: a -> SrcSpan
636626

hie-compat/src-ghc92/Compat/HieAst.hs

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1040,10 +1040,6 @@ instance HiePass p => ToHie (PScoped (LocatedA (Pat (GhcPass p)))) where
10401040
in [ toHie $ L ospan wrap
10411041
, toHie $ PS rsp scope pscope $ (L ospan pat)
10421042
]
1043-
-- CHANGED: removed preprocessor stuff
1044-
-- #if __GLASGOW_HASKELL__ < 811
1045-
-- HieRn -> []
1046-
-- #endif
10471043
where
10481044
contextify :: a ~ LPat (GhcPass p) => HsConDetails (HsPatSigType (NoGhcTc (GhcPass p))) a (HsRecFields (GhcPass p) a)
10491045
-> HsConDetails (TScoped (HsPatSigType (NoGhcTc (GhcPass p)))) (PScoped a) (RContext (HsRecFields (GhcPass p) (PScoped a)))
@@ -1928,11 +1924,6 @@ instance HiePass p => ToHie (LocatedA (HsSplice (GhcPass p))) where
19281924
HsSpliced _ _ _ ->
19291925
[]
19301926
XSplice x -> case ghcPass @p of
1931-
-- CHANGED: removed preprocessor stuff
1932-
-- #if __GLASGOW_HASKELL__ < 811
1933-
-- GhcPs -> noExtCon x
1934-
-- GhcRn -> noExtCon x
1935-
-- #endif
19361927
GhcTc -> case x of
19371928
HsSplicedT _ -> []
19381929

plugins/hls-change-type-signature-plugin/test/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@ test :: TestTree
3939
test = testGroup "changeTypeSignature" [
4040
testRegexes
4141
, codeActionTest "TExpectedActual" 4 11
42-
, knownBrokenForGhcVersions [GHC94 .. GHC912] "Error Message in 9.2+ does not provide enough info" $
42+
, knownBrokenForGhcVersions [GHC96 .. GHC912] "Error Message in 9.2+ does not provide enough info" $
4343
codeActionTest "TRigidType" 4 14
4444
, codeActionTest "TRigidType2" 4 6
4545
, codeActionTest "TLocalBinding" 7 22

plugins/hls-eval-plugin/test/Main.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -84,8 +84,8 @@ tests =
8484
evalInFile "T8.hs" "-- >>> 3 `div` 0" "-- divide by zero" -- The default for marking exceptions is False
8585
, goldenWithEval "Applies file LANGUAGE extensions" "T9" "hs"
8686
, goldenWithEval "Evaluate a type with :kind!" "T10" "hs"
87-
, goldenWithEval' "Reports an error for an incorrect type with :kind!" "T11" "hs"
88-
(if ghcVersion >= GHC94 then "ghc94.expected" else "expected")
87+
-- TODO: I do not understand why this is 'ghc94.expected'.
88+
, goldenWithEval' "Reports an error for an incorrect type with :kind!" "T11" "hs" "ghc94.expected"
8989
, goldenWithEval "Shows a kind with :kind" "T12" "hs"
9090
, goldenWithEval "Reports an error for an incorrect type with :kind" "T13" "hs"
9191
, goldenWithEval' "Returns a fully-instantiated type for :type" "T14" "hs" (if ghcVersion >= GHC98 then "ghc98.expected" else "expected") -- See https://gitlab.haskell.org/ghc/ghc/-/issues/24069
@@ -138,7 +138,6 @@ tests =
138138
GHC910 -> "ghc910.expected"
139139
GHC98 -> "ghc98.expected"
140140
GHC96 -> "ghc96.expected"
141-
GHC94 -> "ghc94.expected"
142141
, goldenWithEval "Prelude has no special treatment, it is imported as stated in the module" "TPrelude" "hs"
143142
, goldenWithEval "Don't panic on {-# UNPACK #-} pragma" "TUNPACK" "hs"
144143
, goldenWithEval "Can handle eval inside nested comment properly" "TNested" "hs"
@@ -219,7 +218,7 @@ tests =
219218
knownBrokenInWindowsBeforeGHC912 msg =
220219
foldl (.) id
221220
[ knownBrokenInSpecificEnv [GhcVer ghcVer, HostOS Windows] msg
222-
| ghcVer <- [GHC94 .. GHC910]
221+
| ghcVer <- [GHC96 .. GHC910]
223222
]
224223

225224
goldenWithEval :: TestName -> FilePath -> FilePath -> TestTree

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 1 addition & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1481,11 +1481,6 @@ suggestNewImport df packageExportsMap ps fileContents Diagnostic{..}
14811481
>>= (findImportDeclByModuleName hsmodImports . T.unpack)
14821482
>>= ideclAs . unLoc
14831483
<&> T.pack . moduleNameString . unLoc
1484-
, -- tentative workaround for detecting qualification in GHC 9.4
1485-
-- FIXME: We can delete this after dropping the support for GHC 9.4
1486-
qualGHC94 <-
1487-
guard (ghcVersion == GHC94)
1488-
*> extractQualifiedModuleNameFromMissingName (extractTextInRange _range fileContents)
14891484
, Just (range, indent) <- newImportInsertRange ps fileContents
14901485
, extendImportSuggestions <- matchRegexUnifySpaces msg
14911486
#if MIN_VERSION_ghc(9,7,0)
@@ -1494,19 +1489,8 @@ suggestNewImport df packageExportsMap ps fileContents Diagnostic{..}
14941489
"Perhaps you want to add ‘[^’]*’ to the import list in the import of ‘([^’]*)’"
14951490
#endif
14961491
= let qis = qualifiedImportStyle df
1497-
-- FIXME: we can use thingMissing once the support for GHC 9.4 is dropped.
1498-
-- In what fllows, @missing@ is assumed to be qualified name.
1499-
-- @thingMissing@ is already as desired with GHC != 9.4.
1500-
-- In GHC 9.4, however, GHC drops a module qualifier from a qualified symbol.
1501-
-- Thus we need to explicitly concatenate qualifier explicity in GHC 9.4.
1502-
missing
1503-
| GHC94 <- ghcVersion
1504-
, isNothing (qual <|> qual')
1505-
, Just q <- qualGHC94 =
1506-
qualify q thingMissing
1507-
| otherwise = thingMissing
15081492
suggestions = nubSortBy simpleCompareImportSuggestion
1509-
(constructNewImportSuggestions packageExportsMap (qual <|> qual' <|> qualGHC94, missing) extendImportSuggestions qis) in
1493+
(constructNewImportSuggestions packageExportsMap (qual <|> qual', thingMissing) extendImportSuggestions qis) in
15101494
map (\(ImportSuggestion _ kind (unNewImport -> imp)) -> (imp, kind, TextEdit range (imp <> "\n" <> T.replicate indent " "))) suggestions
15111495
where
15121496
qualify q (NotInScopeDataConstructor d) = NotInScopeDataConstructor (q <> "." <> d)

plugins/hls-refactor-plugin/test/Main.hs

Lines changed: 13 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
1-
{-# LANGUAGE CPP #-}
21
{-# LANGUAGE AllowAmbiguousTypes #-}
2+
{-# LANGUAGE CPP #-}
33
{-# LANGUAGE DataKinds #-}
44
{-# LANGUAGE DuplicateRecordFields #-}
55
{-# LANGUAGE GADTs #-}
@@ -1359,8 +1359,7 @@ extendImportTests = testGroup "extend import actions"
13591359
[ "import Data.Monoid (First (..))"
13601360
, "f = (First Nothing) <> mempty"
13611361
])
1362-
, brokenForGHC94 "On GHC 9.4, the error messages with -fdefer-type-errors don't have necessary imported target srcspan info." $
1363-
testSession "extend single line qualified import with value" $ template
1362+
, testSession "extend single line qualified import with value" $ template
13641363
[("ModuleA.hs", T.unlines
13651364
[ "module ModuleA where"
13661365
, "stuffA :: Double"
@@ -1552,8 +1551,7 @@ extendImportTests = testGroup "extend import actions"
15521551
)
15531552
(Range (Position 2 3) (Position 2 7))
15541553
)
1555-
, ignoreForGhcVersions [GHC94] "Diagnostic message has no suggestions" $
1556-
testSession "type constructor name same as data constructor name" $ template
1554+
, testSession "type constructor name same as data constructor name" $ template
15571555
[("ModuleA.hs", T.unlines
15581556
[ "module ModuleA where"
15591557
, "newtype Foo = Foo Int"
@@ -1855,7 +1853,7 @@ suggestImportTests = testGroup "suggest import actions"
18551853
suggestAddRecordFieldImportTests :: TestTree
18561854
suggestAddRecordFieldImportTests = testGroup "suggest imports of record fields when using OverloadedRecordDot"
18571855
[ testGroup "The field is suggested when an instance resolution failure occurs"
1858-
([ ignoreForGhcVersions [GHC94, GHC96] "Extension not present <9.2, and the assist is derived from the help message in >=9.4" theTest
1856+
([ ignoreForGhcVersions [GHC96] "Extension not present <9.2, and the assist is derived from the help message in >=9.4" theTest
18591857
]
18601858
++ [
18611859
theTestIndirect qualifiedGhcRecords polymorphicType
@@ -2619,9 +2617,7 @@ addTypeAnnotationsToLiteralsTest = testGroup "add type annotations to literals t
26192617
, ""
26202618
, "f = 1"
26212619
]
2622-
(if ghcVersion >= GHC94
2623-
then [ (DiagnosticSeverity_Warning, (3, 4), "Defaulting the type variable", Nothing) ]
2624-
else [ (DiagnosticSeverity_Warning, (3, 4), "Defaulting the following constraint", Nothing) ])
2620+
[ (DiagnosticSeverity_Warning, (3, 4), "Defaulting the type variable", Nothing) ]
26252621
"Add type annotation ‘Integer’ to ‘1’"
26262622
[ "{-# OPTIONS_GHC -Wtype-defaults #-}"
26272623
, "module A (f) where"
@@ -2638,9 +2634,7 @@ addTypeAnnotationsToLiteralsTest = testGroup "add type annotations to literals t
26382634
, " let x = 3"
26392635
, " in x"
26402636
]
2641-
(if ghcVersion >= GHC94
2642-
then [ (DiagnosticSeverity_Warning, (4, 12), "Defaulting the type variable", Nothing) ]
2643-
else [ (DiagnosticSeverity_Warning, (4, 12), "Defaulting the following constraint", Nothing) ])
2637+
[ (DiagnosticSeverity_Warning, (4, 12), "Defaulting the type variable", Nothing) ]
26442638
"Add type annotation ‘Integer’ to ‘3’"
26452639
[ "{-# OPTIONS_GHC -Wtype-defaults #-}"
26462640
, "module A where"
@@ -2658,9 +2652,7 @@ addTypeAnnotationsToLiteralsTest = testGroup "add type annotations to literals t
26582652
, " let x = let y = 5 in y"
26592653
, " in x"
26602654
]
2661-
(if ghcVersion >= GHC94
2662-
then [ (DiagnosticSeverity_Warning, (4, 20), "Defaulting the type variable", Nothing) ]
2663-
else [ (DiagnosticSeverity_Warning, (4, 20), "Defaulting the following constraint", Nothing) ])
2655+
[ (DiagnosticSeverity_Warning, (4, 20), "Defaulting the type variable", Nothing) ]
26642656
"Add type annotation ‘Integer’ to ‘5’"
26652657
[ "{-# OPTIONS_GHC -Wtype-defaults #-}"
26662658
, "module A where"
@@ -2679,15 +2671,9 @@ addTypeAnnotationsToLiteralsTest = testGroup "add type annotations to literals t
26792671
, ""
26802672
, "f = seq \"debug\" traceShow \"debug\""
26812673
]
2682-
(if ghcVersion >= GHC94
2683-
then
2684-
[ (DiagnosticSeverity_Warning, (6, 8), "Defaulting the type variable", Nothing)
2685-
, (DiagnosticSeverity_Warning, (6, 16), "Defaulting the type variable", Nothing)
2686-
]
2687-
else
2688-
[ (DiagnosticSeverity_Warning, (6, 8), "Defaulting the following constraint", Nothing)
2689-
, (DiagnosticSeverity_Warning, (6, 16), "Defaulting the following constraint", Nothing)
2690-
])
2674+
[ (DiagnosticSeverity_Warning, (6, 8), "Defaulting the type variable", Nothing)
2675+
, (DiagnosticSeverity_Warning, (6, 16), "Defaulting the type variable", Nothing)
2676+
]
26912677
("Add type annotation ‘" <> stringLit <> "’ to ‘\"debug\"")
26922678
[ "{-# OPTIONS_GHC -Wtype-defaults #-}"
26932679
, "{-# LANGUAGE OverloadedStrings #-}"
@@ -2707,9 +2693,7 @@ addTypeAnnotationsToLiteralsTest = testGroup "add type annotations to literals t
27072693
, ""
27082694
, "f a = traceShow \"debug\" a"
27092695
]
2710-
(if ghcVersion >= GHC94
2711-
then [ (DiagnosticSeverity_Warning, (6, 6), "Defaulting the type variable", Nothing) ]
2712-
else [ (DiagnosticSeverity_Warning, (6, 6), "Defaulting the following constraint", Nothing) ])
2696+
[ (DiagnosticSeverity_Warning, (6, 6), "Defaulting the type variable", Nothing) ]
27132697
("Add type annotation ‘" <> stringLit <> "’ to ‘\"debug\"")
27142698
[ "{-# OPTIONS_GHC -Wtype-defaults #-}"
27152699
, "{-# LANGUAGE OverloadedStrings #-}"
@@ -2729,9 +2713,7 @@ addTypeAnnotationsToLiteralsTest = testGroup "add type annotations to literals t
27292713
, ""
27302714
, "f = seq (\"debug\" :: [Char]) (seq (\"debug\" :: [Char]) (traceShow \"debug\"))"
27312715
]
2732-
(if ghcVersion >= GHC94
2733-
then [ (DiagnosticSeverity_Warning, (6, 54), "Defaulting the type variable", Nothing) ]
2734-
else [ (DiagnosticSeverity_Warning, (6, 54), "Defaulting the following constraint", Nothing) ])
2716+
[ (DiagnosticSeverity_Warning, (6, 54), "Defaulting the type variable", Nothing) ]
27352717
("Add type annotation ‘"<> stringLit <>"’ to ‘\"debug\"")
27362718
[ "{-# OPTIONS_GHC -Wtype-defaults #-}"
27372719
, "{-# LANGUAGE OverloadedStrings #-}"
@@ -3405,8 +3387,7 @@ exportUnusedTests = testGroup "export unused actions"
34053387
]
34063388
(R 2 0 2 11)
34073389
"Export ‘bar’"
3408-
, ignoreForGhcVersions [GHC94] "Diagnostic message has no suggestions" $
3409-
testSession "type is exported but not the constructor of same name" $ templateNoAction
3390+
, testSession "type is exported but not the constructor of same name" $ templateNoAction
34103391
[ "{-# OPTIONS_GHC -Wunused-top-binds #-}"
34113392
, "module A (Foo) where"
34123393
, "data Foo = Foo"
@@ -4049,6 +4030,3 @@ pattern R x y x' y' = Range (Position x y) (Position x' y')
40494030
-- @/var@
40504031
withTempDir :: (FilePath -> IO a) -> IO a
40514032
withTempDir f = System.IO.Extra.withTempDir $ (canonicalizePath >=> f)
4052-
4053-
brokenForGHC94 :: String -> TestTree -> TestTree
4054-
brokenForGHC94 = knownBrokenForGhcVersions [GHC94]

0 commit comments

Comments
 (0)