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"
18551853suggestAddRecordFieldImportTests :: TestTree
18561854suggestAddRecordFieldImportTests = 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@
40504031withTempDir :: (FilePath -> IO a ) -> IO a
40514032withTempDir f = System.IO.Extra. withTempDir $ (canonicalizePath >=> f)
4052-
4053- brokenForGHC94 :: String -> TestTree -> TestTree
4054- brokenForGHC94 = knownBrokenForGhcVersions [GHC94 ]
0 commit comments