diff options
author | Simon Peyton Jones <simonpj@microsoft.com> | 2015-04-07 14:54:56 +0100 |
---|---|---|
committer | Simon Peyton Jones <simonpj@microsoft.com> | 2015-04-07 15:10:25 +0100 |
commit | c897613bbf6336d00c9b5433268cb5813308bee9 (patch) | |
tree | 25af8bc9a0cdc2858f7aa6b2a75c7b02651ebc9f /testsuite | |
parent | 547c597112954353cef7157cb0a389bc4f6303eb (diff) | |
download | haskell-c897613bbf6336d00c9b5433268cb5813308bee9.tar.gz |
Error msg wibbles from reduced module prefixes
Diffstat (limited to 'testsuite')
39 files changed, 710 insertions, 785 deletions
diff --git a/testsuite/tests/annotations/should_fail/annfail05.stderr b/testsuite/tests/annotations/should_fail/annfail05.stderr index 712cff2f2a..e9b281ecb8 100644 --- a/testsuite/tests/annotations/should_fail/annfail05.stderr +++ b/testsuite/tests/annotations/should_fail/annfail05.stderr @@ -1,5 +1,4 @@ - -annfail05.hs:11:1: - No instance for (Data.Data.Data NoInstances) - arising from an annotation - In the annotation: {-# ANN f NoInstances #-} +
+annfail05.hs:11:1:
+ No instance for (Data NoInstances) arising from an annotation
+ In the annotation: {-# ANN f NoInstances #-}
diff --git a/testsuite/tests/annotations/should_fail/annfail08.stderr b/testsuite/tests/annotations/should_fail/annfail08.stderr index 1c6f9f645c..2a9980dcb6 100644 --- a/testsuite/tests/annotations/should_fail/annfail08.stderr +++ b/testsuite/tests/annotations/should_fail/annfail08.stderr @@ -1,6 +1,6 @@ annfail08.hs:9:1:
- No instance for (Data.Data.Data (a0 -> a0))
+ No instance for (Data (a0 -> a0))
(maybe you haven't applied a function to enough arguments?)
arising from an annotation
In the annotation: {-# ANN f (id + 1) #-}
diff --git a/testsuite/tests/annotations/should_fail/annfail10.stderr b/testsuite/tests/annotations/should_fail/annfail10.stderr index 5b42bd3c9b..5ac8ab50b3 100644 --- a/testsuite/tests/annotations/should_fail/annfail10.stderr +++ b/testsuite/tests/annotations/should_fail/annfail10.stderr @@ -1,30 +1,25 @@ - -annfail10.hs:9:1: - No instance for (Data.Data.Data a0) arising from an annotation - The type variable ‘a0’ is ambiguous - Note: there are several potential instances: - instance (Data.Data.Data a, Data.Data.Data b) => - Data.Data.Data (Either a b) - -- Defined in ‘Data.Data’ - instance Data.Data.Data Data.Monoid.All -- Defined in ‘Data.Data’ - instance (Data.Data.Data (f a), Data.Data.Data a, - Data.Typeable.Internal.Typeable f) => - Data.Data.Data (Data.Monoid.Alt f a) - -- Defined in ‘Data.Data’ - ...plus 39 others - In the annotation: {-# ANN f 1 #-} - -annfail10.hs:9:11: - No instance for (Num a0) arising from the literal ‘1’ - The type variable ‘a0’ is ambiguous - Note: there are several potential instances: - instance forall (k :: BOX) (f :: k -> *) (a :: k). - Num (f a) => - Num (Data.Monoid.Alt f a) - -- Defined in ‘Data.Monoid’ - instance Num a => Num (Data.Monoid.Product a) - -- Defined in ‘Data.Monoid’ - instance Num a => Num (Data.Monoid.Sum a) - -- Defined in ‘Data.Monoid’ - ...plus 14 others - In the annotation: {-# ANN f 1 #-} +
+annfail10.hs:9:1:
+ No instance for (Data a0) arising from an annotation
+ The type variable ‘a0’ is ambiguous
+ Note: there are several potential instances:
+ instance (Data a, Data b) => Data (Either a b)
+ -- Defined in ‘Data.Data’
+ instance Data All -- Defined in ‘Data.Data’
+ instance (Data (f a), Data a, Typeable f) => Data (Alt f a)
+ -- Defined in ‘Data.Data’
+ ...plus 39 others
+ In the annotation: {-# ANN f 1 #-}
+
+annfail10.hs:9:11:
+ No instance for (Num a0) arising from the literal ‘1’
+ The type variable ‘a0’ is ambiguous
+ Note: there are several potential instances:
+ instance forall (k :: BOX) (f :: k -> *) (a :: k).
+ Num (f a) =>
+ Num (Alt f a)
+ -- Defined in ‘Data.Monoid’
+ instance Num a => Num (Product a) -- Defined in ‘Data.Monoid’
+ instance Num a => Num (Sum a) -- Defined in ‘Data.Monoid’
+ ...plus 14 others
+ In the annotation: {-# ANN f 1 #-}
diff --git a/testsuite/tests/deriving/should_fail/T4846.stderr b/testsuite/tests/deriving/should_fail/T4846.stderr index 33b125f2bc..b0ebb9edfb 100644 --- a/testsuite/tests/deriving/should_fail/T4846.stderr +++ b/testsuite/tests/deriving/should_fail/T4846.stderr @@ -5,10 +5,9 @@ T4846.hs:29:1: ‘Expr Bool’ and ‘Expr BOOL’ are the same Relevant role signatures: type role Expr nominal - In the expression: - GHC.Prim.coerce (mkExpr :: Expr Bool) :: Expr BOOL + In the expression: coerce (mkExpr :: Expr Bool) :: Expr BOOL In an equation for ‘mkExpr’: - mkExpr = GHC.Prim.coerce (mkExpr :: Expr Bool) :: Expr BOOL + mkExpr = coerce (mkExpr :: Expr Bool) :: Expr BOOL When typechecking the code for ‘mkExpr’ in a derived instance for ‘B BOOL’: To see the code I am typechecking, use -ddump-deriv diff --git a/testsuite/tests/ghci.debugger/scripts/break006.stderr b/testsuite/tests/ghci.debugger/scripts/break006.stderr index 865860564d..8a90905260 100644 --- a/testsuite/tests/ghci.debugger/scripts/break006.stderr +++ b/testsuite/tests/ghci.debugger/scripts/break006.stderr @@ -1,32 +1,32 @@ - -<interactive>:6:1: - No instance for (Show t1) arising from a use of ‘print’ - Cannot resolve unknown runtime type ‘t1’ - Use :print or :force to determine these types - Relevant bindings include it :: t1 (bound at <interactive>:6:1) - Note: there are several potential instances: - instance (Show a, Show b) => Show (Either a b) - -- Defined in ‘Data.Either’ - instance Show Data.Monoid.All -- Defined in ‘Data.Monoid’ - instance forall (k :: BOX) (f :: k -> *) (a :: k). - Show (f a) => - Show (Data.Monoid.Alt f a) - -- Defined in ‘Data.Monoid’ - ...plus 33 others - In a stmt of an interactive GHCi command: print it - -<interactive>:8:1: - No instance for (Show t1) arising from a use of ‘print’ - Cannot resolve unknown runtime type ‘t1’ - Use :print or :force to determine these types - Relevant bindings include it :: t1 (bound at <interactive>:8:1) - Note: there are several potential instances: - instance (Show a, Show b) => Show (Either a b) - -- Defined in ‘Data.Either’ - instance Show Data.Monoid.All -- Defined in ‘Data.Monoid’ - instance forall (k :: BOX) (f :: k -> *) (a :: k). - Show (f a) => - Show (Data.Monoid.Alt f a) - -- Defined in ‘Data.Monoid’ - ...plus 33 others - In a stmt of an interactive GHCi command: print it +
+<interactive>:6:1:
+ No instance for (Show t1) arising from a use of ‘print’
+ Cannot resolve unknown runtime type ‘t1’
+ Use :print or :force to determine these types
+ Relevant bindings include it :: t1 (bound at <interactive>:6:1)
+ Note: there are several potential instances:
+ instance (Show a, Show b) => Show (Either a b)
+ -- Defined in ‘Data.Either’
+ instance Show All -- Defined in ‘Data.Monoid’
+ instance forall (k :: BOX) (f :: k -> *) (a :: k).
+ Show (f a) =>
+ Show (Alt f a)
+ -- Defined in ‘Data.Monoid’
+ ...plus 33 others
+ In a stmt of an interactive GHCi command: print it
+
+<interactive>:8:1:
+ No instance for (Show t1) arising from a use of ‘print’
+ Cannot resolve unknown runtime type ‘t1’
+ Use :print or :force to determine these types
+ Relevant bindings include it :: t1 (bound at <interactive>:8:1)
+ Note: there are several potential instances:
+ instance (Show a, Show b) => Show (Either a b)
+ -- Defined in ‘Data.Either’
+ instance Show All -- Defined in ‘Data.Monoid’
+ instance forall (k :: BOX) (f :: k -> *) (a :: k).
+ Show (f a) =>
+ Show (Alt f a)
+ -- Defined in ‘Data.Monoid’
+ ...plus 33 others
+ In a stmt of an interactive GHCi command: print it
diff --git a/testsuite/tests/ghci.debugger/scripts/break024.stdout b/testsuite/tests/ghci.debugger/scripts/break024.stdout index dc3bd73425..62aa429cad 100644 --- a/testsuite/tests/ghci.debugger/scripts/break024.stdout +++ b/testsuite/tests/ghci.debugger/scripts/break024.stdout @@ -1,19 +1,16 @@ -Left user error (error) -Stopped at <exception thrown> -_exception :: e = _ -_exception = SomeException - (GHC.IO.Exception.IOError - Nothing GHC.IO.Exception.UserError [] "error" Nothing Nothing) -*** Exception: user error (error) -Stopped at <exception thrown> -_exception :: e = _ -_exception = SomeException - (GHC.IO.Exception.IOError - Nothing GHC.IO.Exception.UserError [] "error" Nothing Nothing) -*** Exception: user error (error) -Stopped at <exception thrown> -_exception :: e = _ -_exception = SomeException - (GHC.IO.Exception.IOError - Nothing GHC.IO.Exception.UserError [] "error" Nothing Nothing) -Left user error (error) +Left user error (error)
+Stopped at <exception thrown>
+_exception :: e = _
+_exception = SomeException
+ (IOError Nothing UserError [] "error" Nothing Nothing)
+*** Exception: user error (error)
+Stopped at <exception thrown>
+_exception :: e = _
+_exception = SomeException
+ (IOError Nothing UserError [] "error" Nothing Nothing)
+*** Exception: user error (error)
+Stopped at <exception thrown>
+_exception :: e = _
+_exception = SomeException
+ (IOError Nothing UserError [] "error" Nothing Nothing)
+Left user error (error)
diff --git a/testsuite/tests/ghci.debugger/scripts/print026.stdout b/testsuite/tests/ghci.debugger/scripts/print026.stdout index decc3dfb6d..25abae22d8 100644 --- a/testsuite/tests/ghci.debugger/scripts/print026.stdout +++ b/testsuite/tests/ghci.debugger/scripts/print026.stdout @@ -1,6 +1,6 @@ -fromList "abc" -l = Data.Sequence.Seq (Data.Sequence.Deep - 3 (Data.Sequence.One (Data.Sequence.Elem 'a')) Data.Sequence.Empty - (Data.Sequence.Two - (Data.Sequence.Elem 'b') (Data.Sequence.Elem 'c'))) -l = fromList "abc" +fromList "abc"
+l = Data.Sequence.Seq (Data.Sequence.Deep
+ 3 (Data.Sequence.One (Data.Sequence.Elem 'a')) Data.Sequence.Empty
+ (Data.Sequence.Two
+ (Data.Sequence.Elem 'b') (Data.Sequence.Elem 'c')))
+l = fromList "abc"
diff --git a/testsuite/tests/ghci.debugger/scripts/print028.stdout b/testsuite/tests/ghci.debugger/scripts/print028.stdout index 93a80bc69d..3e44dccbc8 100644 --- a/testsuite/tests/ghci.debugger/scripts/print028.stdout +++ b/testsuite/tests/ghci.debugger/scripts/print028.stdout @@ -1,6 +1,5 @@ -l = (_t1::[Maybe Integer]) -Just 1 -r = GHC.IORef.IORef (GHC.STRef.STRef - (GHC.Prim.MutVar# (Just 1 : (_t2::[Maybe Integer])))) -r = GHC.IORef.IORef (GHC.STRef.STRef - (GHC.Prim.MutVar# (Just 1 : _))) +l = (_t1::[Maybe Integer])
+Just 1
+r = IORef (STRef
+ (GHC.Prim.MutVar# (Just 1 : (_t2::[Maybe Integer]))))
+r = IORef (STRef (GHC.Prim.MutVar# (Just 1 : _)))
diff --git a/testsuite/tests/ghci/scripts/T2182ghci2.stderr b/testsuite/tests/ghci/scripts/T2182ghci2.stderr index 0a7f61959d..f850e1d7b4 100644 --- a/testsuite/tests/ghci/scripts/T2182ghci2.stderr +++ b/testsuite/tests/ghci/scripts/T2182ghci2.stderr @@ -1,10 +1,8 @@ - -<interactive>:8:1: - 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>:16:1: - 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>:8:1:
+ No instance for (Show Float) arising from a use of ‘print’
+ In a stmt of an interactive GHCi command: print it
+
+<interactive>:16:1:
+ No instance for (Show Float) arising from a use of ‘print’
+ In a stmt of an interactive GHCi command: print it
diff --git a/testsuite/tests/ghci/scripts/T5417.stdout b/testsuite/tests/ghci/scripts/T5417.stdout index 1085a1750f..2640c4e04c 100644 --- a/testsuite/tests/ghci/scripts/T5417.stdout +++ b/testsuite/tests/ghci/scripts/T5417.stdout @@ -1,9 +1,9 @@ -data B1 a = B1 a -data instance C.F (B1 a) = B2 a -type role D nominal -data family D a -class C.C1 a where - type role C.F nominal - data family C.F a - -- Defined at T5417a.hs:5:5 -data instance C.F (B1 a) = B2 a -- Defined at T5417.hs:8:10 +data B1 a = B1 a
+data instance C.F (B1 a) = B2 a
+type role D nominal
+data family D a
+class C.C1 a where
+ type role C.F nominal
+ data family C.F a
+ -- Defined at T5417a.hs:5:5
+data instance C.F (B1 a) = B2 a -- Defined at T5417.hs:8:10
diff --git a/testsuite/tests/ghci/scripts/T8469.stdout b/testsuite/tests/ghci/scripts/T8469.stdout index cd7966ee66..c052868ebb 100644 --- a/testsuite/tests/ghci/scripts/T8469.stdout +++ b/testsuite/tests/ghci/scripts/T8469.stdout @@ -1,10 +1,10 @@ -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’ +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’
diff --git a/testsuite/tests/ghci/scripts/T9181.stdout b/testsuite/tests/ghci/scripts/T9181.stdout index e1ac00cc83..6b67785d0b 100644 --- a/testsuite/tests/ghci/scripts/T9181.stdout +++ b/testsuite/tests/ghci/scripts/T9181.stdout @@ -1,54 +1,29 @@ -type family (GHC.TypeLits.*) (a :: GHC.TypeLits.Nat) - (b :: GHC.TypeLits.Nat) :: - GHC.TypeLits.Nat -type family (GHC.TypeLits.+) (a :: GHC.TypeLits.Nat) - (b :: GHC.TypeLits.Nat) :: - GHC.TypeLits.Nat -type family (GHC.TypeLits.-) (a :: GHC.TypeLits.Nat) - (b :: GHC.TypeLits.Nat) :: - GHC.TypeLits.Nat -type (GHC.TypeLits.<=) (x :: GHC.TypeLits.Nat) - (y :: GHC.TypeLits.Nat) = - (x GHC.TypeLits.<=? y) ~ 'True -type family (GHC.TypeLits.<=?) (a :: GHC.TypeLits.Nat) - (b :: GHC.TypeLits.Nat) :: - Bool -type family GHC.TypeLits.CmpNat (a :: GHC.TypeLits.Nat) - (b :: GHC.TypeLits.Nat) :: - Ordering -type family GHC.TypeLits.CmpSymbol (a :: GHC.TypeLits.Symbol) - (b :: GHC.TypeLits.Symbol) :: - Ordering -class GHC.TypeLits.KnownNat (n :: GHC.TypeLits.Nat) where - GHC.TypeLits.natSing :: GHC.TypeLits.SNat n -class GHC.TypeLits.KnownSymbol (n :: GHC.TypeLits.Symbol) where - GHC.TypeLits.symbolSing :: GHC.TypeLits.SSymbol n -data GHC.TypeLits.Nat -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 -data GHC.TypeLits.Symbol -type family (GHC.TypeLits.^) (a :: GHC.TypeLits.Nat) - (b :: GHC.TypeLits.Nat) :: - GHC.TypeLits.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 +type family (*) (a :: Nat) (b :: Nat) :: Nat
+type family (+) (a :: Nat) (b :: Nat) :: Nat
+type family (-) (a :: Nat) (b :: Nat) :: Nat
+type (<=) (x :: Nat) (y :: Nat) = (x <=? y) ~ 'True
+type family (<=?) (a :: Nat) (b :: Nat) :: Bool
+type family CmpNat (a :: Nat) (b :: Nat) :: Ordering
+type family CmpSymbol (a :: Symbol) (b :: Symbol) :: Ordering
+class KnownNat (n :: Nat) where
+ natSing :: SNat n
+class KnownSymbol (n :: Symbol) where
+ symbolSing :: SSymbol n
+data Nat
+data SomeNat where
+ SomeNat :: KnownNat n => (Proxy n) -> SomeNat
+data SomeSymbol where
+ SomeSymbol :: KnownSymbol n => (Proxy n) -> SomeSymbol
+data Symbol
+type family (^) (a :: Nat) (b :: 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
diff --git a/testsuite/tests/ghci/scripts/T9881.stdout b/testsuite/tests/ghci/scripts/T9881.stdout index 6866a6a79c..1fa697f102 100644 --- a/testsuite/tests/ghci/scripts/T9881.stdout +++ b/testsuite/tests/ghci/scripts/T9881.stdout @@ -1,32 +1,31 @@ -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’ +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’
diff --git a/testsuite/tests/ghci/scripts/ghci008.stdout b/testsuite/tests/ghci/scripts/ghci008.stdout index 8aec1602a6..0f9c93a4a9 100644 --- a/testsuite/tests/ghci/scripts/ghci008.stdout +++ b/testsuite/tests/ghci/scripts/ghci008.stdout @@ -1,36 +1,34 @@ -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 - -- Defined in ‘GHC.Float’ -instance RealFloat Float -- Defined in ‘GHC.Float’ -instance RealFloat Double -- Defined in ‘GHC.Float’ -base-4.8.1.0:Data.OldList.isPrefixOf :: Eq a => [a] -> [a] -> Bool - -- Defined in ‘base-4.8.1.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 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
+ -- 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.8.1.0:Data.OldList’
diff --git a/testsuite/tests/ghci/scripts/ghci019.stderr b/testsuite/tests/ghci/scripts/ghci019.stderr index de8c7f0901..10f6a54bfe 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 ‘Prelude.==’ or ‘Prelude./=’ - In the instance declaration for ‘Prelude.Eq Foo’ +
+ghci019.hs:9:10: Warning:
+ No explicit implementation for
+ either ‘==’ or ‘/=’
+ In the instance declaration for ‘Eq Foo’
diff --git a/testsuite/tests/ghci/scripts/ghci019.stdout b/testsuite/tests/ghci/scripts/ghci019.stdout index 4f346e70b5..85b5e02157 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 Prelude.Eq Foo -- Defined at ghci019.hs:9:10 +data Foo = Foo -- Defined at ghci019.hs:8:1
+instance 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 51c1b9196a..010fe50878 100644 --- a/testsuite/tests/ghci/scripts/ghci023.stdout +++ b/testsuite/tests/ghci/scripts/ghci023.stdout @@ -1,16 +1,16 @@ --- testing ghci multiline commands :{ .. :} --- via stdin -(1,2,3) -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 -Data.Maybe.maybeToList :: Maybe a -> [a] -data Maybe a = Nothing | Just a --- via readFile -(True,False) -id :: a -> a +-- testing ghci multiline commands :{ .. :}
+-- via stdin
+(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]
+maybe :: b -> (a -> b) -> Maybe a -> b
+maybeToList :: Maybe a -> [a]
+data Maybe a = Nothing | Just a
+-- via readFile
+(True,False)
+id :: a -> a
diff --git a/testsuite/tests/ghci/scripts/ghci025.stdout b/testsuite/tests/ghci/scripts/ghci025.stdout index 532a3347cc..e5b5bc34b7 100644 --- a/testsuite/tests/ghci/scripts/ghci025.stdout +++ b/testsuite/tests/ghci/scripts/ghci025.stdout @@ -1,114 +1,112 @@ --- 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 -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 --- 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 --- 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 -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 -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
+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
+-- 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
+-- 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
+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
+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 bbe355c17a..33b138d2da 100644 --- a/testsuite/tests/ghci/scripts/ghci027.stdout +++ b/testsuite/tests/ghci/scripts/ghci027.stdout @@ -1,8 +1,6 @@ -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 +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
diff --git a/testsuite/tests/indexed-types/should_compile/T3017.stderr b/testsuite/tests/indexed-types/should_compile/T3017.stderr index ee83f16325..3323235259 100644 --- a/testsuite/tests/indexed-types/should_compile/T3017.stderr +++ b/testsuite/tests/indexed-types/should_compile/T3017.stderr @@ -1,20 +1,20 @@ -TYPE SIGNATURES - emptyL :: forall a. ListColl a - test2 :: - forall c t t1. (Num t, Num t1, Coll c, Elem c ~ (t, t1)) => c -> c -TYPE CONSTRUCTORS - class Coll c where - type family Elem c :: * open - empty :: c - insert :: Elem c -> c -> c - data ListColl a = L [a] - Promotable -COERCION AXIOMS - axiom Foo.TFCo:R:ElemListColl :: Elem (ListColl a) = a -INSTANCES - instance Coll (ListColl a) -- Defined at T3017.hs:12:11 -FAMILY INSTANCES - type Elem (ListColl a) -Dependent modules: [] -Dependent packages: [base-4.8.1.0, ghc-prim-0.4.0.0, - integer-gmp-1.0.0.0] +TYPE SIGNATURES
+ emptyL :: forall a. ListColl a
+ test2 ::
+ forall c t t1. (Num t, Num t1, Coll c, Elem c ~ (t, t1)) => c -> c
+TYPE CONSTRUCTORS
+ class Coll c where
+ type family Elem c :: * open
+ empty :: c
+ insert :: Elem c -> c -> c
+ data ListColl a = L [a]
+ Promotable
+COERCION AXIOMS
+ axiom Foo.TFCo:R:ElemListColl :: Elem (ListColl a) = a
+INSTANCES
+ instance Coll (ListColl a) -- Defined at T3017.hs:12:11
+FAMILY INSTANCES
+ type Elem (ListColl a)
+Dependent modules: []
+Dependent packages: [base-4.8.1.0, ghc-prim-0.4.0.0,
+ integer-gmp-1.0.0.0]
diff --git a/testsuite/tests/indexed-types/should_fail/Over.stderr b/testsuite/tests/indexed-types/should_fail/Over.stderr index ae89d053b1..3eef32231b 100644 --- a/testsuite/tests/indexed-types/should_fail/Over.stderr +++ b/testsuite/tests/indexed-types/should_fail/Over.stderr @@ -1,10 +1,10 @@ - -OverB.hs:7:15: - Conflicting family instance declarations: - OverA.C [Int] [a] -- Defined at OverB.hs:7:15 - OverA.C [a] [Int] -- Defined at OverC.hs:7:15 - -OverB.hs:9:15: - Conflicting family instance declarations: - OverA.D [Int] [a] -- Defined at OverB.hs:9:15 - OverA.D [a] [Int] -- Defined at OverC.hs:9:15 +
+OverB.hs:7:15:
+ Conflicting family instance declarations:
+ OverA.C [Int] [a] -- Defined at OverB.hs:7:15
+ OverA.C [a] [Int] -- Defined at OverC.hs:7:15
+
+OverB.hs:9:15:
+ Conflicting family instance declarations:
+ OverA.D [Int] [a] -- Defined at OverB.hs:9:15
+ OverA.D [a] [Int] -- Defined at OverC.hs:9:15
diff --git a/testsuite/tests/indexed-types/should_fail/T9580.stderr b/testsuite/tests/indexed-types/should_fail/T9580.stderr index 2ed480fb7b..e2b7eb0991 100644 --- a/testsuite/tests/indexed-types/should_fail/T9580.stderr +++ b/testsuite/tests/indexed-types/should_fail/T9580.stderr @@ -1,11 +1,11 @@ -[1 of 2] Compiling T9580a ( T9580a.hs, T9580a.o ) -[2 of 2] Compiling T9580 ( T9580.hs, T9580.o ) - -T9580.hs:7:9: - Couldn't match representation of type ‘Dimensional Int Double’ - with that of ‘Double’ - Relevant role signatures: type role Dimensional nominal nominal - The data constructor ‘T9580a.Quantity'’ - of newtype ‘Dimensional Int v’ is not in scope - In the expression: coerce x - In an equation for ‘foo’: foo x = coerce x +[1 of 2] Compiling T9580a ( T9580a.hs, T9580a.o )
+[2 of 2] Compiling T9580 ( T9580.hs, T9580.o )
+
+T9580.hs:7:9:
+ Couldn't match representation of type ‘Dimensional Int Double’
+ with that of ‘Double’
+ Relevant role signatures: type role Dimensional nominal nominal
+ The data constructor ‘T9580a.Quantity'’
+ of newtype ‘Dimensional Int v’ is not in scope
+ In the expression: coerce x
+ In an equation for ‘foo’: foo x = coerce x
diff --git a/testsuite/tests/numeric/should_compile/T7116.stdout b/testsuite/tests/numeric/should_compile/T7116.stdout index 2ff1608bef..520460da36 100644 --- a/testsuite/tests/numeric/should_compile/T7116.stdout +++ b/testsuite/tests/numeric/should_compile/T7116.stdout @@ -1,70 +1,57 @@ - -==================== Tidy Core ==================== -Result size of Tidy Core = {terms: 22, types: 14, coercions: 0} - -dl :: Double -> Double -[GblId, - Arity=1, - Caf=NoCafRefs, - Str=DmdType <S,1*U(U)>m, - Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, - Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) - Tmpl= \ (x [Occ=Once!] :: Double) -> - case x of _ [Occ=Dead] { GHC.Types.D# y -> - GHC.Types.D# (GHC.Prim.+## y y) - }}] -dl = - \ (x :: Double) -> - case x of _ [Occ=Dead] { GHC.Types.D# y -> - GHC.Types.D# (GHC.Prim.+## y y) - } - -dr :: Double -> Double -[GblId, - Arity=1, - Caf=NoCafRefs, - Str=DmdType <S,1*U(U)>m, - Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, - Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) - Tmpl= \ (x [Occ=Once!] :: Double) -> - case x of _ [Occ=Dead] { GHC.Types.D# x1 -> - GHC.Types.D# (GHC.Prim.+## x1 x1) - }}] -dr = dl - -fl :: Float -> Float -[GblId, - Arity=1, - Caf=NoCafRefs, - Str=DmdType <S,1*U(U)>m, - Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, - Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) - Tmpl= \ (x [Occ=Once!] :: Float) -> - case x of _ [Occ=Dead] { GHC.Types.F# y -> - GHC.Types.F# (GHC.Prim.plusFloat# y y) - }}] -fl = - \ (x :: Float) -> - case x of _ [Occ=Dead] { GHC.Types.F# y -> - GHC.Types.F# (GHC.Prim.plusFloat# y y) - } - -fr :: Float -> Float -[GblId, - Arity=1, - Caf=NoCafRefs, - Str=DmdType <S,1*U(U)>m, - Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, - WorkFree=True, Expandable=True, - Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) - Tmpl= \ (x [Occ=Once!] :: Float) -> - case x of _ [Occ=Dead] { GHC.Types.F# x1 -> - GHC.Types.F# (GHC.Prim.plusFloat# x1 x1) - }}] -fr = fl - - - +
+==================== Tidy Core ====================
+Result size of Tidy Core = {terms: 22, types: 14, coercions: 0}
+
+dl :: Double -> Double
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=DmdType <S,1*U(U)>m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
+ Tmpl= \ (x [Occ=Once!] :: Double) ->
+ case x of _ [Occ=Dead] { D# y -> D# (+## y y) }}]
+dl =
+ \ (x :: Double) -> case x of _ [Occ=Dead] { D# y -> D# (+## y y) }
+
+dr :: Double -> Double
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=DmdType <S,1*U(U)>m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
+ Tmpl= \ (x [Occ=Once!] :: Double) ->
+ case x of _ [Occ=Dead] { D# x1 -> D# (+## x1 x1) }}]
+dr = dl
+
+fl :: Float -> Float
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=DmdType <S,1*U(U)>m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
+ Tmpl= \ (x [Occ=Once!] :: Float) ->
+ case x of _ [Occ=Dead] { F# y -> F# (plusFloat# y y) }}]
+fl =
+ \ (x :: Float) ->
+ case x of _ [Occ=Dead] { F# y -> F# (plusFloat# y y) }
+
+fr :: Float -> Float
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=DmdType <S,1*U(U)>m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
+ Tmpl= \ (x [Occ=Once!] :: Float) ->
+ case x of _ [Occ=Dead] { F# x1 -> F# (plusFloat# x1 x1) }}]
+fr = fl
+
+
+
diff --git a/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr b/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr index 6516beb078..52658fdd07 100644 --- a/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr +++ b/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr @@ -1,37 +1,33 @@ - -overloadedlistsfail01.hs:5:8: - No instance for (Show a0) arising from a use of ‘print’ - The type variable ‘a0’ is ambiguous - Note: there are several potential instances: - instance [safe] Show Data.Version.Version - -- Defined in ‘Data.Version’ - instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’ - instance Show Ordering -- Defined in ‘GHC.Show’ - ...plus 23 others - In the expression: print [1] - In an equation for ‘main’: main = print [1] - -overloadedlistsfail01.hs:5:14: - No instance for (GHC.Exts.IsList a0) - arising from an overloaded list - The type variable ‘a0’ is ambiguous - Note: there are several potential instances: - instance GHC.Exts.IsList Data.Version.Version - -- Defined in ‘GHC.Exts’ - instance GHC.Exts.IsList [a] -- Defined in ‘GHC.Exts’ - In the first argument of ‘print’, namely ‘[1]’ - In the expression: print [1] - In an equation for ‘main’: main = print [1] - -overloadedlistsfail01.hs:5:15: - No instance for (Num (GHC.Exts.Item a0)) - arising from the literal ‘1’ - The type variable ‘a0’ is ambiguous - Note: there are several potential instances: - instance Num Integer -- Defined in ‘GHC.Num’ - instance Num Double -- Defined in ‘GHC.Float’ - instance Num Float -- Defined in ‘GHC.Float’ - ...plus two others - In the expression: 1 - In the first argument of ‘print’, namely ‘[1]’ - In the expression: print [1] +
+overloadedlistsfail01.hs:5:8:
+ No instance for (Show a0) arising from a use of ‘print’
+ The type variable ‘a0’ is ambiguous
+ Note: there are several potential instances:
+ instance [safe] Show Version -- Defined in ‘Data.Version’
+ instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
+ instance Show Ordering -- Defined in ‘GHC.Show’
+ ...plus 23 others
+ In the expression: print [1]
+ In an equation for ‘main’: main = print [1]
+
+overloadedlistsfail01.hs:5:14:
+ No instance for (IsList a0) arising from an overloaded list
+ The type variable ‘a0’ is ambiguous
+ Note: there are several potential instances:
+ instance IsList Version -- Defined in ‘GHC.Exts’
+ instance IsList [a] -- Defined in ‘GHC.Exts’
+ In the first argument of ‘print’, namely ‘[1]’
+ In the expression: print [1]
+ In an equation for ‘main’: main = print [1]
+
+overloadedlistsfail01.hs:5:15:
+ No instance for (Num (Item a0)) arising from the literal ‘1’
+ The type variable ‘a0’ is ambiguous
+ Note: there are several potential instances:
+ instance Num Integer -- Defined in ‘GHC.Num’
+ instance Num Double -- Defined in ‘GHC.Float’
+ instance Num Float -- Defined in ‘GHC.Float’
+ ...plus two others
+ In the expression: 1
+ In the first argument of ‘print’, namely ‘[1]’
+ In the expression: print [1]
diff --git a/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr b/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr index d5f52fd66e..4597e1ce56 100644 --- a/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr +++ b/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr @@ -1,13 +1,11 @@ - -overloadedlistsfail02.hs:6:8: - No instance for (GHC.Exts.IsList Foo) - arising from an overloaded list - In the expression: [7] - In an equation for ‘test’: test = [7] - -overloadedlistsfail02.hs:6:9: - No instance for (Num (GHC.Exts.Item Foo)) - arising from the literal ‘7’ - In the expression: 7 - In the expression: [7] - In an equation for ‘test’: test = [7] +
+overloadedlistsfail02.hs:6:8:
+ No instance for (IsList Foo) arising from an overloaded list
+ In the expression: [7]
+ In an equation for ‘test’: test = [7]
+
+overloadedlistsfail02.hs:6:9:
+ No instance for (Num (Item Foo)) arising from the literal ‘7’
+ In the expression: 7
+ In the expression: [7]
+ In an equation for ‘test’: test = [7]
diff --git a/testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr b/testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr index 18f8807e74..439b4c5287 100644 --- a/testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr +++ b/testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr @@ -27,10 +27,10 @@ TYPE SIGNATURES acos :: forall a. Floating a => a -> a acosh :: forall a. Floating a => a -> a all :: - forall a (t :: * -> *). P.Foldable t => (a -> Bool) -> t a -> Bool - and :: forall (t :: * -> *). P.Foldable t => t Bool -> Bool + forall a (t :: * -> *). Foldable t => (a -> Bool) -> t a -> Bool + and :: forall (t :: * -> *). Foldable t => t Bool -> Bool any :: - forall a (t :: * -> *). P.Foldable t => (a -> Bool) -> t a -> Bool + forall a (t :: * -> *). Foldable t => (a -> Bool) -> t a -> Bool appendFile :: FilePath -> String -> IO () asTypeOf :: forall a. a -> a -> a asin :: forall a. Floating a => a -> a @@ -41,9 +41,9 @@ TYPE SIGNATURES break :: forall a. (a -> Bool) -> [a] -> ([a], [a]) ceiling :: forall a b. (Integral b, RealFrac a) => a -> b compare :: forall a. Ord a => a -> a -> Ordering - concat :: forall (t :: * -> *) a. P.Foldable t => t [a] -> [a] + concat :: forall (t :: * -> *) a. Foldable t => t [a] -> [a] concatMap :: - forall a b (t :: * -> *). P.Foldable t => (a -> [b]) -> t a -> [b] + forall a b (t :: * -> *). Foldable t => (a -> [b]) -> t a -> [b] const :: forall a b. a -> b -> a cos :: forall a. Floating a => a -> a cosh :: forall a. Floating a => a -> a @@ -56,7 +56,7 @@ TYPE SIGNATURES dropWhile :: forall a. (a -> Bool) -> [a] -> [a] either :: forall a c b. (a -> c) -> (b -> c) -> Either a b -> c elem :: - forall (t :: * -> *) a. (Eq a, P.Foldable t) => a -> t a -> Bool + forall (t :: * -> *) a. (Eq a, Foldable t) => a -> t a -> Bool encodeFloat :: forall a. RealFloat a => Integer -> Int -> a enumFrom :: forall a. Enum a => a -> [a] enumFromThen :: forall a. Enum a => a -> a -> [a] @@ -77,16 +77,16 @@ TYPE SIGNATURES forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b foldl :: forall (t :: * -> *) b a. - P.Foldable t => + Foldable t => (b -> a -> b) -> b -> t a -> b foldl1 :: - forall (t :: * -> *) a. P.Foldable t => (a -> a -> a) -> t a -> a + forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a foldr :: forall (t :: * -> *) a b. - P.Foldable t => + Foldable t => (a -> b -> b) -> b -> t a -> b foldr1 :: - forall (t :: * -> *) a. P.Foldable t => (a -> a -> a) -> t a -> a + forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a fromEnum :: forall a. Enum a => a -> Int fromInteger :: forall a. Num a => Integer -> a fromIntegral :: forall a b. (Integral a, Num b) => a -> b @@ -109,7 +109,7 @@ TYPE SIGNATURES iterate :: forall a. (a -> a) -> a -> [a] last :: forall a. [a] -> a lcm :: forall a. Integral a => a -> a -> a - length :: forall (t :: * -> *) a. P.Foldable t => t a -> Int + length :: forall (t :: * -> *) a. Foldable t => t a -> Int lex :: ReadS String lines :: String -> [String] log :: forall a. Floating a => a -> a @@ -118,35 +118,32 @@ TYPE SIGNATURES map :: forall a b. (a -> b) -> [a] -> [b] mapM :: forall (t :: * -> *) a (m :: * -> *) b. - (Monad m, P.Traversable t) => + (Monad m, Traversable t) => (a -> m b) -> t a -> m (t b) mapM_ :: forall a (m :: * -> *) b (t :: * -> *). - (Monad m, P.Foldable t) => + (Monad m, Foldable t) => (a -> m b) -> t a -> m () max :: forall a. Ord a => a -> a -> a maxBound :: forall w_. Bounded w_ => w_ - maximum :: - forall (t :: * -> *) a. (Ord a, P.Foldable t) => t a -> a + maximum :: forall (t :: * -> *) a. (Ord a, Foldable t) => t a -> a maybe :: forall b a. b -> (a -> b) -> Maybe a -> b min :: forall a. Ord a => a -> a -> a minBound :: forall w_. Bounded w_ => w_ - minimum :: - forall (t :: * -> *) a. (Ord a, P.Foldable t) => t a -> a + minimum :: forall (t :: * -> *) a. (Ord a, Foldable t) => t a -> a mod :: forall a. Integral a => a -> a -> a negate :: forall a. Num a => a -> a not :: Bool -> Bool notElem :: - forall a (t :: * -> *). (Eq a, P.Foldable t) => a -> t a -> Bool - null :: forall (t :: * -> *) a. P.Foldable t => t a -> Bool + forall a (t :: * -> *). (Eq a, Foldable t) => a -> t a -> Bool + null :: forall (t :: * -> *) a. Foldable t => t a -> Bool odd :: forall a. Integral a => a -> Bool - or :: forall (t :: * -> *). P.Foldable t => t Bool -> Bool + or :: forall (t :: * -> *). Foldable t => t Bool -> Bool otherwise :: Bool pi :: forall w_. Floating w_ => w_ pred :: forall a. Enum a => a -> a print :: forall a. Show a => a -> IO () - product :: - forall (t :: * -> *) a. (Num a, P.Foldable t) => t a -> a + product :: forall (t :: * -> *) a. (Num a, Foldable t) => t a -> a properFraction :: forall a b. (Integral b, RealFrac a) => a -> (b, a) putChar :: Char -> IO () @@ -178,11 +175,11 @@ TYPE SIGNATURES seq :: forall a b. a -> b -> b sequence :: forall (t :: * -> *) (m :: * -> *) a. - (Monad m, P.Traversable t) => + (Monad m, Traversable t) => t (m a) -> m (t a) sequence_ :: forall (t :: * -> *) (m :: * -> *) a. - (Monad m, P.Foldable t) => + (Monad m, Foldable t) => t (m a) -> m () show :: forall a. Show a => a -> String showChar :: Char -> ShowS @@ -201,7 +198,7 @@ TYPE SIGNATURES sqrt :: forall a. Floating a => a -> a subtract :: forall a. Num a => a -> a -> a succ :: forall a. Enum a => a -> a - sum :: forall (t :: * -> *) a. (Num a, P.Foldable t) => t a -> a + sum :: forall (t :: * -> *) a. (Num a, Foldable t) => t a -> a tail :: forall a. [a] -> [a] take :: forall a. Int -> [a] -> [a] takeWhile :: forall a. (a -> Bool) -> [a] -> [a] diff --git a/testsuite/tests/rebindable/rebindable6.stderr b/testsuite/tests/rebindable/rebindable6.stderr index 88cf8abac7..10c8f56ee3 100644 --- a/testsuite/tests/rebindable/rebindable6.stderr +++ b/testsuite/tests/rebindable/rebindable6.stderr @@ -1,66 +1,66 @@ -
-rebindable6.hs:106:17:
- No instance for (HasSeq (IO a -> t0 -> IO b))
- (maybe you haven't applied a function to enough arguments?)
- arising from a do statement
- The type variable ‘t0’ is ambiguous
- Relevant bindings include
- g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
- f :: IO a (bound at rebindable6.hs:104:17)
- test_do :: IO a -> IO (Maybe b) -> IO b
- (bound at rebindable6.hs:104:9)
- Note: there is a potential instance available:
- instance HasSeq (IO a -> IO b -> IO b)
- -- Defined at rebindable6.hs:52:18
- In a stmt of a 'do' block: f
- In the expression:
- do { f;
- Just (b :: b) <- g;
- return b }
- In an equation for ‘test_do’:
- test_do f g
- = do { f;
- Just (b :: b) <- g;
- return b }
-
-rebindable6.hs:107:17:
- No instance for (HasFail ([Prelude.Char] -> t1))
- (maybe you haven't applied a function to enough arguments?)
- arising from a do statement
- The type variable ‘t1’ is ambiguous
- Note: there is a potential instance available:
- instance HasFail (String -> IO a)
- -- Defined at rebindable6.hs:57:18
- In a stmt of a 'do' block: Just (b :: b) <- g
- In the expression:
- do { f;
- Just (b :: b) <- g;
- return b }
- In an equation for ‘test_do’:
- test_do f g
- = do { f;
- Just (b :: b) <- g;
- return b }
-
-rebindable6.hs:108:17:
- No instance for (HasReturn (b -> t1))
- (maybe you haven't applied a function to enough arguments?)
- arising from a use of ‘return’
- The type variable ‘t1’ is ambiguous
- Relevant bindings include
- b :: b (bound at rebindable6.hs:107:23)
- g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
- test_do :: IO a -> IO (Maybe b) -> IO b
- (bound at rebindable6.hs:104:9)
- Note: there is a potential instance available:
- instance HasReturn (a -> IO a) -- Defined at rebindable6.hs:42:18
- In a stmt of a 'do' block: return b
- In the expression:
- do { f;
- Just (b :: b) <- g;
- return b }
- In an equation for ‘test_do’:
- test_do f g
- = do { f;
- Just (b :: b) <- g;
- return b }
+ +rebindable6.hs:106:17: + No instance for (HasSeq (IO a -> t0 -> IO b)) + (maybe you haven't applied a function to enough arguments?) + arising from a do statement + The type variable ‘t0’ is ambiguous + Relevant bindings include + g :: IO (Maybe b) (bound at rebindable6.hs:104:19) + f :: IO a (bound at rebindable6.hs:104:17) + test_do :: IO a -> IO (Maybe b) -> IO b + (bound at rebindable6.hs:104:9) + Note: there is a potential instance available: + instance HasSeq (IO a -> IO b -> IO b) + -- Defined at rebindable6.hs:52:18 + In a stmt of a 'do' block: f + In the expression: + do { f; + Just (b :: b) <- g; + return b } + In an equation for ‘test_do’: + test_do f g + = do { f; + Just (b :: b) <- g; + return b } + +rebindable6.hs:107:17: + No instance for (HasFail ([Char] -> t1)) + (maybe you haven't applied a function to enough arguments?) + arising from a do statement + The type variable ‘t1’ is ambiguous + Note: there is a potential instance available: + instance HasFail (String -> IO a) + -- Defined at rebindable6.hs:57:18 + In a stmt of a 'do' block: Just (b :: b) <- g + In the expression: + do { f; + Just (b :: b) <- g; + return b } + In an equation for ‘test_do’: + test_do f g + = do { f; + Just (b :: b) <- g; + return b } + +rebindable6.hs:108:17: + No instance for (HasReturn (b -> t1)) + (maybe you haven't applied a function to enough arguments?) + arising from a use of ‘return’ + The type variable ‘t1’ is ambiguous + Relevant bindings include + b :: b (bound at rebindable6.hs:107:23) + g :: IO (Maybe b) (bound at rebindable6.hs:104:19) + test_do :: IO a -> IO (Maybe b) -> IO b + (bound at rebindable6.hs:104:9) + Note: there is a potential instance available: + instance HasReturn (a -> IO a) -- Defined at rebindable6.hs:42:18 + In a stmt of a 'do' block: return b + In the expression: + do { f; + Just (b :: b) <- g; + return b } + In an equation for ‘test_do’: + test_do f g + = do { f; + Just (b :: b) <- g; + return b } diff --git a/testsuite/tests/th/T3319.stderr b/testsuite/tests/th/T3319.stderr index b7e3411d41..4406c438fc 100644 --- a/testsuite/tests/th/T3319.stderr +++ b/testsuite/tests/th/T3319.stderr @@ -1,7 +1,7 @@ -T3319.hs:8:3-93: Splicing declarations
- return
- [ForeignD
- (ImportF
- CCall Unsafe "&" (mkName "foo") (AppT (ConT ''Ptr) (ConT ''())))]
- ======>
- foreign import ccall unsafe "static &foo" foo :: Ptr GHC.Tuple.()
+T3319.hs:8:3-93: Splicing declarations + return + [ForeignD + (ImportF + CCall Unsafe "&" (mkName "foo") (AppT (ConT ''Ptr) (ConT ''())))] + ======> + foreign import ccall unsafe "static &foo" foo :: Ptr () diff --git a/testsuite/tests/th/T5700.stderr b/testsuite/tests/th/T5700.stderr index 729a36604f..3564b8cb2a 100644 --- a/testsuite/tests/th/T5700.stderr +++ b/testsuite/tests/th/T5700.stderr @@ -3,4 +3,4 @@ T5700.hs:8:3-9: Splicing declarations ======> instance C D where {-# INLINE inlinable #-} - inlinable _ = GHC.Tuple.() + inlinable _ = () diff --git a/testsuite/tests/th/T7276.stderr b/testsuite/tests/th/T7276.stderr index 157d731c93..1386045774 100644 --- a/testsuite/tests/th/T7276.stderr +++ b/testsuite/tests/th/T7276.stderr @@ -1,8 +1,7 @@ T7276.hs:6:8: - Couldn't match type ‘[Language.Haskell.TH.Syntax.Dec]’ - with ‘Language.Haskell.TH.Syntax.Exp’ - Expected type: Language.Haskell.TH.Lib.ExpQ - Actual type: Language.Haskell.TH.Lib.DecsQ + Couldn't match type ‘[Dec]’ with ‘Exp’ + Expected type: ExpQ + Actual type: DecsQ In the expression: [d| y = 3 |] In the untyped splice: $([d| y = 3 |]) diff --git a/testsuite/tests/th/TH_foreignInterruptible.stderr b/testsuite/tests/th/TH_foreignInterruptible.stderr index 9cbf34ac87..a11ec36daf 100644 --- a/testsuite/tests/th/TH_foreignInterruptible.stderr +++ b/testsuite/tests/th/TH_foreignInterruptible.stderr @@ -8,5 +8,4 @@ TH_foreignInterruptible.hs:8:3-100: Splicing declarations (mkName "foo") (AppT (ConT ''Ptr) (ConT ''())))] ======> - foreign import ccall interruptible "static &foo" foo - :: Ptr GHC.Tuple.() + foreign import ccall interruptible "static &foo" foo :: Ptr () diff --git a/testsuite/tests/typecheck/should_fail/T5095.stderr b/testsuite/tests/typecheck/should_fail/T5095.stderr index e0f9336e01..0cf88546a0 100644 --- a/testsuite/tests/typecheck/should_fail/T5095.stderr +++ b/testsuite/tests/typecheck/should_fail/T5095.stderr @@ -60,28 +60,23 @@ T5095.hs:9:11: -- Defined in ‘integer-gmp-1.0.0.0:GHC.Integer.Type’ instance Eq Integer -- Defined in ‘integer-gmp-1.0.0.0:GHC.Integer.Type’ - instance Eq Data.Monoid.All -- Defined in ‘Data.Monoid’ + instance Eq All -- Defined in ‘Data.Monoid’ instance forall (k :: BOX) (f :: k -> *) (a :: k). Eq (f a) => - Eq (Data.Monoid.Alt f a) + Eq (Alt f a) -- Defined in ‘Data.Monoid’ - instance Eq Data.Monoid.Any -- Defined in ‘Data.Monoid’ - instance Eq a => Eq (Data.Monoid.Dual a) - -- Defined in ‘Data.Monoid’ - instance Eq a => Eq (Data.Monoid.First a) - -- Defined in ‘Data.Monoid’ - instance Eq a => Eq (Data.Monoid.Last a) - -- Defined in ‘Data.Monoid’ - instance Eq a => Eq (Data.Monoid.Product a) - -- Defined in ‘Data.Monoid’ - instance Eq a => Eq (Data.Monoid.Sum a) -- Defined in ‘Data.Monoid’ - instance forall (k :: BOX) (s :: k). Eq (Data.Proxy.Proxy s) + instance Eq Any -- Defined in ‘Data.Monoid’ + instance Eq a => Eq (Dual a) -- Defined in ‘Data.Monoid’ + instance Eq a => Eq (First a) -- Defined in ‘Data.Monoid’ + instance Eq a => Eq (Last a) -- Defined in ‘Data.Monoid’ + instance Eq a => Eq (Product a) -- Defined in ‘Data.Monoid’ + instance Eq a => Eq (Sum a) -- Defined in ‘Data.Monoid’ + instance forall (k :: BOX) (s :: k). Eq (Proxy s) -- Defined in ‘Data.Proxy’ instance (Eq a, Eq b) => Eq (Either a b) -- Defined in ‘Data.Either’ - instance (GHC.Arr.Ix i, Eq e) => Eq (GHC.Arr.Array i e) - -- Defined in ‘GHC.Arr’ - instance Eq (GHC.Arr.STArray s i e) -- Defined in ‘GHC.Arr’ + instance (Ix i, Eq e) => Eq (Array i e) -- Defined in ‘GHC.Arr’ + instance Eq (STArray s i e) -- Defined in ‘GHC.Arr’ (The choice depends on the instantiation of ‘a’ To pick the first instance above, use IncoherentInstances when compiling the other instance declarations) diff --git a/testsuite/tests/typecheck/should_fail/T8262.stderr b/testsuite/tests/typecheck/should_fail/T8262.stderr index 9bc46e3ebe..cfaf5adafa 100644 --- a/testsuite/tests/typecheck/should_fail/T8262.stderr +++ b/testsuite/tests/typecheck/should_fail/T8262.stderr @@ -3,7 +3,7 @@ T8262.hs:5:15: Couldn't match kind ‘*’ with ‘#’ When matching types a :: * - GHC.Prim.Int# :: # + Int# :: # Relevant bindings include foo :: t -> Maybe a (bound at T8262.hs:5:1) In the first argument of ‘Just’, namely ‘(1#)’ diff --git a/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr b/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr index 3989ea4936..85b988a653 100644 --- a/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr +++ b/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr @@ -1,13 +1,12 @@ TcStaticPointersFail02.hs:9:6: - No instance for (Data.Typeable.Internal.Typeable b) - arising from a static form + No instance for (Typeable b) arising from a static form In the expression: static (undefined :: (forall a. a -> a) -> b) In an equation for ‘f1’: f1 = static (undefined :: (forall a. a -> a) -> b) TcStaticPointersFail02.hs:12:6: - No instance for (Data.Typeable.Internal.Typeable m) + No instance for (Typeable m) (maybe you haven't applied a function to enough arguments?) arising from a static form In the expression: static return diff --git a/testsuite/tests/typecheck/should_fail/tcfail068.stderr b/testsuite/tests/typecheck/should_fail/tcfail068.stderr index a25e57524c..d7c8ed7aba 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail068.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail068.stderr @@ -1,96 +1,96 @@ -
-tcfail068.hs:14:9:
- Couldn't match type ‘s1’ with ‘s’
- ‘s1’ is a rigid type variable bound by
- a type expected by the context: GHC.ST.ST s1 (IndTree s a)
- at tcfail068.hs:13:9
- ‘s’ is a rigid type variable bound by
- the type signature for:
- itgen :: Constructed a => (Int, Int) -> a -> IndTree s a
- at tcfail068.hs:11:10
- Expected type: GHC.ST.ST s1 (IndTree s a)
- Actual type: GHC.ST.ST s1 (STArray s1 (Int, Int) a)
- Relevant bindings include
- itgen :: (Int, Int) -> a -> IndTree s a
- (bound at tcfail068.hs:12:1)
- In the first argument of ‘runST’, namely
- ‘(newSTArray ((1, 1), n) x)’
- In the expression: runST (newSTArray ((1, 1), n) x)
-
-tcfail068.hs:19:21:
- Couldn't match type ‘s’ with ‘s1’
- ‘s’ is a rigid type variable bound by
- the type signature for:
- itiap :: Constructed a =>
- (Int, Int) -> (a -> a) -> IndTree s a -> IndTree s a
- at tcfail068.hs:16:10
- ‘s1’ is a rigid type variable bound by
- a type expected by the context: GHC.ST.ST s1 (IndTree s a)
- at tcfail068.hs:18:9
- Expected type: STArray s1 (Int, Int) a
- Actual type: IndTree s a
- Relevant bindings include
- arr :: IndTree s a (bound at tcfail068.hs:17:11)
- itiap :: (Int, Int) -> (a -> a) -> IndTree s a -> IndTree s a
- (bound at tcfail068.hs:17:1)
- In the first argument of ‘readSTArray’, namely ‘arr’
- In the first argument of ‘(>>=)’, namely ‘readSTArray arr i’
-
-tcfail068.hs:24:36:
- Couldn't match type ‘s’ with ‘s1’
- ‘s’ is a rigid type variable bound by
- the type signature for:
- itrap :: Constructed a =>
- ((Int, Int), (Int, Int)) -> (a -> a) -> IndTree s a -> IndTree s a
- at tcfail068.hs:23:10
- ‘s1’ is a rigid type variable bound by
- a type expected by the context: GHC.ST.ST s1 (IndTree s a)
- at tcfail068.hs:24:29
- Expected type: GHC.ST.ST s1 (IndTree s a)
- Actual type: GHC.ST.ST s (IndTree s a)
- Relevant bindings include
- itrap' :: Int -> Int -> GHC.ST.ST s (IndTree s a)
- (bound at tcfail068.hs:26:9)
- itrapsnd :: Int -> Int -> GHC.ST.ST s (IndTree s a)
- (bound at tcfail068.hs:29:9)
- arr :: IndTree s a (bound at tcfail068.hs:24:23)
- itrap :: ((Int, Int), (Int, Int))
- -> (a -> a) -> IndTree s a -> IndTree s a
- (bound at tcfail068.hs:24:1)
- In the first argument of ‘runST’, namely ‘(itrap' i k)’
- In the expression: runST (itrap' i k)
-
-tcfail068.hs:36:46:
- Couldn't match type ‘s’ with ‘s1’
- ‘s’ is a rigid type variable bound by
- the type signature for:
- itrapstate :: Constructed b =>
- ((Int, Int), (Int, Int))
- -> (a -> b -> (a, b))
- -> ((Int, Int) -> c -> a)
- -> (a -> c)
- -> c
- -> IndTree s b
- -> (c, IndTree s b)
- at tcfail068.hs:34:15
- ‘s1’ is a rigid type variable bound by
- a type expected by the context: GHC.ST.ST s1 (c, IndTree s b)
- at tcfail068.hs:36:40
- Expected type: GHC.ST.ST s1 (c, IndTree s b)
- Actual type: GHC.ST.ST s (c, IndTree s b)
- Relevant bindings include
- itrapstate' :: Int -> Int -> c -> GHC.ST.ST s (c, IndTree s b)
- (bound at tcfail068.hs:38:9)
- itrapstatesnd :: Int -> Int -> c -> GHC.ST.ST s (c, IndTree s b)
- (bound at tcfail068.hs:41:9)
- arr :: IndTree s b (bound at tcfail068.hs:36:34)
- itrapstate :: ((Int, Int), (Int, Int))
- -> (a -> b -> (a, b))
- -> ((Int, Int) -> c -> a)
- -> (a -> c)
- -> c
- -> IndTree s b
- -> (c, IndTree s b)
- (bound at tcfail068.hs:36:1)
- In the first argument of ‘runST’, namely ‘(itrapstate' i k s)’
- In the expression: runST (itrapstate' i k s)
+ +tcfail068.hs:14:9: + Couldn't match type ‘s1’ with ‘s’ + ‘s1’ is a rigid type variable bound by + a type expected by the context: ST s1 (IndTree s a) + at tcfail068.hs:13:9 + ‘s’ is a rigid type variable bound by + the type signature for: + itgen :: Constructed a => (Int, Int) -> a -> IndTree s a + at tcfail068.hs:11:10 + Expected type: ST s1 (IndTree s a) + Actual type: ST s1 (STArray s1 (Int, Int) a) + Relevant bindings include + itgen :: (Int, Int) -> a -> IndTree s a + (bound at tcfail068.hs:12:1) + In the first argument of ‘runST’, namely + ‘(newSTArray ((1, 1), n) x)’ + In the expression: runST (newSTArray ((1, 1), n) x) + +tcfail068.hs:19:21: + Couldn't match type ‘s’ with ‘s1’ + ‘s’ is a rigid type variable bound by + the type signature for: + itiap :: Constructed a => + (Int, Int) -> (a -> a) -> IndTree s a -> IndTree s a + at tcfail068.hs:16:10 + ‘s1’ is a rigid type variable bound by + a type expected by the context: ST s1 (IndTree s a) + at tcfail068.hs:18:9 + Expected type: STArray s1 (Int, Int) a + Actual type: IndTree s a + Relevant bindings include + arr :: IndTree s a (bound at tcfail068.hs:17:11) + itiap :: (Int, Int) -> (a -> a) -> IndTree s a -> IndTree s a + (bound at tcfail068.hs:17:1) + In the first argument of ‘readSTArray’, namely ‘arr’ + In the first argument of ‘(>>=)’, namely ‘readSTArray arr i’ + +tcfail068.hs:24:36: + Couldn't match type ‘s’ with ‘s1’ + ‘s’ is a rigid type variable bound by + the type signature for: + itrap :: Constructed a => + ((Int, Int), (Int, Int)) -> (a -> a) -> IndTree s a -> IndTree s a + at tcfail068.hs:23:10 + ‘s1’ is a rigid type variable bound by + a type expected by the context: ST s1 (IndTree s a) + at tcfail068.hs:24:29 + Expected type: ST s1 (IndTree s a) + Actual type: ST s (IndTree s a) + Relevant bindings include + itrap' :: Int -> Int -> ST s (IndTree s a) + (bound at tcfail068.hs:26:9) + itrapsnd :: Int -> Int -> ST s (IndTree s a) + (bound at tcfail068.hs:29:9) + arr :: IndTree s a (bound at tcfail068.hs:24:23) + itrap :: ((Int, Int), (Int, Int)) + -> (a -> a) -> IndTree s a -> IndTree s a + (bound at tcfail068.hs:24:1) + In the first argument of ‘runST’, namely ‘(itrap' i k)’ + In the expression: runST (itrap' i k) + +tcfail068.hs:36:46: + Couldn't match type ‘s’ with ‘s1’ + ‘s’ is a rigid type variable bound by + the type signature for: + itrapstate :: Constructed b => + ((Int, Int), (Int, Int)) + -> (a -> b -> (a, b)) + -> ((Int, Int) -> c -> a) + -> (a -> c) + -> c + -> IndTree s b + -> (c, IndTree s b) + at tcfail068.hs:34:15 + ‘s1’ is a rigid type variable bound by + a type expected by the context: ST s1 (c, IndTree s b) + at tcfail068.hs:36:40 + Expected type: ST s1 (c, IndTree s b) + Actual type: ST s (c, IndTree s b) + Relevant bindings include + itrapstate' :: Int -> Int -> c -> ST s (c, IndTree s b) + (bound at tcfail068.hs:38:9) + itrapstatesnd :: Int -> Int -> c -> ST s (c, IndTree s b) + (bound at tcfail068.hs:41:9) + arr :: IndTree s b (bound at tcfail068.hs:36:34) + itrapstate :: ((Int, Int), (Int, Int)) + -> (a -> b -> (a, b)) + -> ((Int, Int) -> c -> a) + -> (a -> c) + -> c + -> IndTree s b + -> (c, IndTree s b) + (bound at tcfail068.hs:36:1) + In the first argument of ‘runST’, namely ‘(itrapstate' i k s)’ + In the expression: runST (itrapstate' i k s) diff --git a/testsuite/tests/typecheck/should_fail/tcfail123.stderr b/testsuite/tests/typecheck/should_fail/tcfail123.stderr index 1bc0246817..9f5cc09bdf 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail123.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail123.stderr @@ -3,7 +3,7 @@ tcfail123.hs:11:9: Couldn't match kind ‘*’ with ‘#’ When matching types t0 :: * - GHC.Prim.Int# :: # + Int# :: # In the first argument of ‘f’, namely ‘3#’ In the expression: f 3# In an equation for ‘h’: h v = f 3# diff --git a/testsuite/tests/typecheck/should_fail/tcfail128.stderr b/testsuite/tests/typecheck/should_fail/tcfail128.stderr index b33dffb289..6d59560c82 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail128.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail128.stderr @@ -4,7 +4,7 @@ tcfail128.hs:18:16: arising from a use of ‘thaw’ The type variable ‘b0’ is ambiguous Note: there is a potential instance available: - instance Data.Array.Base.MArray GHC.IOArray.IOArray e IO + instance Data.Array.Base.MArray IOArray e IO -- Defined in ‘Data.Array.Base’ In a stmt of a 'do' block: v <- thaw tmp In the expression: diff --git a/testsuite/tests/typecheck/should_fail/tcfail200.stderr b/testsuite/tests/typecheck/should_fail/tcfail200.stderr index ba9f0ceb54..473ff9ebd7 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail200.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail200.stderr @@ -3,7 +3,7 @@ tcfail200.hs:5:15: Couldn't match kind ‘*’ with ‘#’ When matching types t1 :: * - GHC.Prim.Int# :: # + Int# :: # Relevant bindings include x :: (t1, Char) (bound at tcfail200.hs:5:9) In the expression: 1# diff --git a/testsuite/tests/typecheck/should_fail/tcfail220.stderr b/testsuite/tests/typecheck/should_fail/tcfail220.stderr index e565cc7af6..dcb6fbc2e4 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail220.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail220.stderr @@ -3,13 +3,13 @@ tcfail220.hsig:4:1: Type constructor ‘Bool’ has conflicting definitions in the module and its hsig file - Main module: data Bool = False | GHC.Types.True + Main module: data Bool = False | True Hsig file: data Bool a b c d = False The types have different kinds tcfail220.hsig:5:1: Type constructor ‘Maybe’ has conflicting definitions in the module and its hsig file - Main module: data Maybe a = Nothing | GHC.Base.Just a + Main module: data Maybe a = Nothing | Just a Hsig file: data Maybe a b = Nothing The types have different kinds |