summaryrefslogtreecommitdiff
path: root/testsuite/tests/ghci
diff options
context:
space:
mode:
authorBen Gamari <bgamari.foss@gmail.com>2015-12-15 16:08:52 +0100
committerBen Gamari <ben@smart-cactus.org>2015-12-15 20:45:59 +0100
commite2c917381ff099820b1ee30fcfa8bc0c20cf5c1f (patch)
treef9295bd3f9ab1e4d4b296960d1f046d1eb37b449 /testsuite/tests/ghci
parent947e44feebb4e979d7d476ff2aa5c7054a1c0899 (diff)
downloadhaskell-e2c917381ff099820b1ee30fcfa8bc0c20cf5c1f.tar.gz
Narrow scope of special-case for unqualified printing of names in core libraries
Commit 547c597112954353cef7157cb0a389bc4f6303eb modifies the pretty-printer to render names from a set of core packages (`base`, `ghc-prim`, `template-haskell`) as unqualified. The idea here was that many of these names typically are not in scope but are well-known by the user and therefore qualification merely introduces noise. This, however, is a very large hammer and potentially breaks any consumer who relies on parsing GHC output (hence #11208). This commit partially reverts this change, now only printing `Constraint` (which appears quite often in errors) as unqualified. Fixes #11208. Updates tests in `array` submodule. Test Plan: validate Reviewers: hvr, thomie, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1619 GHC Trac Issues: #11208
Diffstat (limited to 'testsuite/tests/ghci')
-rw-r--r--testsuite/tests/ghci/scripts/T11208.hs8
-rw-r--r--testsuite/tests/ghci/scripts/T11208.script2
-rw-r--r--testsuite/tests/ghci/scripts/T11208.stdout2
-rw-r--r--testsuite/tests/ghci/scripts/T2182ghci2.stderr18
-rw-r--r--testsuite/tests/ghci/scripts/T7873.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/T8469.stdout20
-rw-r--r--testsuite/tests/ghci/scripts/T8959.stdout8
-rw-r--r--testsuite/tests/ghci/scripts/T9181.stdout105
-rw-r--r--testsuite/tests/ghci/scripts/T9881.stdout63
-rw-r--r--testsuite/tests/ghci/scripts/ghci008.stdout76
-rw-r--r--testsuite/tests/ghci/scripts/ghci013.stdout3
-rw-r--r--testsuite/tests/ghci/scripts/ghci019.stderr10
-rw-r--r--testsuite/tests/ghci/scripts/ghci019.stdout2
-rw-r--r--testsuite/tests/ghci/scripts/ghci023.stdout16
-rw-r--r--testsuite/tests/ghci/scripts/ghci025.stdout236
-rw-r--r--testsuite/tests/ghci/scripts/ghci027.stdout14
-rw-r--r--testsuite/tests/ghci/scripts/ghci046.stdout4
-rw-r--r--testsuite/tests/ghci/scripts/ghci055.stdout2
18 files changed, 319 insertions, 274 deletions
diff --git a/testsuite/tests/ghci/scripts/T11208.hs b/testsuite/tests/ghci/scripts/T11208.hs
new file mode 100644
index 0000000000..b6ddd167d5
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T11208.hs
@@ -0,0 +1,8 @@
+module T11208 where
+
+import qualified Prelude as P
+
+f n = n P.+ 1
+
+g h (P.Just x) = P.Just (h x)
+g _ P.Nothing = P.Nothing
diff --git a/testsuite/tests/ghci/scripts/T11208.script b/testsuite/tests/ghci/scripts/T11208.script
new file mode 100644
index 0000000000..e177c59e0a
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T11208.script
@@ -0,0 +1,2 @@
+:load T11208
+:browse T11208 \ No newline at end of file
diff --git a/testsuite/tests/ghci/scripts/T11208.stdout b/testsuite/tests/ghci/scripts/T11208.stdout
new file mode 100644
index 0000000000..a00f202e41
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T11208.stdout
@@ -0,0 +1,2 @@
+f :: P.Num a => a -> a
+g :: (r -> a) -> P.Maybe r -> P.Maybe a
diff --git a/testsuite/tests/ghci/scripts/T2182ghci2.stderr b/testsuite/tests/ghci/scripts/T2182ghci2.stderr
index fde88e3c8a..5ebe106bfa 100644
--- a/testsuite/tests/ghci/scripts/T2182ghci2.stderr
+++ b/testsuite/tests/ghci/scripts/T2182ghci2.stderr
@@ -1,8 +1,10 @@
-
-<interactive>:7:1:
- No instance for (Show Float) arising from a use of ‘print’
- In a stmt of an interactive GHCi command: print it
-
-<interactive>:15:1:
- No instance for (Show Float) arising from a use of ‘print’
- In a stmt of an interactive GHCi command: print it
+
+<interactive>:7:1: error:
+ • No instance for (GHC.Show.Show Float)
+ arising from a use of ‘System.IO.print’
+ • In a stmt of an interactive GHCi command: System.IO.print it
+
+<interactive>:15:1: error:
+ • No instance for (GHC.Show.Show Float)
+ arising from a use of ‘System.IO.print’
+ • In a stmt of an interactive GHCi command: System.IO.print it
diff --git a/testsuite/tests/ghci/scripts/T7873.stdout b/testsuite/tests/ghci/scripts/T7873.stdout
index b7415d6222..3f15c0d333 100644
--- a/testsuite/tests/ghci/scripts/T7873.stdout
+++ b/testsuite/tests/ghci/scripts/T7873.stdout
@@ -1,4 +1,6 @@
-data D2 = MkD2 (forall (p :: Any -> *) (a :: Any). p a -> Int)
+data D2
+ = MkD2 (forall (p :: GHC.Prim.Any -> *) (a :: GHC.Prim.Any).
+ p a -> Int)
-- Defined at <interactive>:3:1
data D3 = MkD3 (forall k (p :: k -> *) (a :: k). p a -> Int)
-- Defined at <interactive>:4:1
diff --git a/testsuite/tests/ghci/scripts/T8469.stdout b/testsuite/tests/ghci/scripts/T8469.stdout
index c052868ebb..cd7966ee66 100644
--- a/testsuite/tests/ghci/scripts/T8469.stdout
+++ b/testsuite/tests/ghci/scripts/T8469.stdout
@@ -1,10 +1,10 @@
-data Int = I# Int# -- Defined in ‘GHC.Types’
-instance Bounded Int -- Defined in ‘GHC.Enum’
-instance Enum Int -- Defined in ‘GHC.Enum’
-instance Eq Int -- Defined in ‘GHC.Classes’
-instance Integral Int -- Defined in ‘GHC.Real’
-instance Num Int -- Defined in ‘GHC.Num’
-instance Ord Int -- Defined in ‘GHC.Classes’
-instance Read Int -- Defined in ‘GHC.Read’
-instance Real Int -- Defined in ‘GHC.Real’
-instance Show Int -- Defined in ‘GHC.Show’
+data Int = GHC.Types.I# GHC.Prim.Int# -- Defined in ‘GHC.Types’
+instance Bounded Int -- Defined in ‘GHC.Enum’
+instance Enum Int -- Defined in ‘GHC.Enum’
+instance Eq Int -- Defined in ‘GHC.Classes’
+instance Integral Int -- Defined in ‘GHC.Real’
+instance Num Int -- Defined in ‘GHC.Num’
+instance Ord Int -- Defined in ‘GHC.Classes’
+instance Read Int -- Defined in ‘GHC.Read’
+instance Real Int -- Defined in ‘GHC.Real’
+instance Show Int -- Defined in ‘GHC.Show’
diff --git a/testsuite/tests/ghci/scripts/T8959.stdout b/testsuite/tests/ghci/scripts/T8959.stdout
index 77d1b7d63b..02b5f828c2 100644
--- a/testsuite/tests/ghci/scripts/T8959.stdout
+++ b/testsuite/tests/ghci/scripts/T8959.stdout
@@ -1,9 +1,11 @@
lookup :: Eq a => a -> [(a, b)] -> Maybe b
undefined :: (forall a. a -> a) -> a
- :: (?callStack::CallStack) => (forall a1. a1 -> a1) -> a
+ :: (?callStack::GHC.Stack.Types.CallStack) =>
+ (forall a1. a1 -> a1) -> a
lookup ∷ Eq a ⇒ a → [(a, b)] → Maybe b
undefined :: (forall a. a -> a) -> a
- ∷ (?callStack::CallStack) ⇒ (∀ a1. a1 → a1) → a
+ ∷ (?callStack::GHC.Stack.Types.CallStack) ⇒ (∀ a1. a1 → a1) → a
lookup :: Eq a => a -> [(a, b)] -> Maybe b
undefined :: (forall a. a -> a) -> a
- :: (?callStack::CallStack) => (forall a1. a1 -> a1) -> a
+ :: (?callStack::GHC.Stack.Types.CallStack) =>
+ (forall a1. a1 -> a1) -> a
diff --git a/testsuite/tests/ghci/scripts/T9181.stdout b/testsuite/tests/ghci/scripts/T9181.stdout
index 0e9913966f..3482d54ba4 100644
--- a/testsuite/tests/ghci/scripts/T9181.stdout
+++ b/testsuite/tests/ghci/scripts/T9181.stdout
@@ -1,45 +1,64 @@
-type family (*) (a :: Nat) (b :: Nat)
- Kind: Nat -> Nat -> Nat
-type family (+) (a :: Nat) (b :: Nat)
- Kind: Nat -> Nat -> Nat
-type family (-) (a :: Nat) (b :: Nat)
- Kind: Nat -> Nat -> Nat
-type (<=) (x :: Nat) (y :: Nat) = (x <=? y) ~ 'True
-type family (<=?) (a :: Nat) (b :: Nat)
- Kind: Nat -> Nat -> Bool
-type family CmpNat (a :: Nat) (b :: Nat)
- Kind: Nat -> Nat -> Ordering
-type family CmpSymbol (a :: Symbol) (b :: Symbol)
- Kind: Symbol -> Symbol -> Ordering
-data ErrorMessage where
- Text :: Symbol -> ErrorMessage
- ShowType :: t -> ErrorMessage
- (:<>:) :: ErrorMessage -> ErrorMessage -> ErrorMessage
- (:$$:) :: ErrorMessage -> ErrorMessage -> ErrorMessage
-class KnownNat (n :: Nat) where
- natSing :: SNat n
+type family (GHC.TypeLits.*) (a :: GHC.Types.Nat)
+ (b :: GHC.Types.Nat)
+ Kind: GHC.Types.Nat -> GHC.Types.Nat -> GHC.Types.Nat
+type family (GHC.TypeLits.+) (a :: GHC.Types.Nat)
+ (b :: GHC.Types.Nat)
+ Kind: GHC.Types.Nat -> GHC.Types.Nat -> GHC.Types.Nat
+type family (GHC.TypeLits.-) (a :: GHC.Types.Nat)
+ (b :: GHC.Types.Nat)
+ Kind: GHC.Types.Nat -> GHC.Types.Nat -> GHC.Types.Nat
+type (GHC.TypeLits.<=) (x :: GHC.Types.Nat) (y :: GHC.Types.Nat) =
+ (x GHC.TypeLits.<=? y) ~ 'True
+type family (GHC.TypeLits.<=?) (a :: GHC.Types.Nat)
+ (b :: GHC.Types.Nat)
+ Kind: GHC.Types.Nat -> GHC.Types.Nat -> Bool
+type family GHC.TypeLits.CmpNat (a :: GHC.Types.Nat)
+ (b :: GHC.Types.Nat)
+ Kind: GHC.Types.Nat -> GHC.Types.Nat -> Ordering
+type family GHC.TypeLits.CmpSymbol (a :: GHC.Types.Symbol)
+ (b :: GHC.Types.Symbol)
+ Kind: GHC.Types.Symbol -> GHC.Types.Symbol -> Ordering
+data GHC.TypeLits.ErrorMessage where
+ GHC.TypeLits.Text :: GHC.Types.Symbol -> GHC.TypeLits.ErrorMessage
+ GHC.TypeLits.ShowType :: t -> GHC.TypeLits.ErrorMessage
+ (GHC.TypeLits.:<>:) :: GHC.TypeLits.ErrorMessage
+ -> GHC.TypeLits.ErrorMessage -> GHC.TypeLits.ErrorMessage
+ (GHC.TypeLits.:$$:) :: GHC.TypeLits.ErrorMessage
+ -> GHC.TypeLits.ErrorMessage -> GHC.TypeLits.ErrorMessage
+class GHC.TypeLits.KnownNat (n :: GHC.Types.Nat) where
+ GHC.TypeLits.natSing :: GHC.TypeLits.SNat n
{-# MINIMAL natSing #-}
-class KnownSymbol (n :: Symbol) where
- symbolSing :: SSymbol n
+class GHC.TypeLits.KnownSymbol (n :: GHC.Types.Symbol) where
+ GHC.TypeLits.symbolSing :: GHC.TypeLits.SSymbol n
{-# MINIMAL symbolSing #-}
-data SomeNat where
- SomeNat :: KnownNat n => (Proxy n) -> SomeNat
-data SomeSymbol where
- SomeSymbol :: KnownSymbol n => (Proxy n) -> SomeSymbol
-type family TypeError (a :: ErrorMessage)
- Kind: forall b1. ErrorMessage -> b1
-type family (^) (a :: Nat) (b :: Nat)
- Kind: Nat -> Nat -> Nat
-natVal :: KnownNat n => proxy n -> Integer
-natVal' :: KnownNat n => Proxy# n -> Integer
-sameNat ::
- (KnownNat a, KnownNat b) => Proxy a -> Proxy b -> Maybe (a :~: b)
-sameSymbol ::
- (KnownSymbol a, KnownSymbol b) =>
- Proxy a -> Proxy b -> Maybe (a :~: b)
-someNatVal :: Integer -> Maybe SomeNat
-someSymbolVal :: String -> SomeSymbol
-symbolVal :: KnownSymbol n => proxy n -> String
-symbolVal' :: KnownSymbol n => Proxy# n -> String
-data Nat
-data Symbol
+data GHC.TypeLits.SomeNat where
+ GHC.TypeLits.SomeNat :: GHC.TypeLits.KnownNat n =>
+ (Data.Proxy.Proxy n) -> GHC.TypeLits.SomeNat
+data GHC.TypeLits.SomeSymbol where
+ GHC.TypeLits.SomeSymbol :: GHC.TypeLits.KnownSymbol n =>
+ (Data.Proxy.Proxy n) -> GHC.TypeLits.SomeSymbol
+type family GHC.TypeLits.TypeError (a :: GHC.TypeLits.ErrorMessage)
+ Kind: forall b1. GHC.TypeLits.ErrorMessage -> b1
+type family (GHC.TypeLits.^) (a :: GHC.Types.Nat)
+ (b :: GHC.Types.Nat)
+ Kind: GHC.Types.Nat -> GHC.Types.Nat -> GHC.Types.Nat
+GHC.TypeLits.natVal ::
+ GHC.TypeLits.KnownNat n => proxy n -> Integer
+GHC.TypeLits.natVal' ::
+ GHC.TypeLits.KnownNat n => GHC.Prim.Proxy# n -> Integer
+GHC.TypeLits.sameNat ::
+ (GHC.TypeLits.KnownNat a, GHC.TypeLits.KnownNat b) =>
+ Data.Proxy.Proxy a
+ -> Data.Proxy.Proxy b -> Maybe (a Data.Type.Equality.:~: b)
+GHC.TypeLits.sameSymbol ::
+ (GHC.TypeLits.KnownSymbol a, GHC.TypeLits.KnownSymbol b) =>
+ Data.Proxy.Proxy a
+ -> Data.Proxy.Proxy b -> Maybe (a Data.Type.Equality.:~: b)
+GHC.TypeLits.someNatVal :: Integer -> Maybe GHC.TypeLits.SomeNat
+GHC.TypeLits.someSymbolVal :: String -> GHC.TypeLits.SomeSymbol
+GHC.TypeLits.symbolVal ::
+ GHC.TypeLits.KnownSymbol n => proxy n -> String
+GHC.TypeLits.symbolVal' ::
+ GHC.TypeLits.KnownSymbol n => GHC.Prim.Proxy# n -> String
+data GHC.Types.Nat
+data GHC.Types.Symbol
diff --git a/testsuite/tests/ghci/scripts/T9881.stdout b/testsuite/tests/ghci/scripts/T9881.stdout
index 1fa697f102..6866a6a79c 100644
--- a/testsuite/tests/ghci/scripts/T9881.stdout
+++ b/testsuite/tests/ghci/scripts/T9881.stdout
@@ -1,31 +1,32 @@
-data Data.ByteString.Lazy.ByteString
- = Data.ByteString.Lazy.Internal.Empty
- | Data.ByteString.Lazy.Internal.Chunk {-# UNPACK #-}Data.ByteString.ByteString
- Data.ByteString.Lazy.ByteString
- -- Defined in ‘Data.ByteString.Lazy.Internal’
-instance Eq Data.ByteString.Lazy.ByteString
- -- Defined in ‘Data.ByteString.Lazy.Internal’
-instance Ord Data.ByteString.Lazy.ByteString
- -- Defined in ‘Data.ByteString.Lazy.Internal’
-instance Read Data.ByteString.Lazy.ByteString
- -- Defined in ‘Data.ByteString.Lazy.Internal’
-instance Show Data.ByteString.Lazy.ByteString
- -- Defined in ‘Data.ByteString.Lazy.Internal’
-instance Monoid Data.ByteString.Lazy.ByteString
- -- Defined in ‘Data.ByteString.Lazy.Internal’
-
-data Data.ByteString.ByteString
- = Data.ByteString.Internal.PS {-# UNPACK #-}(ForeignPtr Word8)
- {-# UNPACK #-}Int
- {-# UNPACK #-}Int
- -- Defined in ‘Data.ByteString.Internal’
-instance Eq Data.ByteString.ByteString
- -- Defined in ‘Data.ByteString.Internal’
-instance Ord Data.ByteString.ByteString
- -- Defined in ‘Data.ByteString.Internal’
-instance Read Data.ByteString.ByteString
- -- Defined in ‘Data.ByteString.Internal’
-instance Show Data.ByteString.ByteString
- -- Defined in ‘Data.ByteString.Internal’
-instance Monoid Data.ByteString.ByteString
- -- Defined in ‘Data.ByteString.Internal’
+data Data.ByteString.Lazy.ByteString
+ = Data.ByteString.Lazy.Internal.Empty
+ | Data.ByteString.Lazy.Internal.Chunk {-# UNPACK #-}Data.ByteString.ByteString
+ Data.ByteString.Lazy.ByteString
+ -- Defined in ‘Data.ByteString.Lazy.Internal’
+instance Eq Data.ByteString.Lazy.ByteString
+ -- Defined in ‘Data.ByteString.Lazy.Internal’
+instance Ord Data.ByteString.Lazy.ByteString
+ -- Defined in ‘Data.ByteString.Lazy.Internal’
+instance Read Data.ByteString.Lazy.ByteString
+ -- Defined in ‘Data.ByteString.Lazy.Internal’
+instance Show Data.ByteString.Lazy.ByteString
+ -- Defined in ‘Data.ByteString.Lazy.Internal’
+instance Monoid Data.ByteString.Lazy.ByteString
+ -- Defined in ‘Data.ByteString.Lazy.Internal’
+
+data Data.ByteString.ByteString
+ = Data.ByteString.Internal.PS {-# UNPACK #-}(GHC.ForeignPtr.ForeignPtr
+ GHC.Word.Word8)
+ {-# UNPACK #-}Int
+ {-# UNPACK #-}Int
+ -- Defined in ‘Data.ByteString.Internal’
+instance Eq Data.ByteString.ByteString
+ -- Defined in ‘Data.ByteString.Internal’
+instance Ord Data.ByteString.ByteString
+ -- Defined in ‘Data.ByteString.Internal’
+instance Read Data.ByteString.ByteString
+ -- Defined in ‘Data.ByteString.Internal’
+instance Show Data.ByteString.ByteString
+ -- Defined in ‘Data.ByteString.Internal’
+instance Monoid Data.ByteString.ByteString
+ -- Defined in ‘Data.ByteString.Internal’
diff --git a/testsuite/tests/ghci/scripts/ghci008.stdout b/testsuite/tests/ghci/scripts/ghci008.stdout
index 20c7f0dcad..4cf7448e2b 100644
--- a/testsuite/tests/ghci/scripts/ghci008.stdout
+++ b/testsuite/tests/ghci/scripts/ghci008.stdout
@@ -1,37 +1,39 @@
-class Num a where
- (+) :: a -> a -> a
- ...
- -- Defined in ‘GHC.Num’
-infixl 6 +
-class Num a where
- (+) :: a -> a -> a
- ...
- -- Defined in ‘GHC.Num’
-infixl 6 +
-data Complex a = !a :+ !a -- Defined in ‘Data.Complex’
-infix 6 :+
-data Complex a = !a :+ !a -- Defined in ‘Data.Complex’
-infix 6 :+
-class (RealFrac a, Floating a) => RealFloat a where
- floatRadix :: a -> Integer
- floatDigits :: a -> Int
- floatRange :: a -> (Int, Int)
- decodeFloat :: a -> (Integer, Int)
- encodeFloat :: Integer -> Int -> a
- exponent :: a -> Int
- significand :: a -> a
- scaleFloat :: Int -> a -> a
- isNaN :: a -> Bool
- isInfinite :: a -> Bool
- isDenormalized :: a -> Bool
- isNegativeZero :: a -> Bool
- isIEEE :: a -> Bool
- atan2 :: a -> a -> a
- {-# MINIMAL floatRadix, floatDigits, floatRange, decodeFloat,
- encodeFloat, isNaN, isInfinite, isDenormalized, isNegativeZero,
- isIEEE #-}
- -- Defined in ‘GHC.Float’
-instance RealFloat Float -- Defined in ‘GHC.Float’
-instance RealFloat Double -- Defined in ‘GHC.Float’
-isPrefixOf :: Eq a => [a] -> [a] -> Bool
- -- Defined in ‘base-4.9.0.0:Data.OldList’
+class Num a where
+ (+) :: a -> a -> a
+ ...
+ -- Defined in ‘GHC.Num’
+infixl 6 +
+class Num a where
+ (+) :: a -> a -> a
+ ...
+ -- Defined in ‘GHC.Num’
+infixl 6 +
+data Data.Complex.Complex a = !a Data.Complex.:+ !a
+ -- Defined in ‘Data.Complex’
+infix 6 Data.Complex.:+
+data Data.Complex.Complex a = !a Data.Complex.:+ !a
+ -- Defined in ‘Data.Complex’
+infix 6 Data.Complex.:+
+class (RealFrac a, Floating a) => RealFloat a where
+ floatRadix :: a -> Integer
+ floatDigits :: a -> Int
+ floatRange :: a -> (Int, Int)
+ decodeFloat :: a -> (Integer, Int)
+ encodeFloat :: Integer -> Int -> a
+ exponent :: a -> Int
+ significand :: a -> a
+ scaleFloat :: Int -> a -> a
+ isNaN :: a -> Bool
+ isInfinite :: a -> Bool
+ isDenormalized :: a -> Bool
+ isNegativeZero :: a -> Bool
+ isIEEE :: a -> Bool
+ atan2 :: a -> a -> a
+ {-# MINIMAL floatRadix, floatDigits, floatRange, decodeFloat,
+ encodeFloat, isNaN, isInfinite, isDenormalized, isNegativeZero,
+ isIEEE #-}
+ -- Defined in ‘GHC.Float’
+instance RealFloat Float -- Defined in ‘GHC.Float’
+instance RealFloat Double -- Defined in ‘GHC.Float’
+base-4.9.0.0:Data.OldList.isPrefixOf :: Eq a => [a] -> [a] -> Bool
+ -- Defined in ‘base-4.9.0.0:Data.OldList’
diff --git a/testsuite/tests/ghci/scripts/ghci013.stdout b/testsuite/tests/ghci/scripts/ghci013.stdout
index d5afe0a691..b7065c5169 100644
--- a/testsuite/tests/ghci/scripts/ghci013.stdout
+++ b/testsuite/tests/ghci/scripts/ghci013.stdout
@@ -1 +1,2 @@
-f :: (?callStack::CallStack, Monad m) => (m a, r) -> m b
+f :: (?callStack::GHC.Stack.Types.CallStack, Monad m) =>
+ (m a, r) -> m b
diff --git a/testsuite/tests/ghci/scripts/ghci019.stderr b/testsuite/tests/ghci/scripts/ghci019.stderr
index 10f6a54bfe..aedf854e8a 100644
--- a/testsuite/tests/ghci/scripts/ghci019.stderr
+++ b/testsuite/tests/ghci/scripts/ghci019.stderr
@@ -1,5 +1,5 @@
-
-ghci019.hs:9:10: Warning:
- No explicit implementation for
- either ‘==’ or ‘/=’
- In the instance declaration for ‘Eq Foo’
+
+ghci019.hs:9:10: warning:
+ • 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 5c8b242339..d03720d2b5 100644
--- a/testsuite/tests/ghci/scripts/ghci019.stdout
+++ b/testsuite/tests/ghci/scripts/ghci019.stdout
@@ -1,2 +1,2 @@
data Foo = Foo -- Defined at ghci019.hs:8:1
-instance [safe] Eq Foo -- Defined at ghci019.hs:9:10
+instance [safe] Prelude.Eq Foo -- Defined at ghci019.hs:9:10
diff --git a/testsuite/tests/ghci/scripts/ghci023.stdout b/testsuite/tests/ghci/scripts/ghci023.stdout
index 61a859a73c..334b67d9fe 100644
--- a/testsuite/tests/ghci/scripts/ghci023.stdout
+++ b/testsuite/tests/ghci/scripts/ghci023.stdout
@@ -3,15 +3,15 @@
(1,2,3)
-- layout rule instead of explicit braces and semicolons works too
(1,2,3)
-catMaybes :: [Maybe a] -> [a]
-fromJust :: Maybe a -> a
-fromMaybe :: a -> Maybe a -> a
-isJust :: Maybe a -> Bool
-isNothing :: Maybe a -> Bool
-listToMaybe :: [a] -> Maybe a
-mapMaybe :: (a -> Maybe b) -> [a] -> [b]
+Data.Maybe.catMaybes :: [Maybe a] -> [a]
+Data.Maybe.fromJust :: Maybe a -> a
+Data.Maybe.fromMaybe :: a -> Maybe a -> a
+Data.Maybe.isJust :: Maybe a -> Bool
+Data.Maybe.isNothing :: Maybe a -> Bool
+Data.Maybe.listToMaybe :: [a] -> Maybe a
+Data.Maybe.mapMaybe :: (a -> Maybe b) -> [a] -> [b]
maybe :: b -> (a -> b) -> Maybe a -> b
-maybeToList :: Maybe a -> [a]
+Data.Maybe.maybeToList :: Maybe a -> [a]
data Maybe a = Nothing | Just a
-- via readFile
(True,False)
diff --git a/testsuite/tests/ghci/scripts/ghci025.stdout b/testsuite/tests/ghci/scripts/ghci025.stdout
index fc9bd6e2b1..80c4d4b7a5 100644
--- a/testsuite/tests/ghci/scripts/ghci025.stdout
+++ b/testsuite/tests/ghci/scripts/ghci025.stdout
@@ -1,117 +1,119 @@
--- test :browse! functionality
-:browse! *T
--- defined locally
-T.length :: T.Integer
-class N a
-class S a
-class C a b where
- c1 :: N b => a -> b
- c2 :: (N b, S b) => a -> b
- c3 :: a1 -> b
- c4 :: a1 -> b
- {-# MINIMAL c1, c2, c3, c4 #-}
-c1 :: (C a b, N b) => a -> b
-c2 :: (C a b, N b, S b) => a -> b
-c3 :: C a b => forall a. a -> b
-c4 :: C a b => forall a1. a1 -> b
--- imported via Control.Monad
-class (Alternative m, Monad m) => MonadPlus (m :: * -> *) where
- mzero :: m a
- mplus :: m a -> m a -> m a
-mplus :: MonadPlus m => forall a. m a -> m a -> m a
-mzero :: MonadPlus m => forall a. m a
--- imported via Control.Monad, Prelude
-(>>) :: Monad m => forall a b. m a -> m b -> m b
-(>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b
-fail :: Monad m => forall a. String -> m a
-return :: Monad m => forall a. a -> m a
--- imported via Control.Monad, Prelude, T
-class Applicative m => Monad (m :: * -> *) where
- (>>=) :: m a -> (a -> m b) -> m b
- (>>) :: m a -> m b -> m b
- return :: a -> m a
- fail :: String -> m a
- {-# MINIMAL (>>=) #-}
--- imported via Data.Maybe
-catMaybes :: [Maybe a] -> [a]
-fromJust :: Maybe a -> a
-fromMaybe :: a -> Maybe a -> a
-isJust :: Maybe a -> Bool
-isNothing :: Maybe a -> Bool
-listToMaybe :: [a] -> Maybe a
-mapMaybe :: (a -> Maybe b) -> [a] -> [b]
-maybe :: b -> (a -> b) -> Maybe a -> b
-maybeToList :: Maybe a -> [a]
--- imported via Data.Maybe, Prelude
-Just :: a -> Maybe a
-data Maybe a = Nothing | Just a
-Nothing :: Maybe a
--- imported via Prelude
-(+) :: Num a => a -> a -> a
-(=<<) :: Monad m => (a -> m b) -> m a -> m b
-class Eq a where
- (==) :: a -> a -> Bool
- (/=) :: a -> a -> Bool
- {-# MINIMAL (==) | (/=) #-}
--- imported via Prelude, T
-Prelude.length :: Foldable t => forall a. t a -> Int
--- imported via T
-data T.Integer
- = integer-gmp-1.0.0.0:GHC.Integer.Type.S# !Int#
- | integer-gmp-1.0.0.0:GHC.Integer.Type.Jp# {-# UNPACK #-}integer-gmp-1.0.0.0:GHC.Integer.Type.BigNat
- | integer-gmp-1.0.0.0:GHC.Integer.Type.Jn# {-# UNPACK #-}integer-gmp-1.0.0.0:GHC.Integer.Type.BigNat
-T.length :: Data.ByteString.Internal.ByteString -> Int
-:browse! T
--- defined locally
-T.length :: T.Integer
-class N a
-class S a
-class C a b where
- c1 :: N b => a -> b
- c2 :: (N b, S b) => a -> b
- c3 :: a1 -> b
- c4 :: a1 -> b
- {-# MINIMAL c1, c2, c3, c4 #-}
-c1 :: (C a b, N b) => a -> b
-c2 :: (C a b, N b, S b) => a -> b
-c3 :: C a b => forall a. a -> b
-c4 :: C a b => forall a1. a1 -> b
-:browse! T -- with -fprint-explicit-foralls
--- defined locally
-T.length :: T.Integer
-class N a
-class S a
-class C a b where
- c1 :: N b => a -> b
- c2 :: (N b, S b) => a -> b
- c3 :: forall a1. a1 -> b
- c4 :: forall a1. a1 -> b
- {-# MINIMAL c1, c2, c3, c4 #-}
-c1 :: forall a b. (C a b, N b) => a -> b
-c2 :: forall a b. (C a b, N b, S b) => a -> b
-c3 :: forall a b. C a b => forall a. a -> b
-c4 :: forall a b. C a b => forall a1. a1 -> b
--- test :browse! <target> relative to different contexts
-:browse! Ghci025C -- from *Ghci025C>
--- defined locally
-g :: forall a. Num a => a -> a
-h :: forall a. Integral a => a -> a
--- imported via Ghci025D
-f :: forall a. Num a => a -> a
-:browse! Ghci025C -- from *Ghci025B>, after :add Ghci025B
--- imported via Ghci025C
-g :: forall a. Num a => a -> a
-h :: forall a. Integral a => a -> a
-f :: forall a. Num a => a -> a
-:browse! Ghci025C -- from *Ghci025C>, after :m *Ghci025C
--- defined locally
-g :: forall a. Num a => a -> a
-h :: forall a. Integral a => a -> a
--- imported via Ghci025D
-f :: forall a. Num a => a -> a
-:browse! Ghci025C -- from *Ghci025D>, after :m *Ghci025D
--- not currently imported
-Ghci025C.g :: forall a. Num a => a -> a
-Ghci025C.h :: forall a. Integral a => a -> a
--- defined locally
-f :: forall a. Num a => a -> a
+-- test :browse! functionality
+:browse! *T
+-- defined locally
+T.length :: T.Integer
+class N a
+class S a
+class C a b where
+ c1 :: N b => a -> b
+ c2 :: (N b, S b) => a -> b
+ c3 :: a1 -> b
+ c4 :: a1 -> b
+ {-# MINIMAL c1, c2, c3, c4 #-}
+c1 :: (C a b, N b) => a -> b
+c2 :: (C a b, N b, S b) => a -> b
+c3 :: C a b => forall a. a -> b
+c4 :: C a b => forall a1. a1 -> b
+-- imported via Control.Monad
+class (GHC.Base.Alternative m, Monad m) =>
+ MonadPlus (m :: * -> *) where
+ mzero :: m a
+ mplus :: m a -> m a -> m a
+mplus :: MonadPlus m => forall a. m a -> m a -> m a
+mzero :: MonadPlus m => forall a. m a
+-- imported via Control.Monad, Prelude
+(>>) :: Monad m => forall a b. m a -> m b -> m b
+(>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b
+fail :: Monad m => forall a. GHC.Base.String -> m a
+return :: Monad m => forall a. a -> m a
+-- imported via Control.Monad, Prelude, T
+class GHC.Base.Applicative m => Monad (m :: * -> *) where
+ (>>=) :: m a -> (a -> m b) -> m b
+ (>>) :: m a -> m b -> m b
+ return :: a -> m a
+ fail :: GHC.Base.String -> m a
+ {-# MINIMAL (>>=) #-}
+-- imported via Data.Maybe
+catMaybes :: [Maybe a] -> [a]
+fromJust :: Maybe a -> a
+fromMaybe :: a -> Maybe a -> a
+isJust :: Maybe a -> GHC.Types.Bool
+isNothing :: Maybe a -> GHC.Types.Bool
+listToMaybe :: [a] -> Maybe a
+mapMaybe :: (a -> Maybe b) -> [a] -> [b]
+maybe :: b -> (a -> b) -> Maybe a -> b
+maybeToList :: Maybe a -> [a]
+-- imported via Data.Maybe, Prelude
+Just :: a -> Maybe a
+data Maybe a = Nothing | Just a
+Nothing :: Maybe a
+-- imported via Prelude
+(+) :: GHC.Num.Num a => a -> a -> a
+(=<<) :: Monad m => (a -> m b) -> m a -> m b
+class Eq a where
+ (GHC.Classes.==) :: a -> a -> GHC.Types.Bool
+ (GHC.Classes./=) :: a -> a -> GHC.Types.Bool
+ {-# MINIMAL (==) | (/=) #-}
+-- imported via Prelude, T
+Prelude.length ::
+ Data.Foldable.Foldable t => forall a. t a -> GHC.Types.Int
+-- imported via T
+data T.Integer
+ = integer-gmp-1.0.0.0:GHC.Integer.Type.S# !GHC.Prim.Int#
+ | integer-gmp-1.0.0.0:GHC.Integer.Type.Jp# {-# UNPACK #-}integer-gmp-1.0.0.0:GHC.Integer.Type.BigNat
+ | integer-gmp-1.0.0.0:GHC.Integer.Type.Jn# {-# UNPACK #-}integer-gmp-1.0.0.0:GHC.Integer.Type.BigNat
+T.length :: Data.ByteString.Internal.ByteString -> GHC.Types.Int
+:browse! T
+-- defined locally
+T.length :: T.Integer
+class N a
+class S a
+class C a b where
+ c1 :: N b => a -> b
+ c2 :: (N b, S b) => a -> b
+ c3 :: a1 -> b
+ c4 :: a1 -> b
+ {-# MINIMAL c1, c2, c3, c4 #-}
+c1 :: (C a b, N b) => a -> b
+c2 :: (C a b, N b, S b) => a -> b
+c3 :: C a b => forall a. a -> b
+c4 :: C a b => forall a1. a1 -> b
+:browse! T -- with -fprint-explicit-foralls
+-- defined locally
+T.length :: T.Integer
+class N a
+class S a
+class C a b where
+ c1 :: N b => a -> b
+ c2 :: (N b, S b) => a -> b
+ c3 :: forall a1. a1 -> b
+ c4 :: forall a1. a1 -> b
+ {-# MINIMAL c1, c2, c3, c4 #-}
+c1 :: forall a b. (C a b, N b) => a -> b
+c2 :: forall a b. (C a b, N b, S b) => a -> b
+c3 :: forall a b. C a b => forall a. a -> b
+c4 :: forall a b. C a b => forall a1. a1 -> b
+-- test :browse! <target> relative to different contexts
+:browse! Ghci025C -- from *Ghci025C>
+-- defined locally
+g :: forall a. Num a => a -> a
+h :: forall a. Integral a => a -> a
+-- imported via Ghci025D
+f :: forall a. Num a => a -> a
+:browse! Ghci025C -- from *Ghci025B>, after :add Ghci025B
+-- imported via Ghci025C
+g :: forall a. Num a => a -> a
+h :: forall a. Integral a => a -> a
+f :: forall a. Num a => a -> a
+:browse! Ghci025C -- from *Ghci025C>, after :m *Ghci025C
+-- defined locally
+g :: forall a. Num a => a -> a
+h :: forall a. Integral a => a -> a
+-- imported via Ghci025D
+f :: forall a. Num a => a -> a
+:browse! Ghci025C -- from *Ghci025D>, after :m *Ghci025D
+-- not currently imported
+Ghci025C.g :: forall a. Num a => a -> a
+Ghci025C.h :: forall a. Integral a => a -> a
+-- defined locally
+f :: forall a. Num a => a -> a
diff --git a/testsuite/tests/ghci/scripts/ghci027.stdout b/testsuite/tests/ghci/scripts/ghci027.stdout
index 33b138d2da..bbe355c17a 100644
--- a/testsuite/tests/ghci/scripts/ghci027.stdout
+++ b/testsuite/tests/ghci/scripts/ghci027.stdout
@@ -1,6 +1,8 @@
-class (Alternative m, Monad m) => MonadPlus (m :: * -> *) where
- ...
- mplus :: m a -> m a -> m a
-class (Alternative m, Monad m) => MonadPlus (m :: * -> *) where
- ...
- mplus :: m a -> m a -> m a
+class (GHC.Base.Alternative m, GHC.Base.Monad m) =>
+ GHC.Base.MonadPlus (m :: * -> *) where
+ ...
+ mplus :: m a -> m a -> m a
+class (GHC.Base.Alternative m, GHC.Base.Monad m) =>
+ GHC.Base.MonadPlus (m :: * -> *) where
+ ...
+ Control.Monad.mplus :: m a -> m a -> m a
diff --git a/testsuite/tests/ghci/scripts/ghci046.stdout b/testsuite/tests/ghci/scripts/ghci046.stdout
index 8b112976af..da71a9a73d 100644
--- a/testsuite/tests/ghci/scripts/ghci046.stdout
+++ b/testsuite/tests/ghci/scripts/ghci046.stdout
@@ -2,5 +2,5 @@ AND HTrue HTrue :: *
= HTrue
AND (OR HFalse HTrue) (OR HTrue HFalse) :: *
= HTrue
-t :: (?callStack::CallStack) => HTrue
-t :: (?callStack::CallStack) => HFalse
+t :: (?callStack::GHC.Stack.Types.CallStack) => HTrue
+t :: (?callStack::GHC.Stack.Types.CallStack) => HFalse
diff --git a/testsuite/tests/ghci/scripts/ghci055.stdout b/testsuite/tests/ghci/scripts/ghci055.stdout
index 6011c68f26..c7450d0def 100644
--- a/testsuite/tests/ghci/scripts/ghci055.stdout
+++ b/testsuite/tests/ghci/scripts/ghci055.stdout
@@ -1,3 +1,3 @@
x = _
-x :: ?callStack::CallStack => r = _
+x :: ?callStack::GHC.Stack.Types.CallStack => r = _
y :: Integer = 3