diff options
Diffstat (limited to 'testsuite/tests/ghci')
50 files changed, 90 insertions, 92 deletions
diff --git a/testsuite/tests/ghci/T18071/T18071.hs b/testsuite/tests/ghci/T18071/T18071.hs index 1b0d53c337..aa1387cf69 100644 --- a/testsuite/tests/ghci/T18071/T18071.hs +++ b/testsuite/tests/ghci/T18071/T18071.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE QuantifiedConstraints #-} diff --git a/testsuite/tests/ghci/T18071/T18071.stdout b/testsuite/tests/ghci/T18071/T18071.stdout index 815aa1e245..20411b0310 100644 --- a/testsuite/tests/ghci/T18071/T18071.stdout +++ b/testsuite/tests/ghci/T18071/T18071.stdout @@ -1 +1 @@ -instance [safe] MyShowProxy U -- Defined at T18071.hs:16:10 +instance [safe] MyShowProxy U -- Defined at T18071.hs:17:10 diff --git a/testsuite/tests/ghci/T18262/T18262.hs b/testsuite/tests/ghci/T18262/T18262.hs index 1734de0179..ce4bfe632f 100644 --- a/testsuite/tests/ghci/T18262/T18262.hs +++ b/testsuite/tests/ghci/T18262/T18262.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies, FlexibleInstances, DataKinds, UndecidableInstances #-} import GHC.TypeLits diff --git a/testsuite/tests/ghci/T18262/T18262.stdout b/testsuite/tests/ghci/T18262/T18262.stdout index 76d7e8a596..13868ead5a 100644 --- a/testsuite/tests/ghci/T18262/T18262.stdout +++ b/testsuite/tests/ghci/T18262/T18262.stdout @@ -1 +1 @@ -instance [safe] Err 'B -- Defined at T18262.hs:10:10 +instance [safe] Err 'B -- Defined at T18262.hs:11:10 diff --git a/testsuite/tests/ghci/prog006/Boot1.hs b/testsuite/tests/ghci/prog006/Boot1.hs index 0625737342..7711a5a4bf 100644 --- a/testsuite/tests/ghci/prog006/Boot1.hs +++ b/testsuite/tests/ghci/prog006/Boot1.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Boot where import A diff --git a/testsuite/tests/ghci/prog006/Boot2.hs b/testsuite/tests/ghci/prog006/Boot2.hs index 5e7297e448..cc1b36062a 100644 --- a/testsuite/tests/ghci/prog006/Boot2.hs +++ b/testsuite/tests/ghci/prog006/Boot2.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE ExistentialQuantification #-} module Boot where diff --git a/testsuite/tests/ghci/prog006/prog006.stderr b/testsuite/tests/ghci/prog006/prog006.stderr index aedba9717f..8b23e548ed 100644 --- a/testsuite/tests/ghci/prog006/prog006.stderr +++ b/testsuite/tests/ghci/prog006/prog006.stderr @@ -1,5 +1,5 @@ -Boot.hs:5:13: error: +Boot.hs:6:13: error: • Data constructor ‘D’ has existential type variables, a context, or a specialised result type D :: forall n. Class n => n -> Data (Enable ExistentialQuantification or GADTs to allow this) diff --git a/testsuite/tests/ghci/scripts/T12447.script b/testsuite/tests/ghci/scripts/T12447.script index 3bdd3f4b73..826dec0b63 100644 --- a/testsuite/tests/ghci/scripts/T12447.script +++ b/testsuite/tests/ghci/scripts/T12447.script @@ -1,3 +1,4 @@ +:set -XHaskell2010 :set -XRankNTypes -XConstraintKinds -XTypeApplications import Data.Typeable diff --git a/testsuite/tests/ghci/scripts/T12550.script b/testsuite/tests/ghci/scripts/T12550.script index 2834aeb7d9..53c0e37641 100644 --- a/testsuite/tests/ghci/scripts/T12550.script +++ b/testsuite/tests/ghci/scripts/T12550.script @@ -1,3 +1,4 @@ +:set -XHaskell2010 :set -fprint-explicit-foralls -XKindSignatures -XExplicitNamespaces -XUnicodeSyntax :set -Wno-star-is-type import Data.Kind (type Type) diff --git a/testsuite/tests/ghci/scripts/T13202a.script b/testsuite/tests/ghci/scripts/T13202a.script index 107d332a64..1f1a9908c9 100644 --- a/testsuite/tests/ghci/scripts/T13202a.script +++ b/testsuite/tests/ghci/scripts/T13202a.script @@ -1,3 +1,4 @@ +:set -XHaskell2010 import GHC.Records :set -XTypeApplications -XDataKinds let foo = getField @"name" diff --git a/testsuite/tests/ghci/scripts/T13202a.stderr b/testsuite/tests/ghci/scripts/T13202a.stderr index 8b1851f175..0402e7df7d 100644 --- a/testsuite/tests/ghci/scripts/T13202a.stderr +++ b/testsuite/tests/ghci/scripts/T13202a.stderr @@ -1,5 +1,5 @@ -<interactive>:3:5: error: +<interactive>:4:5: error: • Non type-variable argument in the constraint: HasField "name" r a (Use FlexibleContexts to permit this) • When checking the inferred type diff --git a/testsuite/tests/ghci/scripts/T13420.hs b/testsuite/tests/ghci/scripts/T13420.hs index 6b84e65cb2..5b911d8d4b 100644 --- a/testsuite/tests/ghci/scripts/T13420.hs +++ b/testsuite/tests/ghci/scripts/T13420.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies #-} module T13420 where diff --git a/testsuite/tests/ghci/scripts/T13420.stdout b/testsuite/tests/ghci/scripts/T13420.stdout index 030b902677..9e8d7a6b7f 100644 --- a/testsuite/tests/ghci/scripts/T13420.stdout +++ b/testsuite/tests/ghci/scripts/T13420.stdout @@ -3,4 +3,4 @@ type family F a where F [Int] = Bool F [a] = Double F (a b) = Char - -- Defined at T13420.hs:4:1 + -- Defined at T13420.hs:5:1 diff --git a/testsuite/tests/ghci/scripts/T14969.script b/testsuite/tests/ghci/scripts/T14969.script index ab6af53c6b..476f5bfc65 100644 --- a/testsuite/tests/ghci/scripts/T14969.script +++ b/testsuite/tests/ghci/scripts/T14969.script @@ -1 +1,2 @@ +:set -XHaskell2010 3 _ 4 diff --git a/testsuite/tests/ghci/scripts/T14969.stderr b/testsuite/tests/ghci/scripts/T14969.stderr index 13da943a3c..ee9b5d2de8 100644 --- a/testsuite/tests/ghci/scripts/T14969.stderr +++ b/testsuite/tests/ghci/scripts/T14969.stderr @@ -1,5 +1,5 @@ -<interactive>:1:1: error: +<interactive>:2:1: error: • Non type-variable argument in the constraint: Num (t2 -> t1 -> t3) (Use FlexibleContexts to permit this) diff --git a/testsuite/tests/ghci/scripts/T15546.script b/testsuite/tests/ghci/scripts/T15546.script index 76bcda783e..0a06c5c633 100644 --- a/testsuite/tests/ghci/scripts/T15546.script +++ b/testsuite/tests/ghci/scripts/T15546.script @@ -1,3 +1,4 @@ +:set -XHaskell2010 :set -XTypeFamilies type family E a b where E a a = (); E a b = Bool :info E diff --git a/testsuite/tests/ghci/scripts/T15546.stdout b/testsuite/tests/ghci/scripts/T15546.stdout index d14b442bb8..47ed331dfa 100644 --- a/testsuite/tests/ghci/scripts/T15546.stdout +++ b/testsuite/tests/ghci/scripts/T15546.stdout @@ -2,10 +2,10 @@ type E :: * -> * -> * type family E a b where E a a = () E a b = Bool - -- Defined at <interactive>:2:1 + -- Defined at <interactive>:3:1 type E :: * -> * -> * type family E a b where {- #0 -} E a a = () {- #1 -} E a b = Bool -- incompatible with: #0 - -- Defined at <interactive>:2:1 + -- Defined at <interactive>:3:1 diff --git a/testsuite/tests/ghci/scripts/T18501.script b/testsuite/tests/ghci/scripts/T18501.script index 64975cbc46..947cf936b3 100644 --- a/testsuite/tests/ghci/scripts/T18501.script +++ b/testsuite/tests/ghci/scripts/T18501.script @@ -1,3 +1,4 @@ +:set -XHaskell2010 :set -XAllowAmbiguousTypes class Foo a where foo :: String :t foo diff --git a/testsuite/tests/ghci/scripts/T19279.stdout b/testsuite/tests/ghci/scripts/T19279.stdout index fe7fbbf9f8..37e056e1aa 100644 --- a/testsuite/tests/ghci/scripts/T19279.stdout +++ b/testsuite/tests/ghci/scripts/T19279.stdout @@ -1,3 +1,3 @@ -T :: * -> * +T :: k -> k = T -T :: * -> * +T :: k -> k diff --git a/testsuite/tests/ghci/scripts/T4087.hs b/testsuite/tests/ghci/scripts/T4087.hs index b992a9bb20..8186494508 100644 --- a/testsuite/tests/ghci/scripts/T4087.hs +++ b/testsuite/tests/ghci/scripts/T4087.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE GADTs #-} module T4087 where diff --git a/testsuite/tests/ghci/scripts/T4087.stdout b/testsuite/tests/ghci/scripts/T4087.stdout index 8dafaa881d..6b0bbb51a5 100644 --- a/testsuite/tests/ghci/scripts/T4087.stdout +++ b/testsuite/tests/ghci/scripts/T4087.stdout @@ -2,4 +2,4 @@ type role Equal nominal nominal type Equal :: * -> * -> * data Equal a b where Equal :: Equal a a - -- Defined at T4087.hs:5:1 + -- Defined at T4087.hs:6:1 diff --git a/testsuite/tests/ghci/scripts/T4175.hs b/testsuite/tests/ghci/scripts/T4175.hs index ef34a4891d..7ecd8e9485 100644 --- a/testsuite/tests/ghci/scripts/T4175.hs +++ b/testsuite/tests/ghci/scripts/T4175.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ConstraintKinds #-} module T4175 where diff --git a/testsuite/tests/ghci/scripts/T4175.stdout b/testsuite/tests/ghci/scripts/T4175.stdout index 52d8a688c7..9f93304ca9 100644 --- a/testsuite/tests/ghci/scripts/T4175.stdout +++ b/testsuite/tests/ghci/scripts/T4175.stdout @@ -1,31 +1,31 @@ type A :: * -> * -> * type family A a b - -- Defined at T4175.hs:7:1 -type instance A (Maybe a) a = a -- Defined at T4175.hs:9:15 -type instance A Int Int = () -- Defined at T4175.hs:8:15 -type instance A (B a) b = () -- Defined at T4175.hs:10:15 + -- Defined at T4175.hs:8:1 +type instance A (Maybe a) a = a -- Defined at T4175.hs:10:15 +type instance A Int Int = () -- Defined at T4175.hs:9:15 +type instance A (B a) b = () -- Defined at T4175.hs:11:15 type B :: * -> * data family B a - -- Defined at T4175.hs:12:1 -instance [safe] G B -- Defined at T4175.hs:34:10 -type instance A (B a) b = () -- Defined at T4175.hs:10:15 -data instance B () = MkB -- Defined at T4175.hs:13:15 + -- Defined at T4175.hs:13:1 +instance [safe] G B -- Defined at T4175.hs:35:10 +type instance A (B a) b = () -- Defined at T4175.hs:11:15 +data instance B () = MkB -- Defined at T4175.hs:14:15 type C :: * -> Constraint class C a where type D :: * -> * -> * type family D a b - -- Defined at T4175.hs:16:5 -type instance D () () = Bool -- Defined at T4175.hs:22:10 -type instance D Int () = String -- Defined at T4175.hs:19:10 + -- Defined at T4175.hs:17:5 +type instance D () () = Bool -- Defined at T4175.hs:23:10 +type instance D Int () = String -- Defined at T4175.hs:20:10 type E :: * -> * type family E a where E () = Bool E Int = String - -- Defined at T4175.hs:24:1 + -- Defined at T4175.hs:25:1 type () :: * data () = () -- Defined in ‘GHC.Tuple’ -instance [safe] C () -- Defined at T4175.hs:21:10 +instance [safe] C () -- Defined at T4175.hs:22:10 instance Eq () -- Defined in ‘GHC.Classes’ instance Monoid () -- Defined in ‘GHC.Base’ instance Ord () -- Defined in ‘GHC.Classes’ @@ -34,9 +34,9 @@ instance Enum () -- Defined in ‘GHC.Enum’ instance Show () -- Defined in ‘GHC.Show’ instance Read () -- Defined in ‘GHC.Read’ instance Bounded () -- Defined in ‘GHC.Enum’ -type instance D () () = Bool -- Defined at T4175.hs:22:10 -type instance D Int () = String -- Defined at T4175.hs:19:10 -data instance B () = MkB -- Defined at T4175.hs:13:15 +type instance D () () = Bool -- Defined at T4175.hs:23:10 +type instance D Int () = String -- Defined at T4175.hs:20:10 +data instance B () = MkB -- Defined at T4175.hs:14:15 type Maybe :: * -> * data Maybe a = Nothing | Just a -- Defined in ‘GHC.Maybe’ @@ -53,11 +53,11 @@ instance MonadFail Maybe -- Defined in ‘Control.Monad.Fail’ instance Read a => Read (Maybe a) -- Defined in ‘GHC.Read’ instance Foldable Maybe -- Defined in ‘Data.Foldable’ instance Traversable Maybe -- Defined in ‘Data.Traversable’ -type instance A (Maybe a) a = a -- Defined at T4175.hs:9:15 +type instance A (Maybe a) a = a -- Defined at T4175.hs:10:15 type Int :: * data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in ‘GHC.Types’ -instance [safe] C Int -- Defined at T4175.hs:18:10 +instance [safe] C Int -- Defined at T4175.hs:19:10 instance Eq Int -- Defined in ‘GHC.Classes’ instance Ord Int -- Defined in ‘GHC.Classes’ instance Enum Int -- Defined in ‘GHC.Enum’ @@ -67,9 +67,9 @@ instance Show Int -- Defined in ‘GHC.Show’ instance Read Int -- Defined in ‘GHC.Read’ instance Bounded Int -- Defined in ‘GHC.Enum’ instance Integral Int -- Defined in ‘GHC.Real’ -type instance D Int () = String -- Defined at T4175.hs:19:10 -type instance A Int Int = () -- Defined at T4175.hs:8:15 +type instance D Int () = String -- Defined at T4175.hs:20:10 +type instance A Int Int = () -- Defined at T4175.hs:9:15 type Z :: * -> Constraint class Z a - -- Defined at T4175.hs:28:1 -instance [safe] F (Z a) -- Defined at T4175.hs:31:10 + -- Defined at T4175.hs:29:1 +instance [safe] F (Z a) -- Defined at T4175.hs:32:10 diff --git a/testsuite/tests/ghci/scripts/T5417.hs b/testsuite/tests/ghci/scripts/T5417.hs index e86c076637..bf5e87a80d 100644 --- a/testsuite/tests/ghci/scripts/T5417.hs +++ b/testsuite/tests/ghci/scripts/T5417.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies #-} module T5417 where import qualified T5417a as C diff --git a/testsuite/tests/ghci/scripts/T5417.script b/testsuite/tests/ghci/scripts/T5417.script index d163d7df04..c27a6f6c6c 100644 --- a/testsuite/tests/ghci/scripts/T5417.script +++ b/testsuite/tests/ghci/scripts/T5417.script @@ -1,3 +1,4 @@ +:set -XHaskell2010 :l T5417 :browse :info C.F diff --git a/testsuite/tests/ghci/scripts/T5417.stdout b/testsuite/tests/ghci/scripts/T5417.stdout index 163a9236de..5227ac6651 100644 --- a/testsuite/tests/ghci/scripts/T5417.stdout +++ b/testsuite/tests/ghci/scripts/T5417.stdout @@ -12,4 +12,4 @@ class C.C1 a where type C.F :: * -> * data family C.F a -- Defined at T5417a.hs:7:5 -data instance C.F (B1 a) = B2 a -- Defined at T5417.hs:8:10 +data instance C.F (B1 a) = B2 a -- Defined at T5417.hs:9:10 diff --git a/testsuite/tests/ghci/scripts/T5820.hs b/testsuite/tests/ghci/scripts/T5820.hs index 99d36e5fc2..de6598f805 100644 --- a/testsuite/tests/ghci/scripts/T5820.hs +++ b/testsuite/tests/ghci/scripts/T5820.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module T5820 where data Foo = Foo instance Eq Foo diff --git a/testsuite/tests/ghci/scripts/T5820.stderr b/testsuite/tests/ghci/scripts/T5820.stderr index 3f46fdbc47..370aa6d95c 100644 --- a/testsuite/tests/ghci/scripts/T5820.stderr +++ b/testsuite/tests/ghci/scripts/T5820.stderr @@ -1,5 +1,5 @@ -T5820.hs:3:10: warning: [-Wmissing-methods (in -Wdefault)] +T5820.hs:4:10: warning: [-Wmissing-methods (in -Wdefault)] • No explicit implementation for either ‘==’ or ‘/=’ • In the instance declaration for ‘Eq Foo’ diff --git a/testsuite/tests/ghci/scripts/T5820.stdout b/testsuite/tests/ghci/scripts/T5820.stdout index faa5f6fc76..4940da3f2d 100644 --- a/testsuite/tests/ghci/scripts/T5820.stdout +++ b/testsuite/tests/ghci/scripts/T5820.stdout @@ -1,8 +1,8 @@ type Foo :: * data Foo = Foo - -- Defined at T5820.hs:2:1 -instance [safe] Eq Foo -- Defined at T5820.hs:3:10 + -- Defined at T5820.hs:3:1 +instance [safe] Eq Foo -- Defined at T5820.hs:4:10 type Foo :: * data Foo = Foo - -- Defined at T5820.hs:2:1 -instance [safe] Eq Foo -- Defined at T5820.hs:3:10 + -- Defined at T5820.hs:3:1 +instance [safe] Eq Foo -- Defined at T5820.hs:4:10 diff --git a/testsuite/tests/ghci/scripts/T7939.hs b/testsuite/tests/ghci/scripts/T7939.hs index 04a1f1a623..493c6538d1 100644 --- a/testsuite/tests/ghci/scripts/T7939.hs +++ b/testsuite/tests/ghci/scripts/T7939.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies, PolyKinds, DataKinds, TypeOperators #-} module T7939 where import Data.Kind (Type) diff --git a/testsuite/tests/ghci/scripts/T7939.stdout b/testsuite/tests/ghci/scripts/T7939.stdout index 93739d04dc..0d9e4d363c 100644 --- a/testsuite/tests/ghci/scripts/T7939.stdout +++ b/testsuite/tests/ghci/scripts/T7939.stdout @@ -2,32 +2,32 @@ type Foo :: forall {k}. k -> Constraint class Foo a where type Bar :: forall {k}. k -> * -> * type family Bar a b - -- Defined at T7939.hs:6:4 + -- Defined at T7939.hs:7:4 Bar :: k -> * -> * type F :: * -> * type family F a - -- Defined at T7939.hs:8:1 -type instance F Int = Bool -- Defined at T7939.hs:9:15 + -- Defined at T7939.hs:9:1 +type instance F Int = Bool -- Defined at T7939.hs:10:15 F :: * -> * type G :: * -> * type family G a where G Int = Bool - -- Defined at T7939.hs:11:1 + -- Defined at T7939.hs:12:1 G :: * -> * type H :: Bool -> Bool type family H a where H 'False = 'True - -- Defined at T7939.hs:14:1 + -- Defined at T7939.hs:15:1 H :: Bool -> Bool type J :: forall {k}. [k] -> Bool type family J a where J '[] = 'False forall k (h :: k) (t :: [k]). J (h : t) = 'True - -- Defined at T7939.hs:17:1 + -- Defined at T7939.hs:18:1 J :: [k] -> Bool type K :: forall {a}. [a] -> Maybe a type family K a1 where K '[] = 'Nothing forall a (h :: a) (t :: [a]). K (h : t) = 'Just h - -- Defined at T7939.hs:21:1 + -- Defined at T7939.hs:22:1 K :: [a] -> Maybe a diff --git a/testsuite/tests/ghci/scripts/T9293.hs b/testsuite/tests/ghci/scripts/T9293.hs index f7329c97e5..3a5d3d8986 100644 --- a/testsuite/tests/ghci/scripts/T9293.hs +++ b/testsuite/tests/ghci/scripts/T9293.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Test where data T a where C :: T Int diff --git a/testsuite/tests/ghci/scripts/T9293.script b/testsuite/tests/ghci/scripts/T9293.script index c2fbf46cd7..c4719e26e4 100644 --- a/testsuite/tests/ghci/scripts/T9293.script +++ b/testsuite/tests/ghci/scripts/T9293.script @@ -1,3 +1,4 @@ +:set -XHaskell2010 :set putStrLn "Should fail, GADTs is not enabled" diff --git a/testsuite/tests/ghci/scripts/T9293.stderr b/testsuite/tests/ghci/scripts/T9293.stderr index 4a72589688..8f46cee2d1 100644 --- a/testsuite/tests/ghci/scripts/T9293.stderr +++ b/testsuite/tests/ghci/scripts/T9293.stderr @@ -1,17 +1,17 @@ -<interactive>:4:1: error: +<interactive>:5:1: error: • Illegal generalised algebraic data declaration for ‘T’ (Enable the GADTs extension to allow this) • In the data declaration for ‘T’ -ghci057.hs:3:3: error: +ghci057.hs:4:3: error: • Data constructor ‘C’ has existential type variables, a context, or a specialised result type C :: T Int (Enable ExistentialQuantification or GADTs to allow this) • In the definition of data constructor ‘C’ In the data type declaration for ‘T’ -ghci057.hs:3:3: error: +ghci057.hs:4:3: error: • Data constructor ‘C’ has existential type variables, a context, or a specialised result type C :: T Int (Enable ExistentialQuantification or GADTs to allow this) diff --git a/testsuite/tests/ghci/scripts/T9293.stdout b/testsuite/tests/ghci/scripts/T9293.stdout index 78c1ec819d..15c36fb34e 100644 --- a/testsuite/tests/ghci/scripts/T9293.stdout +++ b/testsuite/tests/ghci/scripts/T9293.stdout @@ -1,8 +1,6 @@ options currently set: none. base language is: Haskell2010 with the following modifiers: - -XNoDatatypeContexts - -XNondecreasingIndentation GHCi-specific dynamic flag settings: other dynamic, non-language, flag settings: -fno-diagnostics-show-caret @@ -20,11 +18,9 @@ Should fail, GADTs is not enabled options currently set: none. base language is: Haskell2010 with the following modifiers: - -XNoDatatypeContexts -XGADTSyntax -XGADTs -XMonoLocalBinds - -XNondecreasingIndentation GHCi-specific dynamic flag settings: other dynamic, non-language, flag settings: -fno-diagnostics-show-caret @@ -42,10 +38,8 @@ Should work, GADTs is in force from :set options currently set: none. base language is: Haskell2010 with the following modifiers: - -XNoDatatypeContexts -XGADTSyntax -XMonoLocalBinds - -XNondecreasingIndentation GHCi-specific dynamic flag settings: other dynamic, non-language, flag settings: -fno-diagnostics-show-caret @@ -62,13 +56,11 @@ warning settings: Should fail, GADTs is now disabled base language is: Haskell2010 with the following modifiers: - -XNoDatatypeContexts -XExtendedDefaultRules -XGADTSyntax -XGADTs -XMonoLocalBinds -XNoMonomorphismRestriction - -XNondecreasingIndentation GHCi-specific dynamic flag settings: other dynamic, non-language, flag settings: -fno-diagnostics-show-caret diff --git a/testsuite/tests/ghci/scripts/ghci019.hs b/testsuite/tests/ghci/scripts/ghci019.hs index 14cf726c86..94d5664f68 100644 --- a/testsuite/tests/ghci/scripts/ghci019.hs +++ b/testsuite/tests/ghci/scripts/ghci019.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} -- #1581 -- Even though Eq is not in scope unqualified, we want to -- see the Eq instance of Foo when we say :i Foo diff --git a/testsuite/tests/ghci/scripts/ghci019.stderr b/testsuite/tests/ghci/scripts/ghci019.stderr index 0d3378ec8e..51d5a0123f 100644 --- a/testsuite/tests/ghci/scripts/ghci019.stderr +++ b/testsuite/tests/ghci/scripts/ghci019.stderr @@ -1,5 +1,5 @@ -ghci019.hs:9:10: warning: [-Wmissing-methods (in -Wdefault)] +ghci019.hs:10:10: warning: [-Wmissing-methods (in -Wdefault)] • No explicit implementation for either ‘Prelude.==’ or ‘Prelude./=’ • In the instance declaration for ‘Prelude.Eq Foo’ diff --git a/testsuite/tests/ghci/scripts/ghci019.stdout b/testsuite/tests/ghci/scripts/ghci019.stdout index 0a9fefb77b..ddcbafebb9 100644 --- a/testsuite/tests/ghci/scripts/ghci019.stdout +++ b/testsuite/tests/ghci/scripts/ghci019.stdout @@ -1,4 +1,4 @@ type Foo :: * data Foo = Foo - -- Defined at ghci019.hs:8:1 -instance [safe] Prelude.Eq Foo -- Defined at ghci019.hs:9:10 + -- Defined at ghci019.hs:9:1 +instance [safe] Prelude.Eq Foo -- Defined at ghci019.hs:10:10 diff --git a/testsuite/tests/ghci/scripts/ghci024.stdout b/testsuite/tests/ghci/scripts/ghci024.stdout index bd8ee9361e..7cf36ac041 100644 --- a/testsuite/tests/ghci/scripts/ghci024.stdout +++ b/testsuite/tests/ghci/scripts/ghci024.stdout @@ -1,9 +1,7 @@ ~~~~~~~~~~ Testing :set options currently set: none. -base language is: Haskell2010 +base language is: GHC2021 with the following modifiers: - -XNoDatatypeContexts - -XNondecreasingIndentation GHCi-specific dynamic flag settings: other dynamic, non-language, flag settings: -fno-diagnostics-show-caret @@ -19,7 +17,7 @@ warning settings: -Wcompat-unqualified-imports ~~~~~~~~~~ Testing :set -a options currently set: none. -base language is: Haskell2010 +base language is: GHC2021 all active language options: GHCi-specific dynamic flag settings: -fno-print-explicit-foralls @@ -27,16 +25,12 @@ other dynamic, non-language, flag settings: warning settings: -Wno-implicit-prelude ~~~~~~~~~~ Testing :show languages -base language is: Haskell2010 +base language is: GHC2021 with the following modifiers: - -XNoDatatypeContexts - -XNondecreasingIndentation ~~~~~~~~~~ Testing :show languages, with -XMagicHash -base language is: Haskell2010 +base language is: GHC2021 with the following modifiers: - -XNoDatatypeContexts -XMagicHash - -XNondecreasingIndentation ~~~~~~~~~~ Testing :show packages active package flags: none ~~~~~~~~~~ Testing :show packages, including the ghc package diff --git a/testsuite/tests/ghci/scripts/ghci025.hs b/testsuite/tests/ghci/scripts/ghci025.hs index b556509aa6..abb6b3d490 100644 --- a/testsuite/tests/ghci/scripts/ghci025.hs +++ b/testsuite/tests/ghci/scripts/ghci025.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE RankNTypes, MultiParamTypeClasses #-} {-# LANGUAGE AllowAmbiguousTypes #-} -- c3 is ambiguous! diff --git a/testsuite/tests/ghci/scripts/ghci057.hs b/testsuite/tests/ghci/scripts/ghci057.hs index 2a6b836d80..23bad888bc 100644 --- a/testsuite/tests/ghci/scripts/ghci057.hs +++ b/testsuite/tests/ghci/scripts/ghci057.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module Test where data T a where C :: T Int diff --git a/testsuite/tests/ghci/scripts/ghci057.script b/testsuite/tests/ghci/scripts/ghci057.script index 547fce52d7..db77b80cb1 100644 --- a/testsuite/tests/ghci/scripts/ghci057.script +++ b/testsuite/tests/ghci/scripts/ghci057.script @@ -1,3 +1,4 @@ +:set -XHaskell2010 :set putStrLn "Should fail, GADTs is not enabled" diff --git a/testsuite/tests/ghci/scripts/ghci057.stderr b/testsuite/tests/ghci/scripts/ghci057.stderr index 4a72589688..8f46cee2d1 100644 --- a/testsuite/tests/ghci/scripts/ghci057.stderr +++ b/testsuite/tests/ghci/scripts/ghci057.stderr @@ -1,17 +1,17 @@ -<interactive>:4:1: error: +<interactive>:5:1: error: • Illegal generalised algebraic data declaration for ‘T’ (Enable the GADTs extension to allow this) • In the data declaration for ‘T’ -ghci057.hs:3:3: error: +ghci057.hs:4:3: error: • Data constructor ‘C’ has existential type variables, a context, or a specialised result type C :: T Int (Enable ExistentialQuantification or GADTs to allow this) • In the definition of data constructor ‘C’ In the data type declaration for ‘T’ -ghci057.hs:3:3: error: +ghci057.hs:4:3: error: • Data constructor ‘C’ has existential type variables, a context, or a specialised result type C :: T Int (Enable ExistentialQuantification or GADTs to allow this) diff --git a/testsuite/tests/ghci/scripts/ghci057.stdout b/testsuite/tests/ghci/scripts/ghci057.stdout index 78c1ec819d..15c36fb34e 100644 --- a/testsuite/tests/ghci/scripts/ghci057.stdout +++ b/testsuite/tests/ghci/scripts/ghci057.stdout @@ -1,8 +1,6 @@ options currently set: none. base language is: Haskell2010 with the following modifiers: - -XNoDatatypeContexts - -XNondecreasingIndentation GHCi-specific dynamic flag settings: other dynamic, non-language, flag settings: -fno-diagnostics-show-caret @@ -20,11 +18,9 @@ Should fail, GADTs is not enabled options currently set: none. base language is: Haskell2010 with the following modifiers: - -XNoDatatypeContexts -XGADTSyntax -XGADTs -XMonoLocalBinds - -XNondecreasingIndentation GHCi-specific dynamic flag settings: other dynamic, non-language, flag settings: -fno-diagnostics-show-caret @@ -42,10 +38,8 @@ Should work, GADTs is in force from :set options currently set: none. base language is: Haskell2010 with the following modifiers: - -XNoDatatypeContexts -XGADTSyntax -XMonoLocalBinds - -XNondecreasingIndentation GHCi-specific dynamic flag settings: other dynamic, non-language, flag settings: -fno-diagnostics-show-caret @@ -62,13 +56,11 @@ warning settings: Should fail, GADTs is now disabled base language is: Haskell2010 with the following modifiers: - -XNoDatatypeContexts -XExtendedDefaultRules -XGADTSyntax -XGADTs -XMonoLocalBinds -XNoMonomorphismRestriction - -XNondecreasingIndentation GHCi-specific dynamic flag settings: other dynamic, non-language, flag settings: -fno-diagnostics-show-caret diff --git a/testsuite/tests/ghci/scripts/ghci064.hs b/testsuite/tests/ghci/scripts/ghci064.hs index 152836d270..c2c2e32b69 100644 --- a/testsuite/tests/ghci/scripts/ghci064.hs +++ b/testsuite/tests/ghci/scripts/ghci064.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE FlexibleInstances, TypeFamilies #-} import Data.Kind (Type) diff --git a/testsuite/tests/ghci/scripts/ghci064.stdout b/testsuite/tests/ghci/scripts/ghci064.stdout index d527dde6c4..0fa911e351 100644 --- a/testsuite/tests/ghci/scripts/ghci064.stdout +++ b/testsuite/tests/ghci/scripts/ghci064.stdout @@ -25,12 +25,12 @@ instance Show w => Show [w] -- Defined in ‘GHC.Show’ instance Read w => Read [w] -- Defined in ‘GHC.Read’ instance GHC.Generics.Generic [w] -- Defined in ‘GHC.Generics’ instance [safe] MyShow w => MyShow [w] - -- Defined at ghci064.hs:7:10 + -- Defined at ghci064.hs:8:10 instance Monoid [T] -- Defined in ‘GHC.Base’ instance Semigroup [T] -- Defined in ‘GHC.Base’ instance GHC.Generics.Generic [T] -- Defined in ‘GHC.Generics’ -instance [safe] MyShow [T] -- Defined at ghci064.hs:7:10 -instance [safe] MyShow [T] -- Defined at ghci064.hs:15:10 +instance [safe] MyShow [T] -- Defined at ghci064.hs:8:10 +instance [safe] MyShow [T] -- Defined at ghci064.hs:16:10 instance Eq Bool -- Defined in ‘GHC.Classes’ instance Ord Bool -- Defined in ‘GHC.Classes’ instance Enum Bool -- Defined in ‘GHC.Enum’ diff --git a/testsuite/tests/ghci/scripts/ghci065.stdout b/testsuite/tests/ghci/scripts/ghci065.stdout index 4c6f40c72c..39b990b04c 100644 --- a/testsuite/tests/ghci/scripts/ghci065.stdout +++ b/testsuite/tests/ghci/scripts/ghci065.stdout @@ -26,7 +26,7 @@ func3 :: Int -> Int -> Int Here's multiple line comment for func3. PatSyn :: Int -- Pattern synonym defined at ghci065.hs:54:1 This is the haddock comment of a pattern synonym -TyCl :: * -> Constraint -- Class defined at ghci065.hs:57:1 +TyCl :: k -> Constraint -- Class defined at ghci065.hs:57:1 This is the haddock comment of a type class TyFam :: * -> * -- Type constructor defined at ghci065.hs:60:1 This is the haddock comment of a type family diff --git a/testsuite/tests/ghci/should_run/T10857a.stdout b/testsuite/tests/ghci/should_run/T10857a.stdout index a37151f062..51f30615f1 100644 --- a/testsuite/tests/ghci/should_run/T10857a.stdout +++ b/testsuite/tests/ghci/should_run/T10857a.stdout @@ -1,6 +1,4 @@ -base language is: Haskell2010 +base language is: GHC2021 with the following modifiers: - -XNoDatatypeContexts -XExtendedDefaultRules -XNoMonomorphismRestriction - -XNondecreasingIndentation diff --git a/testsuite/tests/ghci/should_run/T10857b.stdout b/testsuite/tests/ghci/should_run/T10857b.stdout index 2619fae00d..bcc6fdd383 100644 --- a/testsuite/tests/ghci/should_run/T10857b.stdout +++ b/testsuite/tests/ghci/should_run/T10857b.stdout @@ -1,4 +1,2 @@ -base language is: Haskell2010 +base language is: GHC2021 with the following modifiers: - -XNoDatatypeContexts - -XNondecreasingIndentation diff --git a/testsuite/tests/ghci/should_run/T12525.stdout b/testsuite/tests/ghci/should_run/T12525.stdout index a00ffea4e3..ef48679f94 100644 --- a/testsuite/tests/ghci/should_run/T12525.stdout +++ b/testsuite/tests/ghci/should_run/T12525.stdout @@ -1,4 +1,4 @@ x :: () = () y :: () = () -type Foo :: * -> Constraint +type Foo :: forall {k}. k -> Constraint class Foo a |