From a91cac4fe15bc7751da34cc6507976d67c5afadc Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 10 Jan 2013 16:54:11 +0000
Subject: [PATCH 001/223] Test Trac #7562

---
 tests/typecheck/should_compile/T7562.hs     | 3 +++
 tests/typecheck/should_compile/T7562.stderr | 5 +++++
 tests/typecheck/should_compile/all.T        | 1 +
 3 files changed, 9 insertions(+)
 create mode 100644 tests/typecheck/should_compile/T7562.hs
 create mode 100644 tests/typecheck/should_compile/T7562.stderr

diff --git a/tests/typecheck/should_compile/T7562.hs b/tests/typecheck/should_compile/T7562.hs
new file mode 100644
index 000000000..40634e279
--- /dev/null
+++ b/tests/typecheck/should_compile/T7562.hs
@@ -0,0 +1,3 @@
+module T7562 where
+
+data Pair2 = Pair2 {-# UNPACK #-} Int
diff --git a/tests/typecheck/should_compile/T7562.stderr b/tests/typecheck/should_compile/T7562.stderr
new file mode 100644
index 000000000..1460def5c
--- /dev/null
+++ b/tests/typecheck/should_compile/T7562.stderr
@@ -0,0 +1,5 @@
+
+T7562.hs:3:14: Warning:
+    UNPACK pragma lacks '!' on the first argument of `Pair2'
+    In the definition of data constructor `Pair2'
+    In the data declaration for `Pair2'
diff --git a/tests/typecheck/should_compile/all.T b/tests/typecheck/should_compile/all.T
index 57c80f1ab..94ebf41fd 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -396,3 +396,4 @@ test('holes3', normal, compile_fail, [''])
 test('T7408', normal, compile, [''])
 test('UnboxStrictPrimitiveFields', normal, compile, [''])
 test('T7541', normal, compile, [''])
+test('T7562', normal, compile, [''])
-- 
GitLab


From 384f47e997c800f96d821cdef252923d850abbb0 Mon Sep 17 00:00:00 2001
From: "Iavor S. Diatchki" <iavor.diatchki@gmail.com>
Date: Sun, 13 Jan 2013 16:31:33 -0800
Subject: [PATCH 002/223] Add a missing FD on `Add`, otherwise the test is
 (correctly) rejected.

The reason is the we don't automatically inherit the FDs of
super-classes.
---
 tests/typecheck/should_compile/T6055.hs | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/typecheck/should_compile/T6055.hs b/tests/typecheck/should_compile/T6055.hs
index beede5513..dcc39d161 100644
--- a/tests/typecheck/should_compile/T6055.hs
+++ b/tests/typecheck/should_compile/T6055.hs
@@ -21,7 +21,7 @@ class Add' x y z | x y -> z
 instance Succ y z => Add' D1 y z
 
 
-class (Add' x y z) => Add x y z
+class (Add' x y z) => Add x y z | x y -> z
 instance (Add' D1 y z) => Add D1 y z
 
 
-- 
GitLab


From a7a892332507704eb618bdb5629d56591a217644 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Tue, 15 Jan 2013 14:14:42 +0000
Subject: [PATCH 003/223] Fix test by removing unnessary (and bogus) fundep

---
 tests/typecheck/should_compile/tc235.hs | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/typecheck/should_compile/tc235.hs b/tests/typecheck/should_compile/tc235.hs
index feeca6a99..53822b341 100644
--- a/tests/typecheck/should_compile/tc235.hs
+++ b/tests/typecheck/should_compile/tc235.hs
@@ -17,7 +17,7 @@ instance FooBar [] Bool Bool where
 instance FooBar Maybe Int Int where
   a = error "urk"
 
-class (Monad m)=>Gr g ep m | g -> ep where 
+class (Monad m)=>Gr g ep m where 
  x:: m Int
  v:: m Int
 
-- 
GitLab


From ad669f11715c58c2864e6498a0d8c7206cc88541 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Tue, 15 Jan 2013 14:17:30 +0000
Subject: [PATCH 004/223] Fix test by adding a fundep on class A, which makes
 the B instance legal again

---
 tests/typecheck/should_fail/T5684.hs | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/typecheck/should_fail/T5684.hs b/tests/typecheck/should_fail/T5684.hs
index a8c72595d..41d3773eb 100755
--- a/tests/typecheck/should_fail/T5684.hs
+++ b/tests/typecheck/should_fail/T5684.hs
@@ -5,7 +5,7 @@ module T5684 where
 class B a b | a -> b where
   op :: a -> b -> ()
   
-class A a
+class A a | -> a
 
 instance A b => B Bool b
 
-- 
GitLab


From ca5fbc2f49c798ab74295b131b7c0e416e26000d Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Tue, 15 Jan 2013 14:37:08 +0000
Subject: [PATCH 005/223] Fix Test by adding a fundep to make the (Concete a b)
 instance legal

---
 tests/indexed-types/should_compile/Gentle.hs | 4 +++-
 1 file changed, 3 insertions(+), 1 deletion(-)

diff --git a/tests/indexed-types/should_compile/Gentle.hs b/tests/indexed-types/should_compile/Gentle.hs
index a32ac798a..6cc1512a1 100644
--- a/tests/indexed-types/should_compile/Gentle.hs
+++ b/tests/indexed-types/should_compile/Gentle.hs
@@ -10,7 +10,9 @@ module FooModule where
 class Concrete a b | a -> b where
 	bar :: a -> String
 
-instance (Show a) => Concrete a b where
+class Wuggle b | -> b  -- To make the Concrete instance work
+
+instance (Show a, Wuggle b) => Concrete a b where
 	bar = error "urk"
 
 wib :: Concrete a b => a -> String
-- 
GitLab


From 56cd7ad3722251d26019766cbda50d5fe19df5a8 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Tue, 15 Jan 2013 14:42:49 +0000
Subject: [PATCH 006/223] Fix test by adding an extra fundep to make the
 (HasSingleton (Maybe a) mp) instance legal

---
 tests/polykinds/T6068.hs     | 4 +++-
 tests/polykinds/T6068.stdout | 3 ++-
 2 files changed, 5 insertions(+), 2 deletions(-)

diff --git a/tests/polykinds/T6068.hs b/tests/polykinds/T6068.hs
index f9b7dc2c9..9c754bd87 100644
--- a/tests/polykinds/T6068.hs
+++ b/tests/polykinds/T6068.hs
@@ -20,7 +20,9 @@ data Existential (p :: KProxy k) =
 class HasSingleton a (kp :: KProxy k) | a -> kp where
   exists :: a -> Existential kp
 
-instance forall a (mp :: KProxy (Maybe ak)). HasSingleton (Maybe a) mp where
+class Floop a b | a -> b
+
+instance forall a (mp :: KProxy (Maybe ak)). Floop a mp => HasSingleton (Maybe a) mp where
   exists Nothing = Exists SNothing
 
 -- instance forall (a ::*) (mp :: KProxy (Maybe ak)). HasSingleton (Maybe ak) (Maybe a) mp where
diff --git a/tests/polykinds/T6068.stdout b/tests/polykinds/T6068.stdout
index 2a6d08de6..bf9528b1f 100644
--- a/tests/polykinds/T6068.stdout
+++ b/tests/polykinds/T6068.stdout
@@ -1 +1,2 @@
-exists Nothing :: Existential (Maybe *) mp
+exists Nothing
+  :: Floop * (KProxy (Maybe *)) a mp => Existential (Maybe *) mp
-- 
GitLab


From a0acdf602fa3013909c257e29c26f144831ef3ac Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Tue, 15 Jan 2013 14:53:57 +0000
Subject: [PATCH 007/223] Make tc226 have -O, so that the unboxing stuff
 happens

---
 tests/typecheck/should_compile/tc226.hs | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/tests/typecheck/should_compile/tc226.hs b/tests/typecheck/should_compile/tc226.hs
index 1e5e28ac5..d9c94c2c4 100644
--- a/tests/typecheck/should_compile/tc226.hs
+++ b/tests/typecheck/should_compile/tc226.hs
@@ -1,7 +1,8 @@
-{-# OPTIONS_GHC -funbox-strict-fields #-}
+{-# OPTIONS_GHC -O -funbox-strict-fields #-}
 
 -- The combination of unboxing and a recursive newtype crashed GHC 6.6.1
 -- Trac #1255
+-- Use -O to force the unboxing to happen
 
 module Foo where
 
-- 
GitLab


From 3c0c3d9c8cf9ea17d003c6629ae978f8dec05989 Mon Sep 17 00:00:00 2001
From: Richard Eisenberg <eir@cis.upenn.edu>
Date: Tue, 15 Jan 2013 17:17:46 -0500
Subject: [PATCH 008/223] Add new test case T7585.

---
 tests/indexed-types/should_compile/T7585.hs | 21 +++++++++++++++++++++
 tests/indexed-types/should_compile/all.T    |  2 +-
 2 files changed, 22 insertions(+), 1 deletion(-)
 create mode 100644 tests/indexed-types/should_compile/T7585.hs

diff --git a/tests/indexed-types/should_compile/T7585.hs b/tests/indexed-types/should_compile/T7585.hs
new file mode 100644
index 000000000..475269c85
--- /dev/null
+++ b/tests/indexed-types/should_compile/T7585.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE GADTs, RankNTypes, KindSignatures, PolyKinds, TypeOperators, DataKinds,
+             TypeFamilies #-}
+
+module Bug where
+
+data SBool :: Bool -> * where
+  SFalse :: SBool False
+  STrue :: SBool True
+
+data SList :: [Bool] -> * where
+  SNil :: SList '[]
+  SCons :: SBool h -> SList t -> SList (h ': t)
+
+type family (a :: k) :==: (b :: k) :: Bool
+type instance where
+  '[] :==: '[] = True
+  (h1 ': t1) :==: (h2 ': t2) = True
+  a :==: b = False
+
+(%==%) :: SList ls1 -> SList ls2 -> SBool (ls1 :==: ls2)
+SNil %==% (SCons _ _) = SFalse
\ No newline at end of file
diff --git a/tests/indexed-types/should_compile/all.T b/tests/indexed-types/should_compile/all.T
index d785e82b8..b8edf95d4 100644
--- a/tests/indexed-types/should_compile/all.T
+++ b/tests/indexed-types/should_compile/all.T
@@ -206,5 +206,5 @@ test('T5591b', normal, compile, [''])
 test('T7280', normal, compile, [''])
 test('T7474', normal, compile, [''])
 test('T7489', normal, compile, [''])
-
+test('T7585', normal, compile, [''])
 
-- 
GitLab


From 38f21bb2258c61af008323aa4603698fa5aa9e34 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Wed, 16 Jan 2013 16:40:30 +0000
Subject: [PATCH 009/223] Add a test for #7299

---
 tests/ghc-e/should_run/Makefile | 3 +++
 tests/ghc-e/should_run/all.T    | 1 +
 2 files changed, 4 insertions(+)

diff --git a/tests/ghc-e/should_run/Makefile b/tests/ghc-e/should_run/Makefile
index 2a7fd0a7a..3596f0262 100644
--- a/tests/ghc-e/should_run/Makefile
+++ b/tests/ghc-e/should_run/Makefile
@@ -27,3 +27,6 @@ ghc-e005:
 3890:
 	'$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e ":main" 3890.hs | cat
 
+T7299:
+	'$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "Control.Concurrent.threadDelay (1000 * 1000)"
+
diff --git a/tests/ghc-e/should_run/all.T b/tests/ghc-e/should_run/all.T
index 60bafdf73..e5a252978 100644
--- a/tests/ghc-e/should_run/all.T
+++ b/tests/ghc-e/should_run/all.T
@@ -13,3 +13,4 @@ test('2228',
      ['$MAKE --no-print-directory -s 2228'])
 test('2636', req_interp, run_command, ['$MAKE --no-print-directory -s 2636'])
 test('3890', req_interp, run_command, ['$MAKE --no-print-directory -s 3890'])
+test('T7299', req_interp, run_command, ['$MAKE --no-print-directory -s T7299'])
-- 
GitLab


From 8dbd01a092885ad732bd78ecdebc526088f85a56 Mon Sep 17 00:00:00 2001
From: Austin Seipp <mad.one@gmail.com>
Date: Sun, 13 Jan 2013 03:41:29 -0600
Subject: [PATCH 010/223] Add better support for .cmm test files.

Fixes Trac #7573.

Signed-off-by: Austin Seipp <mad.one@gmail.com>
---
 driver/testglobals.py | 3 +++
 driver/testlib.py     | 8 +++++++-
 2 files changed, 10 insertions(+), 1 deletion(-)

diff --git a/driver/testglobals.py b/driver/testglobals.py
index 10a110503..500e7f401 100644
--- a/driver/testglobals.py
+++ b/driver/testglobals.py
@@ -237,6 +237,9 @@ class TestOptions:
        self.objc_src   = 0
        self.objcpp_src = 0
 
+       # Does this test use a .cmm file?
+       self.cmm_src    = 0
+
        # Should we put .hi/.o files in a subdirectory?
        self.outputdir = None
 
diff --git a/driver/testlib.py b/driver/testlib.py
index 0332d926e..fd11be184 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -517,6 +517,9 @@ def objc_src( opts ):
 def objcpp_src( opts ):
     opts.objcpp_src = 1;
 
+def cmm_src( opts ):
+    opts.cmm_src = 1;
+
 def outputdir( odir ):
     return lambda opts, d=odir: _outputdir(opts, d)
 
@@ -1205,7 +1208,8 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf,
     # Required by GHC 7.3+, harmless for earlier versions:
     if (getTestOpts().c_src or
         getTestOpts().objc_src or
-        getTestOpts().objcpp_src):
+        getTestOpts().objcpp_src or
+        getTestOpts().cmm_src):
         extra_hc_opts += ' -no-hs-main '
 
     if getTestOpts().compile_cmd_prefix == '':
@@ -2111,6 +2115,8 @@ def add_suffix( name, suffix ):
 def add_hs_lhs_suffix(name):
     if getTestOpts().c_src:
         return add_suffix(name, 'c')
+    elif getTestOpts().cmm_src:
+        return add_suffix(name, 'cmm')
     elif getTestOpts().objc_src:
         return add_suffix(name, 'm')
     elif getTestOpts().objcpp_src:
-- 
GitLab


From 5aae346f6b4fb8c580491221e02df842df1612b0 Mon Sep 17 00:00:00 2001
From: David Terei <davidterei@gmail.com>
Date: Thu, 17 Jan 2013 00:24:38 -0800
Subject: [PATCH 011/223] Test for #7600.

---
 tests/codeGen/should_run/T7600.hs     | 111 ++++++++++++++++++++++++++
 tests/codeGen/should_run/T7600.stdout |   2 +
 tests/codeGen/should_run/T7600_A.hs   |  83 +++++++++++++++++++
 tests/codeGen/should_run/all.T        |   2 +
 4 files changed, 198 insertions(+)
 create mode 100644 tests/codeGen/should_run/T7600.hs
 create mode 100644 tests/codeGen/should_run/T7600.stdout
 create mode 100644 tests/codeGen/should_run/T7600_A.hs

diff --git a/tests/codeGen/should_run/T7600.hs b/tests/codeGen/should_run/T7600.hs
new file mode 100644
index 000000000..9f0e118b4
--- /dev/null
+++ b/tests/codeGen/should_run/T7600.hs
@@ -0,0 +1,111 @@
+-- !!! Bug # 7600.
+-- The LLVM backend can be tricky to get right with floating point constants
+-- and GHC. See Note [LLVM Float Types] in compiler/llvmGen/Llvm/Types.hs for
+-- why this is.
+--
+-- Two issues to watch for (that this bug tries to track):
+--
+-- 1) We need to narrow a double to a float but then expand back out (so that
+-- we end up with the precision of a float but in double precision byte form).
+-- GHC seems to optimize this away for some ways of doing this.
+--
+-- 2) The 'realToFrac' method returns different results at the byte level
+-- depending on if optimisations are on or off. We use the double2float and
+-- float2Double methods instead as they don't suffer from this.
+-- 
+-- Also worth looking at ticket # 3676 about issues with 'realToFrac'.
+module Main (main) where
+
+import T7600_A
+
+-- a fp constant that requires double precision, but we only use a single
+-- precision type.
+-- expected output: float 0x7FF0000000000000
+float_number :: Float
+float_number = 1.82173691287639817263897126389712638972163e+300
+
+-- as above but use double precision so we can represent it.
+-- expected output: double 0x7E45C3163C1ACF96
+double_number :: Double
+double_number = 1.82173691287639817263897126389712638972163e+300
+
+-- Test run
+main :: IO ()
+main = test_run float_number double_number
+
+
+
+-- XXX: We don't run below, but it can be useful to test how the optimizer is
+-- running... the NOINLINE pragmas are needed below generally, but often not
+-- for Bug31_A as the constant is in a different module...
+
+-- -- Test run
+-- test_run' :: Float -> Double -> IO ()
+-- test_run' float_number double_number = do
+--     print $ dToStr double_number
+--     print $ dToStr (widen $ narrow double_number)
+--     print $ dToStr (widen' $ narrow' double_number)
+--     let dd = case double_number of { (D# x) -> x }
+--     print $ dToStr (D# (float2Double# (double2Float# dd)))
+--
+-- -- use standard Haskell functions for type conversion... which are kind of
+-- -- insane (see ticket # 3676) [these fail when -O0 is used...]
+-- {-# NOINLINE narrow #-}
+-- narrow :: Double -> Float
+-- narrow = realToFrac
+-- 
+-- {-# NOINLINE widen #-}
+-- widen :: Float -> Double
+-- widen = realToFrac
+-- 
+-- -- use GHC specific functions which work as expected [work for both -O0 and -O]
+-- {-# NOINLINE narrow' #-}
+-- narrow' :: Double -> Float
+-- narrow' = double2Float
+-- 
+-- {-# NOINLINE widen' #-}
+-- widen' :: Float -> Double
+-- widen' = float2Double
+-- 
+-- doubleToBytes :: Double -> [Int]
+-- doubleToBytes d
+--    = runST (do
+--         arr <- newArray_ ((0::Int),7)
+--         writeArray arr 0 d
+--         arr <- castDoubleToWord8Array arr
+--         i0 <- readArray arr 0
+--         i1 <- readArray arr 1
+--         i2 <- readArray arr 2
+--         i3 <- readArray arr 3
+--         i4 <- readArray arr 4
+--         i5 <- readArray arr 5
+--         i6 <- readArray arr 6
+--         i7 <- readArray arr 7
+--         return (map fromIntegral [i0,i1,i2,i3,i4,i5,i6,i7])
+--      )
+-- 
+-- castFloatToWord8Array :: STUArray s Int Float -> ST s (STUArray s Int Word8)
+-- castFloatToWord8Array = castSTUArray
+-- 
+-- castDoubleToWord8Array :: STUArray s Int Double -> ST s (STUArray s Int Word8)
+-- castDoubleToWord8Array = castSTUArray
+-- 
+-- dToStr :: Double -> String
+-- dToStr d
+--   = let bs     = doubleToBytes d
+--         hex d' = case showHex d' "" of
+--                      []    -> error "dToStr: too few hex digits for float"
+--                      [x]   -> ['0',x]
+--                      [x,y] -> [x,y]
+--                      _     -> error "dToStr: too many hex digits for float"
+-- 
+--         str  = map toUpper $ concat . fixEndian . (map hex) $ bs
+--     in  "0x" ++ str
+-- 
+-- fixEndian :: [a] -> [a]
+-- -- #ifdef WORDS_BIGENDIAN
+-- -- fixEndian = id
+-- -- #else
+-- fixEndian = reverse
+-- -- #endif
+
diff --git a/tests/codeGen/should_run/T7600.stdout b/tests/codeGen/should_run/T7600.stdout
new file mode 100644
index 000000000..d37bad086
--- /dev/null
+++ b/tests/codeGen/should_run/T7600.stdout
@@ -0,0 +1,2 @@
+"0x7E45C3163C1ACF96"
+"0x7FF0000000000000"
diff --git a/tests/codeGen/should_run/T7600_A.hs b/tests/codeGen/should_run/T7600_A.hs
new file mode 100644
index 000000000..52c28cbd8
--- /dev/null
+++ b/tests/codeGen/should_run/T7600_A.hs
@@ -0,0 +1,83 @@
+-- !!! Bug # 7600.
+-- See file T7600 for main description.
+{-# LANGUAGE CPP #-}
+module T7600_A (test_run) where
+
+import Control.Monad.ST
+import Data.Array.Unsafe( castSTUArray )
+import Data.Array.ST hiding( castSTUArray )
+import Data.Char
+import Data.Word
+import Numeric
+
+import GHC.Float
+
+-- Test run
+test_run :: Float -> Double -> IO ()
+test_run float_number double_number = do
+    print $ dToStr double_number
+    -- XXX: Below is the bad code due to changing with optimisation.
+    -- print $ dToStr (widen $ narrow double_number)
+    print $ dToStr (widen' $ narrow' double_number)
+
+-- use standard Haskell functions for type conversion... which are kind of
+-- insane (see ticket # 3676) [these fail when -O0 is used...]
+narrow :: Double -> Float
+{-# NOINLINE narrow #-}
+narrow = realToFrac
+
+widen :: Float -> Double
+{-# NOINLINE widen #-}
+widen = realToFrac
+
+-- use GHC specific functions which work as expected [work for both -O0 and -O]
+narrow' :: Double -> Float
+{-# NOINLINE narrow' #-}
+narrow' = double2Float
+
+widen' :: Float -> Double
+{-# NOINLINE widen' #-}
+widen' = float2Double
+
+doubleToBytes :: Double -> [Int]
+doubleToBytes d
+   = runST (do
+        arr <- newArray_ ((0::Int),7)
+        writeArray arr 0 d
+        arr <- castDoubleToWord8Array arr
+        i0 <- readArray arr 0
+        i1 <- readArray arr 1
+        i2 <- readArray arr 2
+        i3 <- readArray arr 3
+        i4 <- readArray arr 4
+        i5 <- readArray arr 5
+        i6 <- readArray arr 6
+        i7 <- readArray arr 7
+        return (map fromIntegral [i0,i1,i2,i3,i4,i5,i6,i7])
+     )
+
+castFloatToWord8Array :: STUArray s Int Float -> ST s (STUArray s Int Word8)
+castFloatToWord8Array = castSTUArray
+
+castDoubleToWord8Array :: STUArray s Int Double -> ST s (STUArray s Int Word8)
+castDoubleToWord8Array = castSTUArray
+
+dToStr :: Double -> String
+dToStr d
+  = let bs     = doubleToBytes d
+        hex d' = case showHex d' "" of
+                     []    -> error "dToStr: too few hex digits for float"
+                     [x]   -> ['0',x]
+                     [x,y] -> [x,y]
+                     _     -> error "dToStr: too many hex digits for float"
+
+        str  = map toUpper $ concat . fixEndian . (map hex) $ bs
+    in  "0x" ++ str
+
+fixEndian :: [a] -> [a]
+#ifdef WORDS_BIGENDIAN
+fixEndian = id
+#else
+fixEndian = reverse
+#endif
+
diff --git a/tests/codeGen/should_run/all.T b/tests/codeGen/should_run/all.T
index 456f2c2b1..a8c5a0a70 100644
--- a/tests/codeGen/should_run/all.T
+++ b/tests/codeGen/should_run/all.T
@@ -104,3 +104,5 @@ test('Word2Float32', unless_wordsize(32, skip), compile_and_run, [''])
 test('Word2Float64', unless_wordsize(64, skip), compile_and_run, [''])
 
 test('T7361', normal, compile_and_run, [''])
+test('T7600', normal, compile_and_run, [''])
+
-- 
GitLab


From 826c4f6a2c40e14446cf275aed793f95685772d9 Mon Sep 17 00:00:00 2001
From: David Terei <davidterei@gmail.com>
Date: Thu, 17 Jan 2013 01:17:30 -0800
Subject: [PATCH 012/223] update gitignore

---
 .gitignore | 86 ++++++++++++++++++++++++++++++++++++++++++++++++++++++
 1 file changed, 86 insertions(+)

diff --git a/.gitignore b/.gitignore
index d01e08fa4..902d8d89f 100644
--- a/.gitignore
+++ b/.gitignore
@@ -1194,3 +1194,89 @@ tests/rts/T6006
 tests/simplCore/should_run/T5915
 tests/simplCore/should_run/T5920
 tests/simplCore/should_run/T5997
+
+tests/codeGen/should_run/T5900
+tests/codeGen/should_run/T7163
+tests/codeGen/should_run/T7361
+tests/codeGen/should_run/T7600
+tests/codeGen/should_run/Word2Float64
+tests/concurrent/should_run/367
+tests/concurrent/should_run/367_letnoescape
+tests/deSugar/should_run/DsLambdaCase
+tests/deSugar/should_run/DsMultiWayIf
+tests/dph/nbody/dph-nbody-copy-fast
+tests/dph/nbody/dph-nbody-copy-opt
+tests/driver/T7060dump/
+tests/driver/dynamicToo/A001.dyn_hi
+tests/driver/dynamicToo/A001.dyn_o
+tests/driver/dynamicToo/B001.dyn_hi
+tests/driver/dynamicToo/B001.dyn_o
+tests/driver/dynamicToo/C001.dyn_hi
+tests/driver/dynamicToo/C001.dyn_o
+tests/driver/dynamicToo/d001
+tests/driver/dynamicToo/s001
+tests/driver/objc/objc-hi
+tests/driver/objc/objcpp-hi
+tests/driver/recomp012/Foo.hs
+tests/driver/recomp012/Main
+tests/driver/recomp012/Main.hs
+tests/driver/recomp012/MyBool.hs
+tests/ext-core/T7239.hcr
+tests/ffi/should_run/7170
+tests/ffi/should_run/T4012
+tests/ghc-api/T7478/A
+tests/ghc-api/T7478/T7478
+tests/lib/integer/IntegerConversionRules.simpl
+tests/lib/integer/gcdInteger
+tests/mdo/should_fail/mdofail006
+tests/mdo/should_run/mdorun004
+tests/mdo/should_run/mdorun005
+tests/numeric/should_run/T7014
+tests/numeric/should_run/T7014.simpl
+tests/numeric/should_run/T7233
+tests/optasm-log
+tests/optllvm-32-log
+tests/optllvm-log
+tests/parser/should_compile/T7476/Main.imports
+tests/parser/should_compile/T7476/T7476
+tests/parser/should_run/ParserMultiWayIf
+tests/perf/compiler/T5837.comp.stats
+tests/perf/should_run/Conversions
+tests/perf/should_run/Conversions.stats
+tests/perf/should_run/T7257
+tests/perf/should_run/T7257.stats
+tests/perf/should_run/T7436
+tests/perf/should_run/T7436.stats
+tests/perf/should_run/T7507
+tests/plugins/simple-plugin/pkg.plugins01/
+tests/plugins/simple-plugin/pkg.plugins02/
+tests/plugins/simple-plugin/pkg.plugins03/
+tests/rts/7087
+tests/rts/T7037
+tests/rts/T7037_main
+tests/rts/T7040
+tests/rts/T7160
+tests/rts/T7227
+tests/rts/T7227.stat
+tests/safeHaskell/check/pkg01/pdb.ImpSafeOnly01/
+tests/safeHaskell/check/pkg01/pdb.ImpSafeOnly02/
+tests/safeHaskell/check/pkg01/pdb.ImpSafeOnly03/
+tests/safeHaskell/check/pkg01/pdb.ImpSafeOnly04/
+tests/safeHaskell/check/pkg01/pdb.ImpSafeOnly05/
+tests/safeHaskell/check/pkg01/pdb.ImpSafeOnly06/
+tests/safeHaskell/check/pkg01/pdb.ImpSafeOnly07/
+tests/safeHaskell/check/pkg01/pdb.ImpSafeOnly08/
+tests/safeHaskell/check/pkg01/pdb.ImpSafeOnly09/
+tests/safeHaskell/check/pkg01/pdb.ImpSafeOnly10/
+tests/safeHaskell/check/pkg01/pdb.safePkg01/
+tests/simplCore/should_compile/T4138.simpl
+tests/simplCore/should_run/T7101
+tests/th/T5555
+tests/th/T7064
+tests/th/TH_StringPrimL
+tests/typecheck/should_run/T5751
+tests/typecheck/should_run/T5913
+tests/typecheck/should_run/T6117
+tests/typecheck/should_run/T7023
+tests/typecheck/should_run/T7126
+
-- 
GitLab


From f93760456692e008b2f4e51d69b6c5efe6c848d0 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 17 Jan 2013 13:51:15 +0000
Subject: [PATCH 013/223] Fix simplrun010 test

Compiler now (correctly) does not eta reduce an infinite loop,
so I had to adjust the test a bit.
---
 tests/simplCore/should_run/all.T              |  4 ++--
 tests/simplCore/should_run/simplrun010.hs     | 15 ++++++++++++++-
 tests/simplCore/should_run/simplrun010.stderr |  4 +++-
 3 files changed, 19 insertions(+), 4 deletions(-)

diff --git a/tests/simplCore/should_run/all.T b/tests/simplCore/should_run/all.T
index fc59a0ac2..40c553fe8 100644
--- a/tests/simplCore/should_run/all.T
+++ b/tests/simplCore/should_run/all.T
@@ -18,8 +18,8 @@ test('simplrun005', normal, compile_and_run, [''])
 test('simplrun007', normal, compile_and_run, [''])
 test('simplrun008', normal, compile_and_run, [''])
 test('simplrun009', normal, compile_and_run, [''])
-test('simplrun010', composes([extra_run_opts('24 16 8'),
-                              exit_code(1)])
+test('simplrun010', composes([extra_run_opts('24 16 8 +RTS -M10m -RTS'),
+                              exit_code(251)])
                   , compile_and_run, [''])
 
 # Really we'd like to run T2486 too, to check that its
diff --git a/tests/simplCore/should_run/simplrun010.hs b/tests/simplCore/should_run/simplrun010.hs
index 6cc79f0d0..eeeb48281 100644
--- a/tests/simplCore/should_run/simplrun010.hs
+++ b/tests/simplCore/should_run/simplrun010.hs
@@ -1,6 +1,8 @@
 {-# LANGUAGE ForeignFunctionInterface, MagicHash, UnboxedTuples #-}
 
 -- From trac #1947
+-- Should fail with heap exhaustion
+-- See notes below with "Infinite loop here".
 
 module Main(main) where
 
@@ -244,9 +246,20 @@ f20 v1 v2 =
                        prelude_error
                          (skipCAF realWorld# (str_ "Prelude.read: ambiguous parse"))
 
+-- Infinite loop here.  It was originally:
+-- f34 v1 v2 v3 =
+--    let v336 = f34 v1 v2 v3
+--    in v336
+--
+-- But that now (correctly) just makes a non-allocating infinite loop
+-- instead of (incorrectly) eta-reducing to f34 = f34.
+-- So I've changed to an infinite, allocating loop, which makes
+-- the heap get exhausted.
 f34 v1 v2 v3 =
-    let v336 = f34 v1 v2 v3
+  if abs v2 < 1000 then 
+    let v336 = f34 (v1+1) (-v2) v3
     in v336
+  else if v2 == 2000 then 0 else v1
 
 f38 v1 v2 =
     case v1 of
diff --git a/tests/simplCore/should_run/simplrun010.stderr b/tests/simplCore/should_run/simplrun010.stderr
index 57647f1f9..a2a586d00 100644
--- a/tests/simplCore/should_run/simplrun010.stderr
+++ b/tests/simplCore/should_run/simplrun010.stderr
@@ -1 +1,3 @@
-simplrun010: <<loop>>
+simplrun010: Heap exhausted;
+Current maximum heap size is 10485760 bytes (10 MB);
+use `+RTS -M<size>' to increase it.
-- 
GitLab


From c85582dc17711c352ae3befbf8a44074ee1d7618 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 17 Jan 2013 13:51:53 +0000
Subject: [PATCH 014/223] Adjust debug output for different syntax of
 strictness annotations

---
 tests/deSugar/should_compile/T2431.stderr         |  2 +-
 tests/simplCore/should_compile/EvalTest.stdout    |  2 +-
 tests/simplCore/should_compile/T3717.stderr       |  4 ++--
 tests/simplCore/should_compile/T3772.stdout       |  4 ++--
 tests/simplCore/should_compile/T4908.stderr       |  6 +++---
 tests/simplCore/should_compile/T4930.stderr       |  4 ++--
 tests/simplCore/should_compile/T7360.stderr       |  6 +++---
 tests/simplCore/should_compile/spec-inline.stderr | 12 ++++++------
 8 files changed, 20 insertions(+), 20 deletions(-)

diff --git a/tests/deSugar/should_compile/T2431.stderr b/tests/deSugar/should_compile/T2431.stderr
index b33871140..f8c5a0ac9 100644
--- a/tests/deSugar/should_compile/T2431.stderr
+++ b/tests/deSugar/should_compile/T2431.stderr
@@ -14,7 +14,7 @@ T2431.$WRefl = \ (@ a) -> T2431.Refl @ a @ a @~ <a>
 
 T2431.absurd
   :: forall a. (GHC.Types.Int T2431.:~: GHC.Types.Bool) -> a
-[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType Tb]
+[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType <L,U>b]
 T2431.absurd =
   \ (@ a) (x :: GHC.Types.Int T2431.:~: GHC.Types.Bool) ->
     case x of _ { }
diff --git a/tests/simplCore/should_compile/EvalTest.stdout b/tests/simplCore/should_compile/EvalTest.stdout
index 5f32ee81d..30c7ea4ef 100644
--- a/tests/simplCore/should_compile/EvalTest.stdout
+++ b/tests/simplCore/should_compile/EvalTest.stdout
@@ -1 +1 @@
-rght [Dmd=Just S] :: EvalTest.AList a
+rght [Dmd=<S,U>] :: EvalTest.AList a
diff --git a/tests/simplCore/should_compile/T3717.stderr b/tests/simplCore/should_compile/T3717.stderr
index 56824f516..d66812280 100644
--- a/tests/simplCore/should_compile/T3717.stderr
+++ b/tests/simplCore/should_compile/T3717.stderr
@@ -4,7 +4,7 @@ Result size of Tidy Core = {terms: 19, types: 10, coercions: 0}
 
 Rec {
 T3717.$wfoo [Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int#
-[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType L]
+[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType <S,U>]
 T3717.$wfoo =
   \ (ww :: GHC.Prim.Int#) ->
     case ww of ds {
@@ -17,7 +17,7 @@ T3717.foo [InlPrag=INLINE[0]] :: GHC.Types.Int -> GHC.Types.Int
 [GblId,
  Arity=1,
  Caf=NoCafRefs,
- Str=DmdType U(L)m,
+ Str=DmdType <S(S),U(U)>m,
  Unf=Unf{Src=Worker=T3717.$wfoo, TopLvl=True, Arity=1, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
diff --git a/tests/simplCore/should_compile/T3772.stdout b/tests/simplCore/should_compile/T3772.stdout
index 13665596f..4f4d60018 100644
--- a/tests/simplCore/should_compile/T3772.stdout
+++ b/tests/simplCore/should_compile/T3772.stdout
@@ -4,7 +4,7 @@ Result size of Tidy Core = {terms: 23, types: 10, coercions: 0}
 
 Rec {
 xs :: GHC.Prim.Int# -> ()
-[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType L]
+[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType <L,U>]
 xs =
   \ (m :: GHC.Prim.Int#) ->
     case GHC.Prim.<=# m 1 of _ {
@@ -14,7 +14,7 @@ xs =
 end Rec }
 
 T3772.foo [InlPrag=NOINLINE] :: GHC.Types.Int -> ()
-[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType U(L)]
+[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType <S,U(U)>]
 T3772.foo =
   \ (n :: GHC.Types.Int) ->
     case n of _ { GHC.Types.I# n# ->
diff --git a/tests/simplCore/should_compile/T4908.stderr b/tests/simplCore/should_compile/T4908.stderr
index 4f2c5f204..8f6952b2c 100644
--- a/tests/simplCore/should_compile/T4908.stderr
+++ b/tests/simplCore/should_compile/T4908.stderr
@@ -6,7 +6,7 @@ Rec {
 T4908.f_$s$wf [Occ=LoopBreaker]
   :: GHC.Prim.Int#
      -> GHC.Types.Int -> GHC.Prim.Int# -> GHC.Types.Bool
-[GblId, Arity=3, Caf=NoCafRefs, Str=DmdType LLL]
+[GblId, Arity=3, Caf=NoCafRefs, Str=DmdType <S,U><L,U><L,U>]
 T4908.f_$s$wf =
   \ (sc :: GHC.Prim.Int#)
     (sc1 :: GHC.Types.Int)
@@ -27,7 +27,7 @@ T4908.$wf
 [GblId,
  Arity=2,
  Caf=NoCafRefs,
- Str=DmdType LL,
+ Str=DmdType <S,U><L,U(UU(U))>,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=2, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=IF_ARGS [30 20] 101 20}]
@@ -52,7 +52,7 @@ T4908.f [InlPrag=INLINE[0]]
 [GblId,
  Arity=2,
  Caf=NoCafRefs,
- Str=DmdType U(L)L,
+ Str=DmdType <S(S),U(U)><L,U(UU(U))>,
  Unf=Unf{Src=Worker=T4908.$wf, TopLvl=True, Arity=2, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
diff --git a/tests/simplCore/should_compile/T4930.stderr b/tests/simplCore/should_compile/T4930.stderr
index 61c2f5afb..fd3b72da2 100644
--- a/tests/simplCore/should_compile/T4930.stderr
+++ b/tests/simplCore/should_compile/T4930.stderr
@@ -3,7 +3,7 @@
 Result size of Tidy Core = {terms: 20, types: 10, coercions: 0}
 
 lvl :: [GHC.Types.Char]
-[GblId]
+[GblId, Str=DmdType]
 lvl = GHC.CString.unpackCString# "Too small"#
 
 T4930.foo1 :: GHC.Types.Int
@@ -13,7 +13,7 @@ T4930.foo1 = GHC.Err.error @ GHC.Types.Int lvl
 T4930.foo :: GHC.Types.Int -> GHC.Types.Int
 [GblId,
  Arity=1,
- Str=DmdType U(L)m,
+ Str=DmdType <S,U(U)>m,
  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
diff --git a/tests/simplCore/should_compile/T7360.stderr b/tests/simplCore/should_compile/T7360.stderr
index 0c5bb899e..f8d0e9179 100644
--- a/tests/simplCore/should_compile/T7360.stderr
+++ b/tests/simplCore/should_compile/T7360.stderr
@@ -6,7 +6,7 @@ T7360.$WFoo3 [InlPrag=INLINE] :: GHC.Types.Int -> T7360.Foo
 [GblId[DataConWrapper],
  Arity=1,
  Caf=NoCafRefs,
- Str=DmdType S,
+ Str=DmdType <S,U>,
  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=False,boring_ok=False)
@@ -17,7 +17,7 @@ T7360.$WFoo3 =
     case dt of dt { __DEFAULT -> T7360.Foo3 dt }
 
 T7360.fun1 [InlPrag=NOINLINE] :: T7360.Foo -> ()
-[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType S]
+[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType <S,U>]
 T7360.fun1 =
   \ (x :: T7360.Foo) -> case x of _ { __DEFAULT -> GHC.Tuple.() }
 
@@ -32,7 +32,7 @@ T7360.fun3 = T7360.fun1 T7360.Foo1
 T7360.fun2 :: forall a. [a] -> ((), GHC.Types.Int)
 [GblId,
  Arity=1,
- Str=DmdType Lm,
+ Str=DmdType <L,U>m,
  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
diff --git a/tests/simplCore/should_compile/spec-inline.stderr b/tests/simplCore/should_compile/spec-inline.stderr
index 2cff9e307..0d7172dd6 100644
--- a/tests/simplCore/should_compile/spec-inline.stderr
+++ b/tests/simplCore/should_compile/spec-inline.stderr
@@ -11,11 +11,11 @@ Roman.foo3 =
 Rec {
 Roman.foo_$s$wgo [Occ=LoopBreaker]
   :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
-[GblId, Arity=2, Caf=NoCafRefs, Str=DmdType LL]
+[GblId, Arity=2, Caf=NoCafRefs, Str=DmdType <L,U><L,U>]
 Roman.foo_$s$wgo =
   \ (sc :: GHC.Prim.Int#) (sc1 :: GHC.Prim.Int#) ->
     let {
-      a [Dmd=Just L] :: GHC.Prim.Int#
+      a :: GHC.Prim.Int#
       [LclId, Str=DmdType]
       a =
         GHC.Prim.+#
@@ -44,7 +44,7 @@ Roman.$wgo
      -> Data.Maybe.Maybe GHC.Types.Int -> GHC.Prim.Int#
 [GblId,
  Arity=2,
- Str=DmdType SS,
+ Str=DmdType <S,U><S,U>,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=2, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=IF_ARGS [60 30] 253 0}]
@@ -56,7 +56,7 @@ Roman.$wgo =
       Data.Maybe.Just x ->
         case x of _ { GHC.Types.I# ipv ->
         let {
-          a [Dmd=Just L] :: GHC.Prim.Int#
+          a :: GHC.Prim.Int#
           [LclId, Str=DmdType]
           a =
             GHC.Prim.+#
@@ -92,7 +92,7 @@ Roman.foo_go [InlPrag=INLINE[0]]
      -> Data.Maybe.Maybe GHC.Types.Int -> GHC.Types.Int
 [GblId,
  Arity=2,
- Str=DmdType SSm,
+ Str=DmdType <S,U><S,U>m,
  Unf=Unf{Src=Worker=Roman.$wgo, TopLvl=True, Arity=2, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
@@ -126,7 +126,7 @@ Roman.foo :: GHC.Types.Int -> GHC.Types.Int
 [GblId,
  Arity=1,
  Caf=NoCafRefs,
- Str=DmdType S(A)m,
+ Str=DmdType <S,U>m,
  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
-- 
GitLab


From 52234dfedb9ad07585271f33513fb2c9e5012e1a Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 17 Jan 2013 13:52:35 +0000
Subject: [PATCH 015/223] Adjust performance bounds slightly

---
 tests/perf/compiler/all.T   | 13 ++++++++++---
 tests/perf/haddock/all.T    |  3 ++-
 tests/perf/should_run/all.T |  7 ++++---
 3 files changed, 16 insertions(+), 7 deletions(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 3ff9f60d0..09cdb0111 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -39,7 +39,7 @@ test('T1969',
                         # 2012-10-08:     303930948 (x86/Linux, new codegen)
                         # 2012-10-29:     298921816 (x86/Windows; increased range to 5%
       if_wordsize(64,
-          compiler_stats_range_field('bytes allocated', 658786936, 1)),
+          compiler_stats_range_field('bytes allocated', 658786936, 5)),
                         # 17/11/2009:     434,845,560 (amd64/Linux)
                         # 08/12/2009:     459,776,680 (amd64/Linux)
                         # 17/05/2010:     519,377,728 (amd64/Linux)
@@ -56,7 +56,10 @@ test('T1969',
                         #                 (^ -fPIC turned off again)
                         # 12/11/2012:     658,786,936 (amd64/Linux)
                         #                 ( UNKNOWN REASON )
+                        # 17/1/13:        667,160,192 (x86_64/Linux)
+                        #                 (new demand analyser)
       only_ways(['normal']),
+
       extra_hc_opts('-dcore-lint -static')
           # Leave -dcore-lint on for this one test, so that we have something
           # that will catch a regression in -dcore-lint performance.
@@ -201,9 +204,13 @@ test('T5030',
           compiler_stats_range_field('bytes allocated', 259547660, 10)),
                      # previous:    196457520
                      # 2012-10-08:  259547660 (x86/Linux, new codegen)
-      # expected value: 346750856 (amd64/Linux):
+
       if_wordsize(64,
-          compiler_stats_range_field('bytes allocated', 530000000, 10)),
+          compiler_stats_range_field('bytes allocated', 602993184, 10)),
+            # Previously 530000000 (+/- 10%)
+            # 17/1/13:       602,993,184  (x86_64/Linux)
+            #                (new demand analyser)
+   
        only_ways(['normal'])
       ],
      compile,
diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T
index e432342cf..5104ea9d1 100644
--- a/tests/perf/haddock/all.T
+++ b/tests/perf/haddock/all.T
@@ -21,10 +21,11 @@ test('haddock.base',
           stats_range_field('max_bytes_used', 45574928, 1))
                                 # 2012-08-14: 45574928 (x86/OSX)
      ,if_wordsize(64,
-          stats_range_field('bytes allocated', 5902601224, 2))
+          stats_range_field('bytes allocated', 6064874536, 2))
                                  # 2012-08-14: 5920822352 (amd64/Linux)
                                  # 2012-09-20: 5829972376 (amd64/Linux)
                                  # 2012-10-08: 5902601224 (amd64/Linux)
+                                 # 2013-01-17: 6064874536 (x86_64/Linux)
      ,if_wordsize(32,
           stats_range_field('bytes allocated', 2955470952, 1))
                                  # 2012-08-14: 3046487920 (x86/OSX)
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 08ff2308a..cdb8852af 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -227,9 +227,10 @@ test('T5536',
                                              1250000000)),
                            # expected value: 1246287228 (i386/Linux)
       if_wordsize(64,
-          stats_num_field('bytes allocated', 2480000000,
-                                             2510000000)),
-                           # expected value: 2492589480 (amd64/Linux)
+          stats_range_field('bytes allocated', 892399040, 5),
+                           # expected value: 2,492,589,480 (amd64/Linux)
+                           # 17/1/13:          892,399,040 (x86_64/Linux)
+                           #                   (new demand analyser)
      extra_clean(['T5536.data']),
      ignore_output,
      only_ways(['normal'])
-- 
GitLab


From 98fee92f15c72f57ca2d1ce71cf22ebb7dd8d23d Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 17 Jan 2013 14:22:09 +0000
Subject: [PATCH 016/223] arith005(ghci) is broken on OS X x86 (#7043)

---
 tests/numeric/should_run/all.T | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/numeric/should_run/all.T b/tests/numeric/should_run/all.T
index ff19507ab..c5cfc8cca 100644
--- a/tests/numeric/should_run/all.T
+++ b/tests/numeric/should_run/all.T
@@ -7,7 +7,7 @@ test('arith001', normal, compile_and_run, [''])
 test('arith002', normal, compile_and_run, [''])
 test('arith003', normal, compile_and_run, [''])
 test('arith004', normal, compile_and_run, [''])
-test('arith005', normal, compile_and_run, [''])
+test('arith005', if_platform('i386-apple-darwin', expect_broken_for(7043, 'ghci')), compile_and_run, [''])
 test('arith006', normal, compile_and_run, [''])
 test('arith007', normal, compile_and_run, [''])
 
-- 
GitLab


From 0e5e3b99f6c354a7bf286c661cc9d7b5bbc0e6cf Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Fri, 18 Jan 2013 14:49:00 +0000
Subject: [PATCH 017/223] Output wibble

---
 tests/simplCore/should_compile/T4201.stdout | 6 +++---
 1 file changed, 3 insertions(+), 3 deletions(-)

diff --git a/tests/simplCore/should_compile/T4201.stdout b/tests/simplCore/should_compile/T4201.stdout
index c3b7e8d26..9f3c2acde 100644
--- a/tests/simplCore/should_compile/T4201.stdout
+++ b/tests/simplCore/should_compile/T4201.stdout
@@ -1,3 +1,3 @@
-       Unfolding: (Eta.bof
-                     `cast`
-                   (Sym (Eta.NTCo:Foo[0]) -> Refl Eta.T)) -}
+    {- Arity: 1, HasNoCafRefs, Strictness: <S,U>m,
+       Unfolding: InlineRule (0, True, True)
+                  Eta.bof `cast` (Sym (Eta.NTCo:Foo[0]) -> Refl Eta.T) -}
-- 
GitLab


From 311f56074ffc9007bc96e4a040e42960fae41e2f Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Fri, 18 Jan 2013 17:30:25 +0000
Subject: [PATCH 018/223] Test Trac #7594

---
 tests/polykinds/T7594.hs     | 27 +++++++++++++++++++++++++++
 tests/polykinds/T7594.stderr | 19 +++++++++++++++++++
 tests/polykinds/all.T        |  1 +
 3 files changed, 47 insertions(+)
 create mode 100644 tests/polykinds/T7594.hs
 create mode 100644 tests/polykinds/T7594.stderr

diff --git a/tests/polykinds/T7594.hs b/tests/polykinds/T7594.hs
new file mode 100644
index 000000000..89e749ce3
--- /dev/null
+++ b/tests/polykinds/T7594.hs
@@ -0,0 +1,27 @@
+{-# LANGUAGE FlexibleInstances     #-}
+{-# LANGUAGE UndecidableInstances  #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE KindSignatures        #-}
+{-# LANGUAGE TypeOperators         #-}
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE GADTs           #-}
+{-# LANGUAGE Rank2Types      #-}
+module T7594 where
+
+import GHC.Prim (Constraint)
+
+class    (c1 t, c2 t) => (:&:) (c1 :: * -> Constraint) (c2 :: * -> Constraint) (t :: *)
+instance (c1 t, c2 t) => (:&:) c1 c2 t
+
+data ColD c where
+  ColD :: (c a) => a -> ColD c
+
+app :: (forall a. (c a) => a -> b) -> ColD c -> b
+app f (ColD x) = f x
+
+q :: ColD (Show :&: Real)
+q = ColD (1.2 :: Double)
+
+bar = app print q
+
+
diff --git a/tests/polykinds/T7594.stderr b/tests/polykinds/T7594.stderr
new file mode 100644
index 000000000..4be0b0a18
--- /dev/null
+++ b/tests/polykinds/T7594.stderr
@@ -0,0 +1,19 @@
+h0
+h1
+h2
+
+T7594.hs:25:11:
+    Couldn't match type `b' with `IO ()'
+      `b' is untouchable
+        inside the constraints ((:&:) Show Real a)
+        bound by a type expected by the context:
+                   (:&:) Show Real a => a -> b
+        at T7594.hs:25:7-17
+      `b' is a rigid type variable bound by
+          the inferred type of bar :: b at T7594.hs:25:1
+    Expected type: a -> b
+      Actual type: a -> IO ()
+    Relevant bindings include bar :: b (bound at T7594.hs:25:1)
+    In the first argument of `app', namely `print'
+    In the expression: app print q
+    In an equation for `bar': bar = app print q
diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T
index 99f8424fa..d84048f1c 100644
--- a/tests/polykinds/all.T
+++ b/tests/polykinds/all.T
@@ -82,3 +82,4 @@ test('T7438', normal, run_command, ['$MAKE -s --no-print-directory T7438'])
 test('T7404', normal, compile_fail,[''])
 test('T7502', normal, compile,[''])
 test('T7488', normal, compile,[''])
+test('T7594', normal, compile_fail,[''])
-- 
GitLab


From ea58ea55f3cdc5682be6e25743f4858b6506a562 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Mon, 21 Jan 2013 09:58:13 +0000
Subject: [PATCH 019/223] Add missing paren

---
 tests/perf/should_run/all.T | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index cdb8852af..d7fe600f5 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -227,7 +227,7 @@ test('T5536',
                                              1250000000)),
                            # expected value: 1246287228 (i386/Linux)
       if_wordsize(64,
-          stats_range_field('bytes allocated', 892399040, 5),
+          stats_range_field('bytes allocated', 892399040, 5)),
                            # expected value: 2,492,589,480 (amd64/Linux)
                            # 17/1/13:          892,399,040 (x86_64/Linux)
                            #                   (new demand analyser)
-- 
GitLab


From 0eab86e6b7d01b5968d3a9a87784dd38ccb18446 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Tue, 22 Jan 2013 18:58:50 +0000
Subject: [PATCH 020/223] Add a test for #1133

---
 tests/deriving/should_compile/Makefile      | 6 ++++++
 tests/deriving/should_compile/T1133.hs      | 8 ++++++++
 tests/deriving/should_compile/T1133.hs-boot | 4 ++++
 tests/deriving/should_compile/all.T         | 4 ++++
 4 files changed, 22 insertions(+)
 create mode 100644 tests/deriving/should_compile/T1133.hs
 create mode 100644 tests/deriving/should_compile/T1133.hs-boot

diff --git a/tests/deriving/should_compile/Makefile b/tests/deriving/should_compile/Makefile
index 9101fbd40..666f7a7e9 100644
--- a/tests/deriving/should_compile/Makefile
+++ b/tests/deriving/should_compile/Makefile
@@ -1,3 +1,9 @@
 TOP=../../..
 include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk
+
+.PHONY: T1133
+T1133:
+	$(TEST_HC) $(TEST_HC_OPTS) -c T1133.hs-boot
+	$(TEST_HC) $(TEST_HC_OPTS) -c T1133.hs
+
diff --git a/tests/deriving/should_compile/T1133.hs b/tests/deriving/should_compile/T1133.hs
new file mode 100644
index 000000000..5d471d1f7
--- /dev/null
+++ b/tests/deriving/should_compile/T1133.hs
@@ -0,0 +1,8 @@
+
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+
+module T1133 where
+
+import {-# SOURCE #-} T1133
+
+newtype X = X Int deriving Enum
diff --git a/tests/deriving/should_compile/T1133.hs-boot b/tests/deriving/should_compile/T1133.hs-boot
new file mode 100644
index 000000000..520a2c0af
--- /dev/null
+++ b/tests/deriving/should_compile/T1133.hs-boot
@@ -0,0 +1,4 @@
+
+module T1133 where
+
+newtype X = X Int
diff --git a/tests/deriving/should_compile/all.T b/tests/deriving/should_compile/all.T
index 11a10b629..6fbe38331 100644
--- a/tests/deriving/should_compile/all.T
+++ b/tests/deriving/should_compile/all.T
@@ -31,3 +31,7 @@ test('drv-functor1', normal, compile, [''])
 test('drv-functor2', normal, compile, [''])
 test('drv-foldable-traversable1', normal, compile, [''])
 test('T6031', extra_clean(['T6031a.o', 'T6031a.hi']), multimod_compile, ['T6031', '-v0'])
+test('T1133',
+     extra_clean(['T1133.o-boot', 'T1133.hi-boot']),
+     run_command,
+     ['$MAKE --no-print-directory -s T1133'])
-- 
GitLab


From 39af698abb1831eb3d1ff405dd5c53bb57ad6f99 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Tue, 22 Jan 2013 19:02:56 +0000
Subject: [PATCH 021/223] Add another test for #1133

---
 tests/deriving/should_fail/Makefile       | 5 +++++
 tests/deriving/should_fail/T1133A.hs      | 6 ++++++
 tests/deriving/should_fail/T1133A.hs-boot | 4 ++++
 tests/deriving/should_fail/T1133A.stderr  | 7 +++++++
 tests/deriving/should_fail/all.T          | 5 ++++-
 5 files changed, 26 insertions(+), 1 deletion(-)
 create mode 100644 tests/deriving/should_fail/T1133A.hs
 create mode 100644 tests/deriving/should_fail/T1133A.hs-boot
 create mode 100644 tests/deriving/should_fail/T1133A.stderr

diff --git a/tests/deriving/should_fail/Makefile b/tests/deriving/should_fail/Makefile
index 0f0995d29..f9f554d5d 100644
--- a/tests/deriving/should_fail/Makefile
+++ b/tests/deriving/should_fail/Makefile
@@ -6,3 +6,8 @@ drvfail016:
 	$(RM) -f drvfail016.hi-boot drvfail016.o-boot
 	'$(TEST_HC)' $(TEST_HC_OPTS) -XGeneralizedNewtypeDeriving -c drvfail016.hs-boot; echo $$?
 
+.PHONY: T1133A
+T1133A:
+	$(TEST_HC) $(TEST_HC_OPTS) -c T1133A.hs-boot
+	-$(TEST_HC) $(TEST_HC_OPTS) -c T1133A.hs
+
diff --git a/tests/deriving/should_fail/T1133A.hs b/tests/deriving/should_fail/T1133A.hs
new file mode 100644
index 000000000..b5950ea1f
--- /dev/null
+++ b/tests/deriving/should_fail/T1133A.hs
@@ -0,0 +1,6 @@
+
+module T1133A where
+
+import {-# SOURCE #-} T1133A
+
+newtype X = X Int deriving Enum
diff --git a/tests/deriving/should_fail/T1133A.hs-boot b/tests/deriving/should_fail/T1133A.hs-boot
new file mode 100644
index 000000000..da89ec0fe
--- /dev/null
+++ b/tests/deriving/should_fail/T1133A.hs-boot
@@ -0,0 +1,4 @@
+
+module T1133A where
+
+newtype X = X Int
diff --git a/tests/deriving/should_fail/T1133A.stderr b/tests/deriving/should_fail/T1133A.stderr
new file mode 100644
index 000000000..734081ede
--- /dev/null
+++ b/tests/deriving/should_fail/T1133A.stderr
@@ -0,0 +1,7 @@
+
+T1133A.hs:6:28:
+    Can't make a derived instance of `Enum X':
+      `X' must be an enumeration type
+      (an enumeration consists of one or more nullary, non-GADT constructors)
+      Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension
+    In the newtype declaration for `X'
diff --git a/tests/deriving/should_fail/all.T b/tests/deriving/should_fail/all.T
index 5ddb2bd37..5fface82b 100644
--- a/tests/deriving/should_fail/all.T
+++ b/tests/deriving/should_fail/all.T
@@ -36,4 +36,7 @@ test('T5287', normal, compile_fail, [''])
 test('T5478', normal, compile_fail, [''])
 test('T5686', normal, compile_fail, [''])
 test('T5922', normal, compile_fail, [''])
-
+test('T1133A',
+     extra_clean(['T1133A.o-boot', 'T1133A.hi-boot']),
+     run_command,
+     ['$MAKE --no-print-directory -s T1133A'])
-- 
GitLab


From a97083aa456ca1bdb9239e8be77bd7a90b7103ea Mon Sep 17 00:00:00 2001
From: Austin Seipp <mad.one@gmail.com>
Date: Sun, 13 Jan 2013 03:51:36 -0600
Subject: [PATCH 022/223] Test for Trac #7571.

Signed-off-by: David Terei <davidterei@gmail.com>
---
 tests/llvm/should_compile/T7571.cmm | 11 +++++++++++
 tests/llvm/should_compile/all.T     |  2 +-
 2 files changed, 12 insertions(+), 1 deletion(-)
 create mode 100644 tests/llvm/should_compile/T7571.cmm

diff --git a/tests/llvm/should_compile/T7571.cmm b/tests/llvm/should_compile/T7571.cmm
new file mode 100644
index 000000000..d4e89d5ad
--- /dev/null
+++ b/tests/llvm/should_compile/T7571.cmm
@@ -0,0 +1,11 @@
+#include "Cmm.h"
+
+testLiteralBranch (W_ dst, W_ src)
+{
+  if (1) {
+    prim %memcpy(dst, src, 1024, 4);
+  } else {
+    prim %memcpy(dst, src, 512, 8);
+  }
+  return ();
+}
diff --git a/tests/llvm/should_compile/all.T b/tests/llvm/should_compile/all.T
index 29e5ae101..d0ce873a3 100644
--- a/tests/llvm/should_compile/all.T
+++ b/tests/llvm/should_compile/all.T
@@ -10,4 +10,4 @@ test('5054_2', reqlib('hmatrix'), compile, ['-package hmatrix'])
 test('5486', normal, compile, [''])
 test('5681', normal, compile, [''])
 test('6158', [reqlib('vector'), reqlib('primitive')], compile, ['-package vector -package primitive'])
-
+test('T7571', cmm_src, compile, [''])
-- 
GitLab


From 7a3ed1d2afac17097a3588e9d29c22f40635364f Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Tue, 22 Jan 2013 23:40:34 +0000
Subject: [PATCH 023/223] Remove a stray colon from the framework fail messages

---
 driver/testlib.py | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index fd11be184..ba03eba4a 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -919,7 +919,7 @@ def skiptest (name, way):
 
 def framework_fail( name, way, reason ):
     full_name = name + '(' + way + ')'
-    print '*** framework failure for', full_name, reason, ':'
+    print '*** framework failure for', full_name, reason
     t.n_framework_failures = t.n_framework_failures + 1
     if name in t.framework_failures:
         t.framework_failures[name].append(way)
-- 
GitLab


From df8b626a4d6a91a21a2fee4dde26d35c2ab12dda Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Tue, 22 Jan 2013 23:44:31 +0000
Subject: [PATCH 024/223] Add a (currently very permissive) test name check

We now get a framework failure if a test name doesn't match
^[a-zA-Z0-9][a-zA-Z0-9._/-]*$
---
 driver/testlib.py | 2 ++
 1 file changed, 2 insertions(+)

diff --git a/driver/testlib.py b/driver/testlib.py
index ba03eba4a..c265350ca 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -645,6 +645,8 @@ def test (name, setup, func, args):
     global allTestNames
     if name in allTestNames:
         framework_fail(name, 'duplicate', 'There are multiple tests with this name')
+    if not re.match('^[a-zA-Z0-9][a-zA-Z0-9._/-]*$', name):
+        framework_fail(name, 'bad_name', 'This test has an invalid name')
     myTestOpts = copy.copy(thisdir_testopts)
 
     if type(setup) is types.ListType:
-- 
GitLab


From 53c7085ea1549532ffda281fa13b1569791f3fd6 Mon Sep 17 00:00:00 2001
From: David Terei <davidterei@gmail.com>
Date: Tue, 22 Jan 2013 23:02:36 -0800
Subject: [PATCH 025/223] Add test for T7575.

---
 tests/llvm/should_compile/T7575.hs | 16 ++++++++++++++++
 tests/llvm/should_compile/all.T    |  1 +
 2 files changed, 17 insertions(+)
 create mode 100644 tests/llvm/should_compile/T7575.hs

diff --git a/tests/llvm/should_compile/T7575.hs b/tests/llvm/should_compile/T7575.hs
new file mode 100644
index 000000000..78b0bd29a
--- /dev/null
+++ b/tests/llvm/should_compile/T7575.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE MagicHash, UnliftedFFITypes #-}
+module T7575 where
+
+import GHC.Prim
+import GHC.Word
+import GHC.Types
+
+foreign import ccall unsafe "hs_eqWord64" dummy_eqWord64# :: Word64# -> Word64# -> Bool
+
+check :: Word64 -> Word64 -> Bool
+check (W64# x#) (W64# y#) = dummy_eqWord64# x# y#
+
+check2 :: Word64 -> Bool
+check2 x = check x 0
+
diff --git a/tests/llvm/should_compile/all.T b/tests/llvm/should_compile/all.T
index d0ce873a3..b2d09ce00 100644
--- a/tests/llvm/should_compile/all.T
+++ b/tests/llvm/should_compile/all.T
@@ -11,3 +11,4 @@ test('5486', normal, compile, [''])
 test('5681', normal, compile, [''])
 test('6158', [reqlib('vector'), reqlib('primitive')], compile, ['-package vector -package primitive'])
 test('T7571', cmm_src, compile, [''])
+test('T7575', normal, compile, [''])
-- 
GitLab


From 4e6e839290421a446af3749adadac62ecfe7c934 Mon Sep 17 00:00:00 2001
From: David Terei <davidterei@gmail.com>
Date: Tue, 22 Jan 2013 23:48:15 -0800
Subject: [PATCH 026/223] Only run T7575 on 32bit arch.

---
 tests/llvm/should_compile/all.T | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/llvm/should_compile/all.T b/tests/llvm/should_compile/all.T
index b2d09ce00..41167377f 100644
--- a/tests/llvm/should_compile/all.T
+++ b/tests/llvm/should_compile/all.T
@@ -11,4 +11,4 @@ test('5486', normal, compile, [''])
 test('5681', normal, compile, [''])
 test('6158', [reqlib('vector'), reqlib('primitive')], compile, ['-package vector -package primitive'])
 test('T7571', cmm_src, compile, [''])
-test('T7575', normal, compile, [''])
+test('T7575', unless_wordsize(32, skip), compile, [''])
-- 
GitLab


From bcadec33746958e4d088ee6e89c54efa99f265bd Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 24 Jan 2013 13:37:06 +0000
Subject: [PATCH 027/223] Test Trac #7587

---
 tests/ghci/scripts/T7587.script | 3 +++
 tests/ghci/scripts/T7587.stdout | 1 +
 tests/ghci/scripts/all.T        | 1 +
 3 files changed, 5 insertions(+)
 create mode 100644 tests/ghci/scripts/T7587.script
 create mode 100644 tests/ghci/scripts/T7587.stdout

diff --git a/tests/ghci/scripts/T7587.script b/tests/ghci/scripts/T7587.script
new file mode 100644
index 000000000..76a7883f7
--- /dev/null
+++ b/tests/ghci/scripts/T7587.script
@@ -0,0 +1,3 @@
+:set -XPolyKinds
+data A x y
+:k A
diff --git a/tests/ghci/scripts/T7587.stdout b/tests/ghci/scripts/T7587.stdout
new file mode 100644
index 000000000..776eb6d22
--- /dev/null
+++ b/tests/ghci/scripts/T7587.stdout
@@ -0,0 +1 @@
+A :: k -> k1 -> *
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index 880efa312..317a34605 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -135,4 +135,5 @@ test('ghci058',
      extra_clean(['Ghci058.hs', 'Ghci058.hi', 'Ghci058.o']),
      ghci_script,
      ['ghci058.script'])
+test('T7587', normal, ghci_script, ['T7587.script'])
 
-- 
GitLab


From 5e7f657c4514fc206003bce987602b91ce72b815 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 24 Jan 2013 13:38:02 +0000
Subject: [PATCH 028/223] Fix debugging glitch in test output

---
 tests/polykinds/T7594.stderr | 3 ---
 1 file changed, 3 deletions(-)

diff --git a/tests/polykinds/T7594.stderr b/tests/polykinds/T7594.stderr
index 4be0b0a18..85a927dec 100644
--- a/tests/polykinds/T7594.stderr
+++ b/tests/polykinds/T7594.stderr
@@ -1,6 +1,3 @@
-h0
-h1
-h2
 
 T7594.hs:25:11:
     Couldn't match type `b' with `IO ()'
-- 
GitLab


From cdfefe82bf47b53c3370f07e09458a208878edb6 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 24 Jan 2013 13:59:26 +0000
Subject: [PATCH 029/223] Test Trac #2247

---
 tests/typecheck/should_fail/T2247.hs     | 18 ++++++++++++++++++
 tests/typecheck/should_fail/T2247.stderr |  6 ++++++
 tests/typecheck/should_fail/all.T        |  1 +
 3 files changed, 25 insertions(+)
 create mode 100644 tests/typecheck/should_fail/T2247.hs
 create mode 100644 tests/typecheck/should_fail/T2247.stderr

diff --git a/tests/typecheck/should_fail/T2247.hs b/tests/typecheck/should_fail/T2247.hs
new file mode 100644
index 000000000..3779f2db7
--- /dev/null
+++ b/tests/typecheck/should_fail/T2247.hs
@@ -0,0 +1,18 @@
+{-# LANGUAGE FunctionalDependencies, MultiParamTypeClasses, UndecidableInstances, FlexibleInstances #-}
+
+module T2247 where
+
+class FD a b | a -> b
+instance CFD a b => FD a b
+
+class {- FD a b => -} CFD a b
+instance CFD Bool Char
+instance CFD Bool Bool
+
+f' :: FD Bool Bool => Bool
+f' = True
+
+g' :: FD Bool Char => Bool
+g' = False
+
+x = f'
diff --git a/tests/typecheck/should_fail/T2247.stderr b/tests/typecheck/should_fail/T2247.stderr
new file mode 100644
index 000000000..70ef7f703
--- /dev/null
+++ b/tests/typecheck/should_fail/T2247.stderr
@@ -0,0 +1,6 @@
+
+T2247.hs:6:10:
+    Illegal instance declaration for `FD a b'
+      Multiple uses of this instance may be inconsistent
+      with the functional dependencies of the class.
+    In the instance declaration for `FD a b'
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index a4d021662..ad62ce75f 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -293,3 +293,4 @@ test('T7525', normal, compile_fail, [''])
 test('T7368a', normal, compile_fail, [''])
 test('T7545', normal, compile_fail, [''])
 test('T7279', normal, compile_fail, [''])
+test('T2247', normal, compile_fail, [''])
-- 
GitLab


From 2cb474d25990f42b87160ac7ed5c10dd93ca32d9 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 24 Jan 2013 16:39:50 +0000
Subject: [PATCH 030/223] Fix T1133, T1133A when BINDIST=YES

---
 tests/deriving/should_compile/Makefile | 4 ++--
 tests/deriving/should_fail/Makefile    | 4 ++--
 2 files changed, 4 insertions(+), 4 deletions(-)

diff --git a/tests/deriving/should_compile/Makefile b/tests/deriving/should_compile/Makefile
index 666f7a7e9..3ae7d49eb 100644
--- a/tests/deriving/should_compile/Makefile
+++ b/tests/deriving/should_compile/Makefile
@@ -4,6 +4,6 @@ include $(TOP)/mk/test.mk
 
 .PHONY: T1133
 T1133:
-	$(TEST_HC) $(TEST_HC_OPTS) -c T1133.hs-boot
-	$(TEST_HC) $(TEST_HC_OPTS) -c T1133.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c T1133.hs-boot
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c T1133.hs
 
diff --git a/tests/deriving/should_fail/Makefile b/tests/deriving/should_fail/Makefile
index f9f554d5d..629e01125 100644
--- a/tests/deriving/should_fail/Makefile
+++ b/tests/deriving/should_fail/Makefile
@@ -8,6 +8,6 @@ drvfail016:
 
 .PHONY: T1133A
 T1133A:
-	$(TEST_HC) $(TEST_HC_OPTS) -c T1133A.hs-boot
-	-$(TEST_HC) $(TEST_HC_OPTS) -c T1133A.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c T1133A.hs-boot
+	-'$(TEST_HC)' $(TEST_HC_OPTS) -c T1133A.hs
 
-- 
GitLab


From 5daeb972ba2a0be521a36ff148811c36fd8ce9c8 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 24 Jan 2013 17:04:40 +0000
Subject: [PATCH 031/223] Don't allow '/' characters in test names

---
 driver/testlib.py | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index c265350ca..4868e6d78 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -645,7 +645,7 @@ def test (name, setup, func, args):
     global allTestNames
     if name in allTestNames:
         framework_fail(name, 'duplicate', 'There are multiple tests with this name')
-    if not re.match('^[a-zA-Z0-9][a-zA-Z0-9._/-]*$', name):
+    if not re.match('^[a-zA-Z0-9][a-zA-Z0-9._-]*$', name):
         framework_fail(name, 'bad_name', 'This test has an invalid name')
     myTestOpts = copy.copy(thisdir_testopts)
 
-- 
GitLab


From 413dd2fbd98bf411e30762b0e6800d3e6119da8e Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 24 Jan 2013 17:31:32 +0000
Subject: [PATCH 032/223] Use .hpc.<testname> for the hpc directory

All tests used to use .hpc, which caused failures when running in
parallel.
---
 config/ghc        | 10 +++++-----
 driver/testlib.py |  8 ++++----
 2 files changed, 9 insertions(+), 9 deletions(-)

diff --git a/config/ghc b/config/ghc
index 73ff7d3fd..da7cc3a2a 100644
--- a/config/ghc
+++ b/config/ghc
@@ -80,7 +80,7 @@ if (ghc_with_llvm == 1):
 config.in_tree_compiler = in_tree_compiler
 config.clean_only       = clean_only
 
-config.way_flags = {
+config.way_flags = lambda name : {
     'normal'       : [],
     'g1'           : [],
     'optasm'       : ['-O', '-fasm'],
@@ -97,7 +97,7 @@ config.way_flags = {
     'threaded1_ls' : ['-threaded', '-debug'],
     'threaded2'    : ['-O', '-threaded', '-eventlog'],
     'threaded2_hT' : ['-O', '-threaded'],
-    'hpc'          : ['-O', '-fhpc' ],
+    'hpc'          : ['-O', '-fhpc', '-hpcdir', '.hpc.' + name ],
     'prof_hc_hb'   : ['-O', '-prof', '-static', '-auto-all'],
     'prof_hb'      : ['-O', '-prof', '-static', '-auto-all'],
     'prof_hd'      : ['-O', '-prof', '-static', '-auto-all'],
@@ -153,15 +153,15 @@ config.way_rts_flags = {
 
 prof_ways = map (lambda x: x[0], \
                  filter(lambda x: '-prof' in x[1], \
-                        config.way_flags.items()))
+                        config.way_flags('dummy_name').items()))
 
 threaded_ways = map (lambda x: x[0], \
                  filter(lambda x: '-threaded' in x[1] or 'ghci' == x[0], \
-                        config.way_flags.items()))
+                        config.way_flags('dummy_name').items()))
 
 opt_ways = map (lambda x: x[0], \
                  filter(lambda x: '-O' in x[1], \
-                        config.way_flags.items()))
+                        config.way_flags('dummy_name').items()))
 
 def get_compiler_info():
 # This should really not go through the shell
diff --git a/driver/testlib.py b/driver/testlib.py
index 4868e6d78..f21b380bc 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -1229,7 +1229,7 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf,
           + config.compiler + "' " \
           + join(comp_flags,' ') + ' ' \
           + to_do + ' ' + srcname + ' ' \
-          + join(config.way_flags[way],' ') + ' ' \
+          + join(config.way_flags(name)[way],' ') + ' ' \
           + extra_hc_opts + ' ' \
           + opts.extra_hc_opts + ' ' \
           + '>' + errname + ' 2>&1'
@@ -1415,7 +1415,7 @@ def interpreter_run( name, way, extra_hc_opts, compile_only, top_mod ):
     cmd = "'" + config.compiler + "' " \
           + join(flags,' ') + ' ' \
           + srcname + ' ' \
-          + join(config.way_flags[way],' ') + ' ' \
+          + join(config.way_flags(name)[way],' ') + ' ' \
           + extra_hc_opts + ' ' \
           + getTestOpts().extra_hc_opts + ' ' \
           + '<' + scriptname +  ' 1>' + outname + ' 2>' + errname
@@ -1511,7 +1511,7 @@ def extcore_run( name, way, extra_hc_opts, compile_only, top_mod ):
     cmd = 'cd ' + getTestOpts().testdir + " && '" \
           + config.compiler + "' " \
           + join(flags,' ') + ' ' \
-          + join(config.way_flags[way],' ') + ' ' \
+          + join(config.way_flags(name)[way],' ') + ' ' \
           + extra_hc_opts + ' ' \
           + getTestOpts().extra_hc_opts \
           + to_do \
@@ -1536,7 +1536,7 @@ def extcore_run( name, way, extra_hc_opts, compile_only, top_mod ):
         deplist2 = string.replace(deplist,'.lhs,', '.hcr');
         to_compile = string.replace(deplist2,'.hs,', '.hcr');
 
-    flags = join(filter(lambda f: f != '-fext-core',config.way_flags[way]),' ')
+    flags = join(filter(lambda f: f != '-fext-core',config.way_flags(name)[way]),' ')
     if getTestOpts().outputdir != None:
         flags.extend(["-outputdir", getTestOpts().outputdir])
 
-- 
GitLab


From 576fca8930b22cabcebfa4e6487d0c2619bce231 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 24 Jan 2013 17:34:47 +0000
Subject: [PATCH 033/223] Clean the .hpc directories

---
 driver/testlib.py | 5 +++++
 1 file changed, 5 insertions(+)

diff --git a/driver/testlib.py b/driver/testlib.py
index f21b380bc..b57a0800a 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -761,6 +761,11 @@ def test_common_work (name, opts, func, args):
                 except:
                     pass
 
+            try:
+                shutil.rmtree(in_testdir('.hpc.' + name))
+            except:
+                pass
+
             try:
                 cleanCmd = getTestOpts().clean_cmd
                 if cleanCmd != None:
-- 
GitLab


From d262089127c54bfe81963628ac70a309f8133492 Mon Sep 17 00:00:00 2001
From: David Terei <davidterei@gmail.com>
Date: Thu, 24 Jan 2013 14:18:56 -0800
Subject: [PATCH 034/223] fix runtests to set LD_LIBRARY_PATH environment
 variable.

Patch from Karel Gardas <karel.gardas@centrum.cz>.
---
 driver/runtests.py | 48 +++++++++++++++++++++++++---------------------
 1 file changed, 26 insertions(+), 22 deletions(-)

diff --git a/driver/runtests.py b/driver/runtests.py
index 66e3bf4d5..d2b5c7849 100644
--- a/driver/runtests.py
+++ b/driver/runtests.py
@@ -181,28 +181,32 @@ from testlib import *
 
 # On Windows we need to set $PATH to include the paths to all the DLLs
 # in order for the dynamic library tests to work.
-if windows or darwin:
-    pkginfo = getStdout([config.ghc_pkg, 'dump'])
-    topdir = config.libdir
-    for line in pkginfo.split('\n'):
-        if line.startswith('library-dirs:'):
-            path = line.rstrip()
-            path = re.sub('^library-dirs: ', '', path)
-            path = re.sub('\\$topdir', topdir, path)
-            if path.startswith('"'):
-                path = re.sub('^"(.*)"$', '\\1', path)
-                path = re.sub('\\\\(.)', '\\1', path)
-            if windows:
-                if config.cygwin:
-                    # On cygwin we can't put "c:\foo" in $PATH, as : is a
-                    # field separator. So convert to /cygdrive/c/foo instead.
-                    # Other pythons use ; as the separator, so no problem.
-                    path = re.sub('([a-zA-Z]):', '/cygdrive/\\1', path)
-                    path = re.sub('\\\\', '/', path)
-                os.environ['PATH'] = os.pathsep.join([path, os.environ.get("PATH", "")])
-            else:
-                # darwin
-                os.environ['DYLD_LIBRARY_PATH'] = os.pathsep.join([path, os.environ.get("DYLD_LIBRARY_PATH", "")])
+# if windows or darwin:
+pkginfo = getStdout([config.ghc_pkg, 'dump'])
+topdir = config.libdir
+for line in pkginfo.split('\n'):
+    if line.startswith('library-dirs:'):
+        path = line.rstrip()
+        path = re.sub('^library-dirs: ', '', path)
+        path = re.sub('\\$topdir', topdir, path)
+        if path.startswith('"'):
+            path = re.sub('^"(.*)"$', '\\1', path)
+            path = re.sub('\\\\(.)', '\\1', path)
+        if windows:
+            if config.cygwin:
+                # On cygwin we can't put "c:\foo" in $PATH, as : is a
+                # field separator. So convert to /cygdrive/c/foo instead.
+                # Other pythons use ; as the separator, so no problem.
+                path = re.sub('([a-zA-Z]):', '/cygdrive/\\1', path)
+                path = re.sub('\\\\', '/', path)
+            os.environ['PATH'] = os.pathsep.join([path, os.environ.get("PATH", "")])
+        elif darwin:
+            # darwin
+            os.environ['DYLD_LIBRARY_PATH'] = os.pathsep.join([path, os.environ.get("DYLD_LIBRARY_PATH", "")])
+        else:
+            # unix
+            os.environ['LD_LIBRARY_PATH'] = os.pathsep.join([path, os.environ.get("LD_LIBRARY_PATH", "")])
+
 
 global testopts_local
 testopts_local.x = TestOptions()
-- 
GitLab


From 53da29a4f7c005f8d32903f8d59568d563b847e3 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 01:28:17 +0000
Subject: [PATCH 035/223] Rename some tests to not start with a digit

---
 tests/driver/1372/all.T                          |  5 -----
 tests/driver/2499.stderr                         |  4 ----
 tests/driver/Makefile                            | 10 +++++-----
 tests/driver/{1372 => T1372}/Makefile            |  2 +-
 .../{1372/1372.stderr => T1372/T1372.stderr}     |  0
 tests/driver/T1372/all.T                         |  5 +++++
 tests/driver/{1372 => T1372}/p1/A1.hs            |  0
 tests/driver/{1372 => T1372}/p1/A2.hs            |  0
 tests/driver/{1372 => T1372}/p1/Setup.hs         |  0
 tests/driver/{1372 => T1372}/p1/p1.cabal         |  0
 tests/driver/{1372 => T1372}/p2/Main.hs          |  0
 tests/driver/{1372 => T1372}/p2/Setup.hs         |  0
 tests/driver/{1372 => T1372}/p2/p2.cabal         |  0
 tests/driver/{1959 => T1959}/B.hs                |  0
 tests/driver/{1959 => T1959}/C.hs                |  0
 tests/driver/{1959 => T1959}/D.hs                |  0
 tests/driver/{1959 => T1959}/E1.hs               |  0
 tests/driver/{1959 => T1959}/E2.hs               |  0
 tests/driver/{1959 => T1959}/Makefile            |  0
 .../{1959/1959.stdout => T1959/T1959.stdout}     |  0
 tests/driver/{1959 => T1959}/test.T              |  2 +-
 tests/driver/{2464.hs => T2464.hs}               |  0
 tests/driver/{2464.stderr => T2464.stderr}       |  2 +-
 tests/driver/{2499.hs => T2499.hs}               |  0
 tests/driver/T2499.stderr                        |  4 ++++
 tests/driver/{2566.stderr => T2566.stderr}       |  0
 tests/driver/{3674.hs => T3674.hs}               |  2 +-
 tests/driver/{3674_pre.hs => T3674_pre.hs}       |  0
 tests/driver/{437 => T437}/Makefile              |  2 +-
 .../driver/{437/437.stderr => T437/T437.stderr}  |  0
 .../driver/{437/437.stdout => T437/T437.stdout}  |  0
 tests/driver/{437 => T437}/Test.hs               |  0
 tests/driver/{437 => T437}/Test2.hs              |  0
 tests/driver/{437 => T437}/all.T                 |  4 ++--
 tests/driver/{5313.hs => T5313.hs}               |  0
 tests/driver/all.T                               | 16 ++++++++--------
 36 files changed, 29 insertions(+), 29 deletions(-)
 delete mode 100644 tests/driver/1372/all.T
 delete mode 100644 tests/driver/2499.stderr
 rename tests/driver/{1372 => T1372}/Makefile (99%)
 rename tests/driver/{1372/1372.stderr => T1372/T1372.stderr} (100%)
 create mode 100644 tests/driver/T1372/all.T
 rename tests/driver/{1372 => T1372}/p1/A1.hs (100%)
 rename tests/driver/{1372 => T1372}/p1/A2.hs (100%)
 rename tests/driver/{1372 => T1372}/p1/Setup.hs (100%)
 rename tests/driver/{1372 => T1372}/p1/p1.cabal (100%)
 rename tests/driver/{1372 => T1372}/p2/Main.hs (100%)
 rename tests/driver/{1372 => T1372}/p2/Setup.hs (100%)
 rename tests/driver/{1372 => T1372}/p2/p2.cabal (100%)
 rename tests/driver/{1959 => T1959}/B.hs (100%)
 rename tests/driver/{1959 => T1959}/C.hs (100%)
 rename tests/driver/{1959 => T1959}/D.hs (100%)
 rename tests/driver/{1959 => T1959}/E1.hs (100%)
 rename tests/driver/{1959 => T1959}/E2.hs (100%)
 rename tests/driver/{1959 => T1959}/Makefile (100%)
 rename tests/driver/{1959/1959.stdout => T1959/T1959.stdout} (100%)
 rename tests/driver/{1959 => T1959}/test.T (93%)
 rename tests/driver/{2464.hs => T2464.hs} (100%)
 rename tests/driver/{2464.stderr => T2464.stderr} (89%)
 rename tests/driver/{2499.hs => T2499.hs} (100%)
 create mode 100644 tests/driver/T2499.stderr
 rename tests/driver/{2566.stderr => T2566.stderr} (100%)
 rename tests/driver/{3674.hs => T3674.hs} (60%)
 rename tests/driver/{3674_pre.hs => T3674_pre.hs} (100%)
 rename tests/driver/{437 => T437}/Makefile (98%)
 rename tests/driver/{437/437.stderr => T437/T437.stderr} (100%)
 rename tests/driver/{437/437.stdout => T437/T437.stdout} (100%)
 rename tests/driver/{437 => T437}/Test.hs (100%)
 rename tests/driver/{437 => T437}/Test2.hs (100%)
 rename tests/driver/{437 => T437}/all.T (65%)
 rename tests/driver/{5313.hs => T5313.hs} (100%)

diff --git a/tests/driver/1372/all.T b/tests/driver/1372/all.T
deleted file mode 100644
index cabf3c01f..000000000
--- a/tests/driver/1372/all.T
+++ /dev/null
@@ -1,5 +0,0 @@
-test('1372',
-     clean_cmd('$MAKE -s clean'),
-     run_command,
-     ['$MAKE -s --no-print-directory 1372'])
-
diff --git a/tests/driver/2499.stderr b/tests/driver/2499.stderr
deleted file mode 100644
index 73404befe..000000000
--- a/tests/driver/2499.stderr
+++ /dev/null
@@ -1,4 +0,0 @@
-
-2499.hs:1:12: unknown flag in  {-# OPTIONS_GHC #-} pragma: -package
-
-2499.hs:1:12: unknown flag in  {-# OPTIONS_GHC #-} pragma: blargh
diff --git a/tests/driver/Makefile b/tests/driver/Makefile
index e293772f4..bd24b2e88 100644
--- a/tests/driver/Makefile
+++ b/tests/driver/Makefile
@@ -411,7 +411,7 @@ test200:
 
 # -----------------------------------------------------------------------------
 
-2566::
+T2566::
 	if "$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) -c foo2566.bar; then false else true; fi
 
 .PHONY: mode001
@@ -439,10 +439,10 @@ shared001:
 
 # -----------------------------------------------------------------------------
 
-3674:
-	$(RM) 3674*.o 3674*.hi 3674_pre
-	"$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) --make 3674_pre.hs
-	"$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) --make 3674.hs
+T3674:
+	$(RM) T3674*.o T3674*.hi T3674_pre
+	"$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) --make T3674_pre.hs
+	"$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) --make T3674.hs
 
 .PHONY: rtsopts001
 rtsopts001:
diff --git a/tests/driver/1372/Makefile b/tests/driver/T1372/Makefile
similarity index 99%
rename from tests/driver/1372/Makefile
rename to tests/driver/T1372/Makefile
index e0b3873ec..91ef6d50c 100644
--- a/tests/driver/1372/Makefile
+++ b/tests/driver/T1372/Makefile
@@ -17,7 +17,7 @@ clean:
 	rm -f p1/A.hs
 	rm -f $(LOCAL_PKGCONF)
 
-1372:
+T1372:
 	$(MAKE) clean
 	$(MAKE) prep
 # This should recompile Main.hs, because A in package p1 has changed
diff --git a/tests/driver/1372/1372.stderr b/tests/driver/T1372/T1372.stderr
similarity index 100%
rename from tests/driver/1372/1372.stderr
rename to tests/driver/T1372/T1372.stderr
diff --git a/tests/driver/T1372/all.T b/tests/driver/T1372/all.T
new file mode 100644
index 000000000..352d66b5d
--- /dev/null
+++ b/tests/driver/T1372/all.T
@@ -0,0 +1,5 @@
+test('T1372',
+     clean_cmd('$MAKE -s clean'),
+     run_command,
+     ['$MAKE -s --no-print-directory T1372'])
+
diff --git a/tests/driver/1372/p1/A1.hs b/tests/driver/T1372/p1/A1.hs
similarity index 100%
rename from tests/driver/1372/p1/A1.hs
rename to tests/driver/T1372/p1/A1.hs
diff --git a/tests/driver/1372/p1/A2.hs b/tests/driver/T1372/p1/A2.hs
similarity index 100%
rename from tests/driver/1372/p1/A2.hs
rename to tests/driver/T1372/p1/A2.hs
diff --git a/tests/driver/1372/p1/Setup.hs b/tests/driver/T1372/p1/Setup.hs
similarity index 100%
rename from tests/driver/1372/p1/Setup.hs
rename to tests/driver/T1372/p1/Setup.hs
diff --git a/tests/driver/1372/p1/p1.cabal b/tests/driver/T1372/p1/p1.cabal
similarity index 100%
rename from tests/driver/1372/p1/p1.cabal
rename to tests/driver/T1372/p1/p1.cabal
diff --git a/tests/driver/1372/p2/Main.hs b/tests/driver/T1372/p2/Main.hs
similarity index 100%
rename from tests/driver/1372/p2/Main.hs
rename to tests/driver/T1372/p2/Main.hs
diff --git a/tests/driver/1372/p2/Setup.hs b/tests/driver/T1372/p2/Setup.hs
similarity index 100%
rename from tests/driver/1372/p2/Setup.hs
rename to tests/driver/T1372/p2/Setup.hs
diff --git a/tests/driver/1372/p2/p2.cabal b/tests/driver/T1372/p2/p2.cabal
similarity index 100%
rename from tests/driver/1372/p2/p2.cabal
rename to tests/driver/T1372/p2/p2.cabal
diff --git a/tests/driver/1959/B.hs b/tests/driver/T1959/B.hs
similarity index 100%
rename from tests/driver/1959/B.hs
rename to tests/driver/T1959/B.hs
diff --git a/tests/driver/1959/C.hs b/tests/driver/T1959/C.hs
similarity index 100%
rename from tests/driver/1959/C.hs
rename to tests/driver/T1959/C.hs
diff --git a/tests/driver/1959/D.hs b/tests/driver/T1959/D.hs
similarity index 100%
rename from tests/driver/1959/D.hs
rename to tests/driver/T1959/D.hs
diff --git a/tests/driver/1959/E1.hs b/tests/driver/T1959/E1.hs
similarity index 100%
rename from tests/driver/1959/E1.hs
rename to tests/driver/T1959/E1.hs
diff --git a/tests/driver/1959/E2.hs b/tests/driver/T1959/E2.hs
similarity index 100%
rename from tests/driver/1959/E2.hs
rename to tests/driver/T1959/E2.hs
diff --git a/tests/driver/1959/Makefile b/tests/driver/T1959/Makefile
similarity index 100%
rename from tests/driver/1959/Makefile
rename to tests/driver/T1959/Makefile
diff --git a/tests/driver/1959/1959.stdout b/tests/driver/T1959/T1959.stdout
similarity index 100%
rename from tests/driver/1959/1959.stdout
rename to tests/driver/T1959/T1959.stdout
diff --git a/tests/driver/1959/test.T b/tests/driver/T1959/test.T
similarity index 93%
rename from tests/driver/1959/test.T
rename to tests/driver/T1959/test.T
index ff9e8f63a..563206f09 100644
--- a/tests/driver/1959/test.T
+++ b/tests/driver/T1959/test.T
@@ -1,4 +1,4 @@
-test('1959',
+test('T1959',
      extra_clean(['E.hi', 'E.o', 'E.hs', 'prog', 'compile.out',
                   'B.hi', 'B.o', 'C.hi', 'C.o', 'D.hi', 'D.o']),
      run_command,
diff --git a/tests/driver/2464.hs b/tests/driver/T2464.hs
similarity index 100%
rename from tests/driver/2464.hs
rename to tests/driver/T2464.hs
diff --git a/tests/driver/2464.stderr b/tests/driver/T2464.stderr
similarity index 89%
rename from tests/driver/2464.stderr
rename to tests/driver/T2464.stderr
index 31e794e33..92e5e640c 100644
--- a/tests/driver/2464.stderr
+++ b/tests/driver/T2464.stderr
@@ -1,3 +1,3 @@
 
-2464.hs:3:16:
+T2464.hs:3:16:
     Warning: -fffi is deprecated: use -XForeignFunctionInterface or pragma {-# LANGUAGE ForeignFunctionInterface #-} instead
diff --git a/tests/driver/2499.hs b/tests/driver/T2499.hs
similarity index 100%
rename from tests/driver/2499.hs
rename to tests/driver/T2499.hs
diff --git a/tests/driver/T2499.stderr b/tests/driver/T2499.stderr
new file mode 100644
index 000000000..9a082d34b
--- /dev/null
+++ b/tests/driver/T2499.stderr
@@ -0,0 +1,4 @@
+
+T2499.hs:1:12: unknown flag in  {-# OPTIONS_GHC #-} pragma: -package
+
+T2499.hs:1:12: unknown flag in  {-# OPTIONS_GHC #-} pragma: blargh
diff --git a/tests/driver/2566.stderr b/tests/driver/T2566.stderr
similarity index 100%
rename from tests/driver/2566.stderr
rename to tests/driver/T2566.stderr
diff --git a/tests/driver/3674.hs b/tests/driver/T3674.hs
similarity index 60%
rename from tests/driver/3674.hs
rename to tests/driver/T3674.hs
index 2253ca12c..055b28122 100644
--- a/tests/driver/3674.hs
+++ b/tests/driver/T3674.hs
@@ -1,4 +1,4 @@
-{-# OPTIONS -F -pgmF ./3674_pre #-}
+{-# OPTIONS -F -pgmF ./T3674_pre #-}
 
 module Test3674 where
 
diff --git a/tests/driver/3674_pre.hs b/tests/driver/T3674_pre.hs
similarity index 100%
rename from tests/driver/3674_pre.hs
rename to tests/driver/T3674_pre.hs
diff --git a/tests/driver/437/Makefile b/tests/driver/T437/Makefile
similarity index 98%
rename from tests/driver/437/Makefile
rename to tests/driver/T437/Makefile
index 649d462b1..8c18b1c3c 100644
--- a/tests/driver/437/Makefile
+++ b/tests/driver/T437/Makefile
@@ -15,7 +15,7 @@ clean:
 
 # bug #437
 
-437: clean
+T437: clean
 	'$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP)  --make -main-is Test.main Test.hs
 	'$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP)  --make -main-is Test2.main Test2.hs
 	./Test
diff --git a/tests/driver/437/437.stderr b/tests/driver/T437/T437.stderr
similarity index 100%
rename from tests/driver/437/437.stderr
rename to tests/driver/T437/T437.stderr
diff --git a/tests/driver/437/437.stdout b/tests/driver/T437/T437.stdout
similarity index 100%
rename from tests/driver/437/437.stdout
rename to tests/driver/T437/T437.stdout
diff --git a/tests/driver/437/Test.hs b/tests/driver/T437/Test.hs
similarity index 100%
rename from tests/driver/437/Test.hs
rename to tests/driver/T437/Test.hs
diff --git a/tests/driver/437/Test2.hs b/tests/driver/T437/Test2.hs
similarity index 100%
rename from tests/driver/437/Test2.hs
rename to tests/driver/T437/Test2.hs
diff --git a/tests/driver/437/all.T b/tests/driver/T437/all.T
similarity index 65%
rename from tests/driver/437/all.T
rename to tests/driver/T437/all.T
index 34bb7f88b..258873894 100644
--- a/tests/driver/437/all.T
+++ b/tests/driver/T437/all.T
@@ -1,7 +1,7 @@
 # Test for #437, a recompilation bug with '-main-is'
 
-test('437',
+test('T437',
      [ clean_cmd('$MAKE -s clean') ],
      run_command,
-     ['$MAKE -s --no-print-directory 437'])
+     ['$MAKE -s --no-print-directory T437'])
 
diff --git a/tests/driver/5313.hs b/tests/driver/T5313.hs
similarity index 100%
rename from tests/driver/5313.hs
rename to tests/driver/T5313.hs
diff --git a/tests/driver/all.T b/tests/driver/all.T
index f60dc4172..1bf7c7e33 100644
--- a/tests/driver/all.T
+++ b/tests/driver/all.T
@@ -282,15 +282,15 @@ test('driver200',
      run_command,
      ['$MAKE -s --no-print-directory test200'])
 
-test('2566',
+test('T2566',
      normalise_fun(normalise_errmsg),
      run_command,
-     ['$MAKE -s --no-print-directory 2566'])
+     ['$MAKE -s --no-print-directory T2566'])
 
 test('pragma001', normal, compile, [''])
 test('pragma002', normal, compile, [''])
 
-test('2499', normal, compile_fail, [''])
+test('T2499', normal, compile_fail, [''])
 
 test('mode001', normal, run_command,
      ['$MAKE -s --no-print-directory mode001'])
@@ -311,14 +311,14 @@ test('dynHelloWorld',
      compile_and_run,
      [''])
 
-test('5313', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc'])
+test('T5313', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc'])
 
-test('2464', normal, compile, [''])
-test('3674',
+test('T2464', normal, compile, [''])
+test('T3674',
      [ignore_output,
-      extra_clean(['3674_pre.hi', '3674_pre.o', '3674_pre', '3674_pre.exe'])],
+      extra_clean(['T3674_pre.hi', 'T3674_pre.o', 'T3674_pre', 'T3674_pre.exe'])],
      run_command, 
-     ['$MAKE -s --no-print-directory 3674'])
+     ['$MAKE -s --no-print-directory T3674'])
 
 test('rtsopts001',
      extra_clean(['rtsOpts.hi', 'rtsOpts.o', 'rtsOpts', 'rtsOpts.exe']),
-- 
GitLab


From faa34f5d466010facb7127727208897446c1d0d0 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 01:39:18 +0000
Subject: [PATCH 036/223] Make do_test catch and re-raise KeyboardInterrupt

This means that hitting ^C now stops the testsuite from running,
rather than just killing the current test.
---
 driver/testlib.py | 2 ++
 1 file changed, 2 insertions(+)

diff --git a/driver/testlib.py b/driver/testlib.py
index b57a0800a..0c8e1f340 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -887,6 +887,8 @@ def do_test(name, way, func, args):
                         t.expected_failures[name] = [way]
         else:
             framework_fail(name, way, 'bad result ' + passFail)
+    except KeyboardInterrupt:
+        raise
     except:
         framework_fail(name, way, 'do_test exception')
         traceback.print_exc()
-- 
GitLab


From f98008c683bba218f0041a9e8e0d3e52e526fc25 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Fri, 25 Jan 2013 12:11:22 +0000
Subject: [PATCH 037/223] Adjust test; Int is not promotable

---
 tests/polykinds/T7488.hs | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/polykinds/T7488.hs b/tests/polykinds/T7488.hs
index c76de8471..e833cddaa 100644
--- a/tests/polykinds/T7488.hs
+++ b/tests/polykinds/T7488.hs
@@ -4,5 +4,5 @@
 
 module T7488 where
 
-newtype A = A Int
+newtype A = A Bool
 data B (x :: A)
-- 
GitLab


From 5a7e7665ba81f5fc07f9e504efbe7410f68179a9 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Fri, 25 Jan 2013 12:14:04 +0000
Subject: [PATCH 038/223] Error message wibbles

---
 .../indexed-types/should_compile/T3017.stderr | 48 +++++++--------
 tests/polykinds/T5716.stderr                  | 10 ++--
 tests/typecheck/should_compile/tc231.stderr   | 58 +++++++++----------
 tests/typecheck/should_fail/T3468.stderr      | 24 ++++----
 4 files changed, 69 insertions(+), 71 deletions(-)

diff --git a/tests/indexed-types/should_compile/T3017.stderr b/tests/indexed-types/should_compile/T3017.stderr
index b7bedaea6..28ddc1452 100644
--- a/tests/indexed-types/should_compile/T3017.stderr
+++ b/tests/indexed-types/should_compile/T3017.stderr
@@ -1,24 +1,24 @@
-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
-  Coll :: * -> Constraint
-  class Coll c
-      RecFlag NonRecursive
-      type family Elem c :: *
-      empty :: c insert :: Elem c -> c -> c
-  ListColl :: * -> *
-  data ListColl a
-      No C type associated
-      RecFlag NonRecursive
-      = L :: forall a. [a] -> ListColl a Stricts: _
-      FamilyInstance: none
-COERCION AXIOMS
-  axiom Foo.TFCo:R:ElemListColl :: forall a. Elem (ListColl a) ~# a
-INSTANCES
-  instance Coll (ListColl a) -- Defined at T3017.hs:12:11
-FAMILY INSTANCES
-  type Elem (ListColl a) -- Defined at T3017.hs:13:9
-Dependent modules: []
-Dependent packages: [base, ghc-prim, integer-gmp]
+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
+  Coll :: * -> Constraint
+  class Coll c
+      RecFlag NonRecursive
+      type family Elem c :: *
+      empty :: c insert :: Elem c -> c -> c
+  ListColl :: * -> *
+  data ListColl a
+      No C type associated
+      RecFlag NonRecursive, Promotable
+      = L :: forall a. [a] -> ListColl a Stricts: _
+      FamilyInstance: none
+COERCION AXIOMS
+  axiom Foo.TFCo:R:ElemListColl :: forall a. Elem (ListColl a) ~# a
+INSTANCES
+  instance Coll (ListColl a) -- Defined at T3017.hs:12:11
+FAMILY INSTANCES
+  type Elem (ListColl a) -- Defined at T3017.hs:13:9
+Dependent modules: []
+Dependent packages: [base, ghc-prim, integer-gmp]
diff --git a/tests/polykinds/T5716.stderr b/tests/polykinds/T5716.stderr
index 7e38d01f6..165f32bd7 100644
--- a/tests/polykinds/T5716.stderr
+++ b/tests/polykinds/T5716.stderr
@@ -1,6 +1,4 @@
-
-T5716.hs:13:33:
-    `U1' of type `DF Int -> U' is not promotable
-    In the type `I (U1 DFInt)'
-    In the definition of data constructor `I1'
-    In the data declaration for `I'
+
+T5716.hs:13:11:
+    `U' of kind `*' is not promotable
+    In the kind `U -> *'
diff --git a/tests/typecheck/should_compile/tc231.stderr b/tests/typecheck/should_compile/tc231.stderr
index 0e9196c3f..99f7dfdb2 100644
--- a/tests/typecheck/should_compile/tc231.stderr
+++ b/tests/typecheck/should_compile/tc231.stderr
@@ -1,29 +1,29 @@
-TYPE SIGNATURES
-  foo ::
-    forall s b chain.
-    Zork s (Z [Char]) b =>
-    Q s (Z [Char]) chain -> ST s ()
-  s :: forall t t1. Q t (Z [Char]) t1 -> Q t (Z [Char]) t1
-TYPE CONSTRUCTORS
-  Q :: * -> * -> * -> *
-  data Q s a chain
-      No C type associated
-      RecFlag NonRecursive
-      = Node :: forall s a chain. s -> a -> chain -> Q s a chain
-            Stricts: _ _ _
-      FamilyInstance: none
-  Z :: * -> *
-  data Z a
-      No C type associated
-      RecFlag NonRecursive
-      = Z :: forall a. a -> Z a Stricts: _
-      FamilyInstance: none
-  Zork :: * -> * -> * -> Constraint
-  class Zork s a b | a -> b
-      RecFlag NonRecursive
-      huh :: forall chain. Q s a chain -> ST s ()
-COERCION AXIOMS
-  axiom ShouldCompile.NTCo:Zork ::
-    forall s a b. Zork s a b ~# (forall chain. Q s a chain -> ST s ())
-Dependent modules: []
-Dependent packages: [base, ghc-prim, integer-gmp]
+TYPE SIGNATURES
+  foo ::
+    forall s b chain.
+    Zork s (Z [Char]) b =>
+    Q s (Z [Char]) chain -> ST s ()
+  s :: forall t t1. Q t (Z [Char]) t1 -> Q t (Z [Char]) t1
+TYPE CONSTRUCTORS
+  Q :: * -> * -> * -> *
+  data Q s a chain
+      No C type associated
+      RecFlag NonRecursive, Promotable
+      = Node :: forall s a chain. s -> a -> chain -> Q s a chain
+            Stricts: _ _ _
+      FamilyInstance: none
+  Z :: * -> *
+  data Z a
+      No C type associated
+      RecFlag NonRecursive, Promotable
+      = Z :: forall a. a -> Z a Stricts: _
+      FamilyInstance: none
+  Zork :: * -> * -> * -> Constraint
+  class Zork s a b | a -> b
+      RecFlag NonRecursive
+      huh :: forall chain. Q s a chain -> ST s ()
+COERCION AXIOMS
+  axiom ShouldCompile.NTCo:Zork ::
+    forall s a b. Zork s a b ~# (forall chain. Q s a chain -> ST s ())
+Dependent modules: []
+Dependent packages: [base, ghc-prim, integer-gmp]
diff --git a/tests/typecheck/should_fail/T3468.stderr b/tests/typecheck/should_fail/T3468.stderr
index ac040ba05..1dcc3488e 100644
--- a/tests/typecheck/should_fail/T3468.stderr
+++ b/tests/typecheck/should_fail/T3468.stderr
@@ -1,12 +1,12 @@
-
-T3468.hs-boot:3:6:
-    Type constructor `Tool' has conflicting definitions in the module and its hs-boot file
-    Main module: data Tool d
-                     No C type associated
-                     RecFlag Recursive
-                     = F :: forall d a r. a -> Tool d Stricts: _
-                     FamilyInstance: none
-    Boot file:   abstract(False) Tool
-                     No C type associated
-                     RecFlag NonRecursive
-                     FamilyInstance: none
+
+T3468.hs-boot:3:6:
+    Type constructor `Tool' has conflicting definitions in the module and its hs-boot file
+    Main module: data Tool d
+                     No C type associated
+                     RecFlag Recursive, Promotable
+                     = F :: forall d a r. a -> Tool d Stricts: _
+                     FamilyInstance: none
+    Boot file:   abstract(False) Tool
+                     No C type associated
+                     RecFlag NonRecursive, Not promotable
+                     FamilyInstance: none
-- 
GitLab


From 693dc735527dd34ba9e279df024822de5fb3d2ea Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 13:56:36 +0000
Subject: [PATCH 039/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/numeric/should_run/{1603.hs => T1603.hs}         | 0
 tests/numeric/should_run/{1603.stdout => T1603.stdout} | 0
 tests/numeric/should_run/{3676.hs => T3676.hs}         | 0
 tests/numeric/should_run/{3676.stdout => T3676.stdout} | 0
 tests/numeric/should_run/{4381.hs => T4381.hs}         | 0
 tests/numeric/should_run/{4381.stdout => T4381.stdout} | 0
 tests/numeric/should_run/{4383.hs => T4383.hs}         | 0
 tests/numeric/should_run/{4383.stdout => T4383.stdout} | 0
 tests/numeric/should_run/all.T                         | 8 ++++----
 9 files changed, 4 insertions(+), 4 deletions(-)
 rename tests/numeric/should_run/{1603.hs => T1603.hs} (100%)
 rename tests/numeric/should_run/{1603.stdout => T1603.stdout} (100%)
 rename tests/numeric/should_run/{3676.hs => T3676.hs} (100%)
 rename tests/numeric/should_run/{3676.stdout => T3676.stdout} (100%)
 rename tests/numeric/should_run/{4381.hs => T4381.hs} (100%)
 rename tests/numeric/should_run/{4381.stdout => T4381.stdout} (100%)
 rename tests/numeric/should_run/{4383.hs => T4383.hs} (100%)
 rename tests/numeric/should_run/{4383.stdout => T4383.stdout} (100%)

diff --git a/tests/numeric/should_run/1603.hs b/tests/numeric/should_run/T1603.hs
similarity index 100%
rename from tests/numeric/should_run/1603.hs
rename to tests/numeric/should_run/T1603.hs
diff --git a/tests/numeric/should_run/1603.stdout b/tests/numeric/should_run/T1603.stdout
similarity index 100%
rename from tests/numeric/should_run/1603.stdout
rename to tests/numeric/should_run/T1603.stdout
diff --git a/tests/numeric/should_run/3676.hs b/tests/numeric/should_run/T3676.hs
similarity index 100%
rename from tests/numeric/should_run/3676.hs
rename to tests/numeric/should_run/T3676.hs
diff --git a/tests/numeric/should_run/3676.stdout b/tests/numeric/should_run/T3676.stdout
similarity index 100%
rename from tests/numeric/should_run/3676.stdout
rename to tests/numeric/should_run/T3676.stdout
diff --git a/tests/numeric/should_run/4381.hs b/tests/numeric/should_run/T4381.hs
similarity index 100%
rename from tests/numeric/should_run/4381.hs
rename to tests/numeric/should_run/T4381.hs
diff --git a/tests/numeric/should_run/4381.stdout b/tests/numeric/should_run/T4381.stdout
similarity index 100%
rename from tests/numeric/should_run/4381.stdout
rename to tests/numeric/should_run/T4381.stdout
diff --git a/tests/numeric/should_run/4383.hs b/tests/numeric/should_run/T4383.hs
similarity index 100%
rename from tests/numeric/should_run/4383.hs
rename to tests/numeric/should_run/T4383.hs
diff --git a/tests/numeric/should_run/4383.stdout b/tests/numeric/should_run/T4383.stdout
similarity index 100%
rename from tests/numeric/should_run/4383.stdout
rename to tests/numeric/should_run/T4383.stdout
diff --git a/tests/numeric/should_run/all.T b/tests/numeric/should_run/all.T
index c5cfc8cca..beee59da8 100644
--- a/tests/numeric/should_run/all.T
+++ b/tests/numeric/should_run/all.T
@@ -49,10 +49,10 @@ test('arith018', normal, compile_and_run, [''])
 test('arith019', normal, compile_and_run, [''])
 test('expfloat', normal, compile_and_run, [''])
 
-test('1603', skip, compile_and_run, [''])
-test('3676', expect_broken(3676), compile_and_run, [''])
-test('4381', normal, compile_and_run, [''])
-test('4383', normal, compile_and_run, [''])
+test('T1603', skip, compile_and_run, [''])
+test('T3676', expect_broken(3676), compile_and_run, [''])
+test('T4381', normal, compile_and_run, [''])
+test('T4383', normal, compile_and_run, [''])
 
 test('add2', normal, compile_and_run, ['-fobject-code'])
 test('mul2', normal, compile_and_run, ['-fobject-code'])
-- 
GitLab


From fd233b876a415086e9a611d8a6338f4d1e187c7b Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 14:05:14 +0000
Subject: [PATCH 040/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/codeGen/should_compile/Makefile         |  4 +--
 .../should_compile/{1916.hs => T1916.hs}      |  0
 .../should_compile/{2388.hs => T2388.hs}      |  0
 .../should_compile/{2578.hs => T2578.hs}      |  0
 .../should_compile/{3132.hs => T3132.hs}      |  0
 .../should_compile/{3579.hs => T3579.hs}      |  0
 tests/codeGen/should_compile/all.T            | 10 +++----
 tests/codeGen/should_run/5626.stderr          |  1 -
 .../codeGen/should_run/{1852.hs => T1852.hs}  |  0
 .../should_run/{1852.stdout => T1852.stdout}  |  0
 .../codeGen/should_run/{1861.hs => T1861.hs}  |  0
 .../should_run/{1861.stdout => T1861.stdout}  |  0
 .../codeGen/should_run/{2080.hs => T2080.hs}  |  0
 .../should_run/{2080.stdout => T2080.stdout}  |  0
 .../codeGen/should_run/{2838.hs => T2838.hs}  |  0
 .../should_run/{2838.stdout => T2838.stdout}  |  0
 .../{2838.stdout-ws-64 => T2838.stdout-ws-64} |  0
 .../codeGen/should_run/{3207.hs => T3207.hs}  |  0
 .../should_run/{3207.stdout => T3207.stdout}  |  0
 .../codeGen/should_run/{3561.hs => T3561.hs}  |  0
 .../should_run/{3561.stdout => T3561.stdout}  |  0
 .../codeGen/should_run/{3677.hs => T3677.hs}  |  0
 .../should_run/{3677.stdout => T3677.stdout}  |  0
 .../codeGen/should_run/{4441.hs => T4441.hs}  |  0
 .../should_run/{4441.stdout => T4441.stdout}  |  0
 .../codeGen/should_run/{5129.hs => T5129.hs}  |  0
 .../codeGen/should_run/{5149.hs => T5149.hs}  |  0
 .../should_run/{5149.stdout => T5149.stdout}  |  0
 .../{5149_cmm.cmm => T5149_cmm.cmm}           |  0
 .../codeGen/should_run/{5626.hs => T5626.hs}  |  0
 tests/codeGen/should_run/T5626.stderr         |  1 +
 .../codeGen/should_run/{5747.hs => T5747.hs}  |  0
 .../should_run/{5747.stdout => T5747.stdout}  |  0
 .../codeGen/should_run/{5785.hs => T5785.hs}  |  0
 .../should_run/{5785.stdout => T5785.stdout}  |  0
 .../codeGen/should_run/{6146.hs => T6146.hs}  |  0
 .../should_run/{6146.stdin => T6146.stdin}    |  0
 .../should_run/{6146.stdout => T6146.stdout}  |  0
 tests/codeGen/should_run/all.T                | 30 +++++++++----------
 39 files changed, 23 insertions(+), 23 deletions(-)
 rename tests/codeGen/should_compile/{1916.hs => T1916.hs} (100%)
 rename tests/codeGen/should_compile/{2388.hs => T2388.hs} (100%)
 rename tests/codeGen/should_compile/{2578.hs => T2578.hs} (100%)
 rename tests/codeGen/should_compile/{3132.hs => T3132.hs} (100%)
 rename tests/codeGen/should_compile/{3579.hs => T3579.hs} (100%)
 delete mode 100644 tests/codeGen/should_run/5626.stderr
 rename tests/codeGen/should_run/{1852.hs => T1852.hs} (100%)
 rename tests/codeGen/should_run/{1852.stdout => T1852.stdout} (100%)
 rename tests/codeGen/should_run/{1861.hs => T1861.hs} (100%)
 rename tests/codeGen/should_run/{1861.stdout => T1861.stdout} (100%)
 rename tests/codeGen/should_run/{2080.hs => T2080.hs} (100%)
 rename tests/codeGen/should_run/{2080.stdout => T2080.stdout} (100%)
 rename tests/codeGen/should_run/{2838.hs => T2838.hs} (100%)
 rename tests/codeGen/should_run/{2838.stdout => T2838.stdout} (100%)
 rename tests/codeGen/should_run/{2838.stdout-ws-64 => T2838.stdout-ws-64} (100%)
 rename tests/codeGen/should_run/{3207.hs => T3207.hs} (100%)
 rename tests/codeGen/should_run/{3207.stdout => T3207.stdout} (100%)
 rename tests/codeGen/should_run/{3561.hs => T3561.hs} (100%)
 rename tests/codeGen/should_run/{3561.stdout => T3561.stdout} (100%)
 rename tests/codeGen/should_run/{3677.hs => T3677.hs} (100%)
 rename tests/codeGen/should_run/{3677.stdout => T3677.stdout} (100%)
 rename tests/codeGen/should_run/{4441.hs => T4441.hs} (100%)
 rename tests/codeGen/should_run/{4441.stdout => T4441.stdout} (100%)
 rename tests/codeGen/should_run/{5129.hs => T5129.hs} (100%)
 rename tests/codeGen/should_run/{5149.hs => T5149.hs} (100%)
 rename tests/codeGen/should_run/{5149.stdout => T5149.stdout} (100%)
 rename tests/codeGen/should_run/{5149_cmm.cmm => T5149_cmm.cmm} (100%)
 rename tests/codeGen/should_run/{5626.hs => T5626.hs} (100%)
 create mode 100644 tests/codeGen/should_run/T5626.stderr
 rename tests/codeGen/should_run/{5747.hs => T5747.hs} (100%)
 rename tests/codeGen/should_run/{5747.stdout => T5747.stdout} (100%)
 rename tests/codeGen/should_run/{5785.hs => T5785.hs} (100%)
 rename tests/codeGen/should_run/{5785.stdout => T5785.stdout} (100%)
 rename tests/codeGen/should_run/{6146.hs => T6146.hs} (100%)
 rename tests/codeGen/should_run/{6146.stdin => T6146.stdin} (100%)
 rename tests/codeGen/should_run/{6146.stdout => T6146.stdout} (100%)

diff --git a/tests/codeGen/should_compile/Makefile b/tests/codeGen/should_compile/Makefile
index ff4309919..c804a12ea 100644
--- a/tests/codeGen/should_compile/Makefile
+++ b/tests/codeGen/should_compile/Makefile
@@ -2,6 +2,6 @@ TOP=../../..
 include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk
 
-2578:
-	'$(TEST_HC)' $(TEST_HC_OPTS) --make 2578 -fforce-recomp -v0
+T2578:
+	'$(TEST_HC)' $(TEST_HC_OPTS) --make T2578 -fforce-recomp -v0
 
diff --git a/tests/codeGen/should_compile/1916.hs b/tests/codeGen/should_compile/T1916.hs
similarity index 100%
rename from tests/codeGen/should_compile/1916.hs
rename to tests/codeGen/should_compile/T1916.hs
diff --git a/tests/codeGen/should_compile/2388.hs b/tests/codeGen/should_compile/T2388.hs
similarity index 100%
rename from tests/codeGen/should_compile/2388.hs
rename to tests/codeGen/should_compile/T2388.hs
diff --git a/tests/codeGen/should_compile/2578.hs b/tests/codeGen/should_compile/T2578.hs
similarity index 100%
rename from tests/codeGen/should_compile/2578.hs
rename to tests/codeGen/should_compile/T2578.hs
diff --git a/tests/codeGen/should_compile/3132.hs b/tests/codeGen/should_compile/T3132.hs
similarity index 100%
rename from tests/codeGen/should_compile/3132.hs
rename to tests/codeGen/should_compile/T3132.hs
diff --git a/tests/codeGen/should_compile/3579.hs b/tests/codeGen/should_compile/T3579.hs
similarity index 100%
rename from tests/codeGen/should_compile/3579.hs
rename to tests/codeGen/should_compile/T3579.hs
diff --git a/tests/codeGen/should_compile/all.T b/tests/codeGen/should_compile/all.T
index 77d7f0247..046d98ec5 100644
--- a/tests/codeGen/should_compile/all.T
+++ b/tests/codeGen/should_compile/all.T
@@ -7,13 +7,13 @@ test('cg006', normal, compile, [''])
 test('cg007', normal, compile, [''])
 test('cg008', normal, compile, [''])
 
-test('1916', normal, compile, [''])
-test('2388', normal, compile, [''])
-test('3132', normal, compile, ['-dcmm-lint'])
+test('T1916', normal, compile, [''])
+test('T2388', normal, compile, [''])
+test('T3132', normal, compile, ['-dcmm-lint'])
 test('T3286', extra_clean(['T3286b.o','T3286b.hi']), 
               multimod_compile, ['T3286', '-v0'])
-test('3579', normal, compile, [''])
-test('2578', normal, run_command, ['$MAKE -s --no-print-directory 2578'])
+test('T3579', normal, compile, [''])
+test('T2578', normal, run_command, ['$MAKE -s --no-print-directory T2578'])
 # skip llvm on i386 as we don't support fPIC
 test('jmp_tbl', if_arch('i386', omit_ways(['llvm', 'optllvm'])), compile, ['-fPIC -O'])
 test('massive_array',
diff --git a/tests/codeGen/should_run/5626.stderr b/tests/codeGen/should_run/5626.stderr
deleted file mode 100644
index 7cab83de7..000000000
--- a/tests/codeGen/should_run/5626.stderr
+++ /dev/null
@@ -1 +0,0 @@
-5626: Prelude.undefined
diff --git a/tests/codeGen/should_run/1852.hs b/tests/codeGen/should_run/T1852.hs
similarity index 100%
rename from tests/codeGen/should_run/1852.hs
rename to tests/codeGen/should_run/T1852.hs
diff --git a/tests/codeGen/should_run/1852.stdout b/tests/codeGen/should_run/T1852.stdout
similarity index 100%
rename from tests/codeGen/should_run/1852.stdout
rename to tests/codeGen/should_run/T1852.stdout
diff --git a/tests/codeGen/should_run/1861.hs b/tests/codeGen/should_run/T1861.hs
similarity index 100%
rename from tests/codeGen/should_run/1861.hs
rename to tests/codeGen/should_run/T1861.hs
diff --git a/tests/codeGen/should_run/1861.stdout b/tests/codeGen/should_run/T1861.stdout
similarity index 100%
rename from tests/codeGen/should_run/1861.stdout
rename to tests/codeGen/should_run/T1861.stdout
diff --git a/tests/codeGen/should_run/2080.hs b/tests/codeGen/should_run/T2080.hs
similarity index 100%
rename from tests/codeGen/should_run/2080.hs
rename to tests/codeGen/should_run/T2080.hs
diff --git a/tests/codeGen/should_run/2080.stdout b/tests/codeGen/should_run/T2080.stdout
similarity index 100%
rename from tests/codeGen/should_run/2080.stdout
rename to tests/codeGen/should_run/T2080.stdout
diff --git a/tests/codeGen/should_run/2838.hs b/tests/codeGen/should_run/T2838.hs
similarity index 100%
rename from tests/codeGen/should_run/2838.hs
rename to tests/codeGen/should_run/T2838.hs
diff --git a/tests/codeGen/should_run/2838.stdout b/tests/codeGen/should_run/T2838.stdout
similarity index 100%
rename from tests/codeGen/should_run/2838.stdout
rename to tests/codeGen/should_run/T2838.stdout
diff --git a/tests/codeGen/should_run/2838.stdout-ws-64 b/tests/codeGen/should_run/T2838.stdout-ws-64
similarity index 100%
rename from tests/codeGen/should_run/2838.stdout-ws-64
rename to tests/codeGen/should_run/T2838.stdout-ws-64
diff --git a/tests/codeGen/should_run/3207.hs b/tests/codeGen/should_run/T3207.hs
similarity index 100%
rename from tests/codeGen/should_run/3207.hs
rename to tests/codeGen/should_run/T3207.hs
diff --git a/tests/codeGen/should_run/3207.stdout b/tests/codeGen/should_run/T3207.stdout
similarity index 100%
rename from tests/codeGen/should_run/3207.stdout
rename to tests/codeGen/should_run/T3207.stdout
diff --git a/tests/codeGen/should_run/3561.hs b/tests/codeGen/should_run/T3561.hs
similarity index 100%
rename from tests/codeGen/should_run/3561.hs
rename to tests/codeGen/should_run/T3561.hs
diff --git a/tests/codeGen/should_run/3561.stdout b/tests/codeGen/should_run/T3561.stdout
similarity index 100%
rename from tests/codeGen/should_run/3561.stdout
rename to tests/codeGen/should_run/T3561.stdout
diff --git a/tests/codeGen/should_run/3677.hs b/tests/codeGen/should_run/T3677.hs
similarity index 100%
rename from tests/codeGen/should_run/3677.hs
rename to tests/codeGen/should_run/T3677.hs
diff --git a/tests/codeGen/should_run/3677.stdout b/tests/codeGen/should_run/T3677.stdout
similarity index 100%
rename from tests/codeGen/should_run/3677.stdout
rename to tests/codeGen/should_run/T3677.stdout
diff --git a/tests/codeGen/should_run/4441.hs b/tests/codeGen/should_run/T4441.hs
similarity index 100%
rename from tests/codeGen/should_run/4441.hs
rename to tests/codeGen/should_run/T4441.hs
diff --git a/tests/codeGen/should_run/4441.stdout b/tests/codeGen/should_run/T4441.stdout
similarity index 100%
rename from tests/codeGen/should_run/4441.stdout
rename to tests/codeGen/should_run/T4441.stdout
diff --git a/tests/codeGen/should_run/5129.hs b/tests/codeGen/should_run/T5129.hs
similarity index 100%
rename from tests/codeGen/should_run/5129.hs
rename to tests/codeGen/should_run/T5129.hs
diff --git a/tests/codeGen/should_run/5149.hs b/tests/codeGen/should_run/T5149.hs
similarity index 100%
rename from tests/codeGen/should_run/5149.hs
rename to tests/codeGen/should_run/T5149.hs
diff --git a/tests/codeGen/should_run/5149.stdout b/tests/codeGen/should_run/T5149.stdout
similarity index 100%
rename from tests/codeGen/should_run/5149.stdout
rename to tests/codeGen/should_run/T5149.stdout
diff --git a/tests/codeGen/should_run/5149_cmm.cmm b/tests/codeGen/should_run/T5149_cmm.cmm
similarity index 100%
rename from tests/codeGen/should_run/5149_cmm.cmm
rename to tests/codeGen/should_run/T5149_cmm.cmm
diff --git a/tests/codeGen/should_run/5626.hs b/tests/codeGen/should_run/T5626.hs
similarity index 100%
rename from tests/codeGen/should_run/5626.hs
rename to tests/codeGen/should_run/T5626.hs
diff --git a/tests/codeGen/should_run/T5626.stderr b/tests/codeGen/should_run/T5626.stderr
new file mode 100644
index 000000000..df9cfc932
--- /dev/null
+++ b/tests/codeGen/should_run/T5626.stderr
@@ -0,0 +1 @@
+T5626: Prelude.undefined
diff --git a/tests/codeGen/should_run/5747.hs b/tests/codeGen/should_run/T5747.hs
similarity index 100%
rename from tests/codeGen/should_run/5747.hs
rename to tests/codeGen/should_run/T5747.hs
diff --git a/tests/codeGen/should_run/5747.stdout b/tests/codeGen/should_run/T5747.stdout
similarity index 100%
rename from tests/codeGen/should_run/5747.stdout
rename to tests/codeGen/should_run/T5747.stdout
diff --git a/tests/codeGen/should_run/5785.hs b/tests/codeGen/should_run/T5785.hs
similarity index 100%
rename from tests/codeGen/should_run/5785.hs
rename to tests/codeGen/should_run/T5785.hs
diff --git a/tests/codeGen/should_run/5785.stdout b/tests/codeGen/should_run/T5785.stdout
similarity index 100%
rename from tests/codeGen/should_run/5785.stdout
rename to tests/codeGen/should_run/T5785.stdout
diff --git a/tests/codeGen/should_run/6146.hs b/tests/codeGen/should_run/T6146.hs
similarity index 100%
rename from tests/codeGen/should_run/6146.hs
rename to tests/codeGen/should_run/T6146.hs
diff --git a/tests/codeGen/should_run/6146.stdin b/tests/codeGen/should_run/T6146.stdin
similarity index 100%
rename from tests/codeGen/should_run/6146.stdin
rename to tests/codeGen/should_run/T6146.stdin
diff --git a/tests/codeGen/should_run/6146.stdout b/tests/codeGen/should_run/T6146.stdout
similarity index 100%
rename from tests/codeGen/should_run/6146.stdout
rename to tests/codeGen/should_run/T6146.stdout
diff --git a/tests/codeGen/should_run/all.T b/tests/codeGen/should_run/all.T
index a8c5a0a70..b12c30b8f 100644
--- a/tests/codeGen/should_run/all.T
+++ b/tests/codeGen/should_run/all.T
@@ -75,23 +75,23 @@ test('cgrun069', omit_ways(['ghci']), multi_compile_and_run,
 test('cgrun070', normal, compile_and_run, [''])
 test('cgrun071', normal, compile_and_run, [''])
 
-test('1852', normal, compile_and_run, [''])
-test('1861', extra_run_opts('0'), compile_and_run, [''])
-test('2080', normal, compile_and_run, [''])
-test('2838', normal, compile_and_run, [''])
-test('3207', normal, compile_and_run, [''])
-test('3561', normal, compile_and_run, [''])
-test('3677', extra_run_opts('+RTS -K8k -RTS'), compile_and_run, [''])
-test('4441', normal, compile_and_run, [''])
-test('5149', omit_ways(['ghci']), multi_compile_and_run,
-                 ['5149', [('5149_cmm.cmm', '')], ''])
-test('5129', normal, compile_and_run, [''])
-test('5626', exit_code(1), compile_and_run, [''])
-test('5747', if_arch('i386', extra_hc_opts('-msse2')), compile_and_run, ['-O2'])
-test('5785', normal, compile_and_run, [''])
+test('T1852', normal, compile_and_run, [''])
+test('T1861', extra_run_opts('0'), compile_and_run, [''])
+test('T2080', normal, compile_and_run, [''])
+test('T2838', normal, compile_and_run, [''])
+test('T3207', normal, compile_and_run, [''])
+test('T3561', normal, compile_and_run, [''])
+test('T3677', extra_run_opts('+RTS -K8k -RTS'), compile_and_run, [''])
+test('T4441', normal, compile_and_run, [''])
+test('T5149', omit_ways(['ghci']), multi_compile_and_run,
+                 ['T5149', [('T5149_cmm.cmm', '')], ''])
+test('T5129', normal, compile_and_run, [''])
+test('T5626', exit_code(1), compile_and_run, [''])
+test('T5747', if_arch('i386', extra_hc_opts('-msse2')), compile_and_run, ['-O2'])
+test('T5785', normal, compile_and_run, [''])
 test('setByteArray', normal, compile_and_run, [''])
 
-test('6146', normal, compile_and_run, [''])
+test('T6146', normal, compile_and_run, [''])
 test('T5900', normal, compile_and_run, [''])
 test('T7163', normal, compile_and_run, [''])
 
-- 
GitLab


From 70d30ab999680d5bb9b2b964efe52e1f083ceb77 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 14:35:53 +0000
Subject: [PATCH 041/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/concurrent/should_run/4030.stderr       |  1 -
 tests/concurrent/should_run/5611.stderr       |  1 -
 tests/concurrent/should_run/5866.stderr       |  1 -
 .../should_run/{1980.hs => T1980.hs}          |  0
 .../should_run/{2910.hs => T2910.hs}          |  0
 .../should_run/{2910.stdout => T2910.stdout}  |  0
 .../should_run/{2910a.hs => T2910a.hs}        |  0
 .../{2910a.stdout => T2910a.stdout}           |  0
 .../should_run/{3279.hs => T3279.hs}          |  0
 .../should_run/{3279.stdout => T3279.stdout}  |  0
 .../should_run/{3429.hs => T3429.hs}          |  0
 .../should_run/{3429.stdout => T3429.stdout}  |  0
 .../concurrent/should_run/{367.hs => T367.hs} |  0
 .../should_run/{367.stdout => T367.stdout}    |  0
 ...367_letnoescape.hs => T367_letnoescape.hs} |  0
 ...oescape.stdout => T367_letnoescape.stdout} |  0
 .../should_run/{4030.hs => T4030.hs}          |  0
 tests/concurrent/should_run/T4030.stderr      |  1 +
 .../should_run/{4262.hs => T4262.hs}          |  0
 .../should_run/{4262.stdout => T4262.stdout}  |  0
 .../should_run/{4811.hs => T4811.hs}          |  0
 .../should_run/{4813.hs => T4813.hs}          |  0
 .../should_run/{5238.hs => T5238.hs}          |  0
 .../should_run/{5238.stdout => T5238.stdout}  |  0
 .../should_run/{5421.hs => T5421.hs}          |  0
 .../should_run/{5558.hs => T5558.hs}          |  0
 .../should_run/{5611.hs => T5611.hs}          |  0
 tests/concurrent/should_run/T5611.stderr      |  1 +
 .../should_run/{5611.stdout => T5611.stdout}  |  0
 .../should_run/{5866.hs => T5866.hs}          |  0
 tests/concurrent/should_run/T5866.stderr      |  1 +
 tests/concurrent/should_run/all.T             | 40 +++++++++----------
 32 files changed, 23 insertions(+), 23 deletions(-)
 delete mode 100644 tests/concurrent/should_run/4030.stderr
 delete mode 100644 tests/concurrent/should_run/5611.stderr
 delete mode 100644 tests/concurrent/should_run/5866.stderr
 rename tests/concurrent/should_run/{1980.hs => T1980.hs} (100%)
 rename tests/concurrent/should_run/{2910.hs => T2910.hs} (100%)
 rename tests/concurrent/should_run/{2910.stdout => T2910.stdout} (100%)
 rename tests/concurrent/should_run/{2910a.hs => T2910a.hs} (100%)
 rename tests/concurrent/should_run/{2910a.stdout => T2910a.stdout} (100%)
 rename tests/concurrent/should_run/{3279.hs => T3279.hs} (100%)
 rename tests/concurrent/should_run/{3279.stdout => T3279.stdout} (100%)
 rename tests/concurrent/should_run/{3429.hs => T3429.hs} (100%)
 rename tests/concurrent/should_run/{3429.stdout => T3429.stdout} (100%)
 rename tests/concurrent/should_run/{367.hs => T367.hs} (100%)
 rename tests/concurrent/should_run/{367.stdout => T367.stdout} (100%)
 rename tests/concurrent/should_run/{367_letnoescape.hs => T367_letnoescape.hs} (100%)
 rename tests/concurrent/should_run/{367_letnoescape.stdout => T367_letnoescape.stdout} (100%)
 rename tests/concurrent/should_run/{4030.hs => T4030.hs} (100%)
 create mode 100644 tests/concurrent/should_run/T4030.stderr
 rename tests/concurrent/should_run/{4262.hs => T4262.hs} (100%)
 rename tests/concurrent/should_run/{4262.stdout => T4262.stdout} (100%)
 rename tests/concurrent/should_run/{4811.hs => T4811.hs} (100%)
 rename tests/concurrent/should_run/{4813.hs => T4813.hs} (100%)
 rename tests/concurrent/should_run/{5238.hs => T5238.hs} (100%)
 rename tests/concurrent/should_run/{5238.stdout => T5238.stdout} (100%)
 rename tests/concurrent/should_run/{5421.hs => T5421.hs} (100%)
 rename tests/concurrent/should_run/{5558.hs => T5558.hs} (100%)
 rename tests/concurrent/should_run/{5611.hs => T5611.hs} (100%)
 create mode 100644 tests/concurrent/should_run/T5611.stderr
 rename tests/concurrent/should_run/{5611.stdout => T5611.stdout} (100%)
 rename tests/concurrent/should_run/{5866.hs => T5866.hs} (100%)
 create mode 100644 tests/concurrent/should_run/T5866.stderr

diff --git a/tests/concurrent/should_run/4030.stderr b/tests/concurrent/should_run/4030.stderr
deleted file mode 100644
index 0e2a7bfc1..000000000
--- a/tests/concurrent/should_run/4030.stderr
+++ /dev/null
@@ -1 +0,0 @@
-4030: <<loop>>
diff --git a/tests/concurrent/should_run/5611.stderr b/tests/concurrent/should_run/5611.stderr
deleted file mode 100644
index 7a7f2c7ac..000000000
--- a/tests/concurrent/should_run/5611.stderr
+++ /dev/null
@@ -1 +0,0 @@
-5611: user error (Exception delivered successfully)
diff --git a/tests/concurrent/should_run/5866.stderr b/tests/concurrent/should_run/5866.stderr
deleted file mode 100644
index a4774f25a..000000000
--- a/tests/concurrent/should_run/5866.stderr
+++ /dev/null
@@ -1 +0,0 @@
-5866: thread blocked indefinitely in an STM transaction
diff --git a/tests/concurrent/should_run/1980.hs b/tests/concurrent/should_run/T1980.hs
similarity index 100%
rename from tests/concurrent/should_run/1980.hs
rename to tests/concurrent/should_run/T1980.hs
diff --git a/tests/concurrent/should_run/2910.hs b/tests/concurrent/should_run/T2910.hs
similarity index 100%
rename from tests/concurrent/should_run/2910.hs
rename to tests/concurrent/should_run/T2910.hs
diff --git a/tests/concurrent/should_run/2910.stdout b/tests/concurrent/should_run/T2910.stdout
similarity index 100%
rename from tests/concurrent/should_run/2910.stdout
rename to tests/concurrent/should_run/T2910.stdout
diff --git a/tests/concurrent/should_run/2910a.hs b/tests/concurrent/should_run/T2910a.hs
similarity index 100%
rename from tests/concurrent/should_run/2910a.hs
rename to tests/concurrent/should_run/T2910a.hs
diff --git a/tests/concurrent/should_run/2910a.stdout b/tests/concurrent/should_run/T2910a.stdout
similarity index 100%
rename from tests/concurrent/should_run/2910a.stdout
rename to tests/concurrent/should_run/T2910a.stdout
diff --git a/tests/concurrent/should_run/3279.hs b/tests/concurrent/should_run/T3279.hs
similarity index 100%
rename from tests/concurrent/should_run/3279.hs
rename to tests/concurrent/should_run/T3279.hs
diff --git a/tests/concurrent/should_run/3279.stdout b/tests/concurrent/should_run/T3279.stdout
similarity index 100%
rename from tests/concurrent/should_run/3279.stdout
rename to tests/concurrent/should_run/T3279.stdout
diff --git a/tests/concurrent/should_run/3429.hs b/tests/concurrent/should_run/T3429.hs
similarity index 100%
rename from tests/concurrent/should_run/3429.hs
rename to tests/concurrent/should_run/T3429.hs
diff --git a/tests/concurrent/should_run/3429.stdout b/tests/concurrent/should_run/T3429.stdout
similarity index 100%
rename from tests/concurrent/should_run/3429.stdout
rename to tests/concurrent/should_run/T3429.stdout
diff --git a/tests/concurrent/should_run/367.hs b/tests/concurrent/should_run/T367.hs
similarity index 100%
rename from tests/concurrent/should_run/367.hs
rename to tests/concurrent/should_run/T367.hs
diff --git a/tests/concurrent/should_run/367.stdout b/tests/concurrent/should_run/T367.stdout
similarity index 100%
rename from tests/concurrent/should_run/367.stdout
rename to tests/concurrent/should_run/T367.stdout
diff --git a/tests/concurrent/should_run/367_letnoescape.hs b/tests/concurrent/should_run/T367_letnoescape.hs
similarity index 100%
rename from tests/concurrent/should_run/367_letnoescape.hs
rename to tests/concurrent/should_run/T367_letnoescape.hs
diff --git a/tests/concurrent/should_run/367_letnoescape.stdout b/tests/concurrent/should_run/T367_letnoescape.stdout
similarity index 100%
rename from tests/concurrent/should_run/367_letnoescape.stdout
rename to tests/concurrent/should_run/T367_letnoescape.stdout
diff --git a/tests/concurrent/should_run/4030.hs b/tests/concurrent/should_run/T4030.hs
similarity index 100%
rename from tests/concurrent/should_run/4030.hs
rename to tests/concurrent/should_run/T4030.hs
diff --git a/tests/concurrent/should_run/T4030.stderr b/tests/concurrent/should_run/T4030.stderr
new file mode 100644
index 000000000..428476bb8
--- /dev/null
+++ b/tests/concurrent/should_run/T4030.stderr
@@ -0,0 +1 @@
+T4030: <<loop>>
diff --git a/tests/concurrent/should_run/4262.hs b/tests/concurrent/should_run/T4262.hs
similarity index 100%
rename from tests/concurrent/should_run/4262.hs
rename to tests/concurrent/should_run/T4262.hs
diff --git a/tests/concurrent/should_run/4262.stdout b/tests/concurrent/should_run/T4262.stdout
similarity index 100%
rename from tests/concurrent/should_run/4262.stdout
rename to tests/concurrent/should_run/T4262.stdout
diff --git a/tests/concurrent/should_run/4811.hs b/tests/concurrent/should_run/T4811.hs
similarity index 100%
rename from tests/concurrent/should_run/4811.hs
rename to tests/concurrent/should_run/T4811.hs
diff --git a/tests/concurrent/should_run/4813.hs b/tests/concurrent/should_run/T4813.hs
similarity index 100%
rename from tests/concurrent/should_run/4813.hs
rename to tests/concurrent/should_run/T4813.hs
diff --git a/tests/concurrent/should_run/5238.hs b/tests/concurrent/should_run/T5238.hs
similarity index 100%
rename from tests/concurrent/should_run/5238.hs
rename to tests/concurrent/should_run/T5238.hs
diff --git a/tests/concurrent/should_run/5238.stdout b/tests/concurrent/should_run/T5238.stdout
similarity index 100%
rename from tests/concurrent/should_run/5238.stdout
rename to tests/concurrent/should_run/T5238.stdout
diff --git a/tests/concurrent/should_run/5421.hs b/tests/concurrent/should_run/T5421.hs
similarity index 100%
rename from tests/concurrent/should_run/5421.hs
rename to tests/concurrent/should_run/T5421.hs
diff --git a/tests/concurrent/should_run/5558.hs b/tests/concurrent/should_run/T5558.hs
similarity index 100%
rename from tests/concurrent/should_run/5558.hs
rename to tests/concurrent/should_run/T5558.hs
diff --git a/tests/concurrent/should_run/5611.hs b/tests/concurrent/should_run/T5611.hs
similarity index 100%
rename from tests/concurrent/should_run/5611.hs
rename to tests/concurrent/should_run/T5611.hs
diff --git a/tests/concurrent/should_run/T5611.stderr b/tests/concurrent/should_run/T5611.stderr
new file mode 100644
index 000000000..6fdc96912
--- /dev/null
+++ b/tests/concurrent/should_run/T5611.stderr
@@ -0,0 +1 @@
+T5611: user error (Exception delivered successfully)
diff --git a/tests/concurrent/should_run/5611.stdout b/tests/concurrent/should_run/T5611.stdout
similarity index 100%
rename from tests/concurrent/should_run/5611.stdout
rename to tests/concurrent/should_run/T5611.stdout
diff --git a/tests/concurrent/should_run/5866.hs b/tests/concurrent/should_run/T5866.hs
similarity index 100%
rename from tests/concurrent/should_run/5866.hs
rename to tests/concurrent/should_run/T5866.hs
diff --git a/tests/concurrent/should_run/T5866.stderr b/tests/concurrent/should_run/T5866.stderr
new file mode 100644
index 000000000..f2d13997e
--- /dev/null
+++ b/tests/concurrent/should_run/T5866.stderr
@@ -0,0 +1 @@
+T5866: thread blocked indefinitely in an STM transaction
diff --git a/tests/concurrent/should_run/all.T b/tests/concurrent/should_run/all.T
index 71b821f47..356cdbc6b 100644
--- a/tests/concurrent/should_run/all.T
+++ b/tests/concurrent/should_run/all.T
@@ -22,20 +22,20 @@ test('conc072', only_ways(['threaded2']), compile_and_run, [''])
 test('conc073', normal, compile_and_run, [''])
 
 # vector code must get inlined to become non-allocating
-test('367', composes([reqlib('vector'), timeout_multiplier(0.001)]), compile_and_run, ['-O2 -fno-omit-yields'])
-test('367_letnoescape', composes([timeout_multiplier(0.001)]), compile_and_run, ['-fno-omit-yields'])
+test('T367', composes([reqlib('vector'), timeout_multiplier(0.001)]), compile_and_run, ['-O2 -fno-omit-yields'])
+test('T367_letnoescape', composes([timeout_multiplier(0.001)]), compile_and_run, ['-fno-omit-yields'])
 
-test('1980', normal, compile_and_run, [''])
-test('2910', normal, compile_and_run, [''])
-test('2910a', normal, compile_and_run, [''])
-test('3279', normal, compile_and_run, [''])
+test('T1980', normal, compile_and_run, [''])
+test('T2910', normal, compile_and_run, [''])
+test('T2910a', normal, compile_and_run, [''])
+test('T3279', normal, compile_and_run, [''])
 
 # This test takes a long time with the default context switch interval
-test('3429', extra_run_opts('+RTS -C0.001 -RTS'), compile_and_run, [''])
+test('T3429', extra_run_opts('+RTS -C0.001 -RTS'), compile_and_run, [''])
 
 # without -O, goes into an infinite loop
 # GHCi does not detect the infinite loop.  We should really fix this.
-test('4030', omit_ways('ghci'), compile_and_run, ['-O'])
+test('T4030', omit_ways('ghci'), compile_and_run, ['-O'])
 
 # each of these runs for about a second
 test('throwto001', [reqlib('random'), extra_run_opts('1000 2000')],
@@ -50,29 +50,29 @@ test('async001', normal, compile_and_run, [''])
 
 test('numsparks001', only_ways(['threaded1']), compile_and_run, [''])
 
-test('4262', [ skip, # skip for now, it doesn't give reliable results
-               only_ways(['threaded1']),
-               unless_os('linux',skip),
-               if_compiler_lt('ghc', '7.1', expect_fail) ],
-             compile_and_run, [''])
+test('T4262', [ skip, # skip for now, it doesn't give reliable results
+                only_ways(['threaded1']),
+                unless_os('linux',skip),
+                if_compiler_lt('ghc', '7.1', expect_fail) ],
+              compile_and_run, [''])
 
-test('4813', normal, compile_and_run, [''])
-test('4811', normal, compile_and_run, [''])
+test('T4813', normal, compile_and_run, [''])
+test('T4811', normal, compile_and_run, [''])
 
 test('allowinterrupt001', normal, compile_and_run, [''])
 
 # try hard to provoke the error by running the test 100 times
-test('5558',
+test('T5558',
      [ only_ways(['threaded2']),
        cmd_wrapper(
          lambda c: "for i in %s; do %s || break; done"  %
            (" ".join(str(i) for i in range(1,101)), c)) ],
      compile_and_run, [''])
 
-test('5421', normal, compile_and_run, [''])
-test('5611', normal, compile_and_run, [''])
-test('5238', normal, compile_and_run, [''])
-test('5866', exit_code(1), compile_and_run, [''])
+test('T5421', normal, compile_and_run, [''])
+test('T5611', normal, compile_and_run, [''])
+test('T5238', normal, compile_and_run, [''])
+test('T5866', exit_code(1), compile_and_run, [''])
 
 # -----------------------------------------------------------------------------
 # These tests we only do for a full run
-- 
GitLab


From 014c90c080e5d25ea4ccd713881143ec5054cc45 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 14:48:26 +0000
Subject: [PATCH 042/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/rts/2783.stderr                         |  1 -
 tests/rts/5644/all.T                          |  7 ----
 tests/rts/7087.stderr                         |  1 -
 tests/rts/Makefile                            | 10 ++---
 tests/rts/{2047.hs => T2047.hs}               |  0
 tests/rts/{2783.hs => T2783.hs}               |  0
 tests/rts/T2783.stderr                        |  1 +
 tests/rts/{3236.c => T3236.c}                 |  0
 tests/rts/{3236.stderr => T3236.stderr}       |  0
 tests/rts/{3424.hs => T3424.hs}               |  0
 tests/rts/{3424.stdout => T3424.stdout}       |  0
 tests/rts/{4850.hs => T4850.hs}               |  0
 tests/rts/{4850.stdout => T4850.stdout}       |  0
 tests/rts/{5250.hs => T5250.hs}               |  0
 tests/rts/{5644 => T5644}/Conf.hs             |  0
 tests/rts/{5644 => T5644}/Makefile            |  0
 tests/rts/{5644 => T5644}/ManyQueue.hs        |  0
 .../{5644/5644.stderr => T5644/T5644.stderr}  |  2 +-
 tests/rts/{5644 => T5644}/Util.hs             |  0
 tests/rts/T5644/all.T                         |  7 ++++
 tests/rts/{5644 => T5644}/heap-overflow.hs    |  0
 tests/rts/{5993.hs => T5993.hs}               |  0
 tests/rts/{5993.stdout => T5993.stdout}       |  0
 tests/rts/{7087.hs => T7087.hs}               |  0
 tests/rts/T7087.stderr                        |  1 +
 tests/rts/all.T                               | 40 +++++++++----------
 26 files changed, 35 insertions(+), 35 deletions(-)
 delete mode 100644 tests/rts/2783.stderr
 delete mode 100644 tests/rts/5644/all.T
 delete mode 100644 tests/rts/7087.stderr
 rename tests/rts/{2047.hs => T2047.hs} (100%)
 rename tests/rts/{2783.hs => T2783.hs} (100%)
 create mode 100644 tests/rts/T2783.stderr
 rename tests/rts/{3236.c => T3236.c} (100%)
 rename tests/rts/{3236.stderr => T3236.stderr} (100%)
 rename tests/rts/{3424.hs => T3424.hs} (100%)
 rename tests/rts/{3424.stdout => T3424.stdout} (100%)
 rename tests/rts/{4850.hs => T4850.hs} (100%)
 rename tests/rts/{4850.stdout => T4850.stdout} (100%)
 rename tests/rts/{5250.hs => T5250.hs} (100%)
 rename tests/rts/{5644 => T5644}/Conf.hs (100%)
 rename tests/rts/{5644 => T5644}/Makefile (100%)
 rename tests/rts/{5644 => T5644}/ManyQueue.hs (100%)
 rename tests/rts/{5644/5644.stderr => T5644/T5644.stderr} (79%)
 rename tests/rts/{5644 => T5644}/Util.hs (100%)
 create mode 100644 tests/rts/T5644/all.T
 rename tests/rts/{5644 => T5644}/heap-overflow.hs (100%)
 rename tests/rts/{5993.hs => T5993.hs} (100%)
 rename tests/rts/{5993.stdout => T5993.stdout} (100%)
 rename tests/rts/{7087.hs => T7087.hs} (100%)
 create mode 100644 tests/rts/T7087.stderr

diff --git a/tests/rts/2783.stderr b/tests/rts/2783.stderr
deleted file mode 100644
index 86d45f2a1..000000000
--- a/tests/rts/2783.stderr
+++ /dev/null
@@ -1 +0,0 @@
-2783: <<loop>>
diff --git a/tests/rts/5644/all.T b/tests/rts/5644/all.T
deleted file mode 100644
index bd820d5f7..000000000
--- a/tests/rts/5644/all.T
+++ /dev/null
@@ -1,7 +0,0 @@
-test('5644', [
-               only_ways(['optasm','threaded1','threaded2']),
-               extra_run_opts('+RTS -M20m -RTS'),
-               exit_code(251) # RTS exit code for "out of memory"
-             ],
-             multimod_compile_and_run,
-             ['heap-overflow.hs','-O'])
diff --git a/tests/rts/7087.stderr b/tests/rts/7087.stderr
deleted file mode 100644
index d3a25047e..000000000
--- a/tests/rts/7087.stderr
+++ /dev/null
@@ -1 +0,0 @@
-7087: thread killed
diff --git a/tests/rts/Makefile b/tests/rts/Makefile
index 7f7781f31..2eb952df2 100644
--- a/tests/rts/Makefile
+++ b/tests/rts/Makefile
@@ -31,11 +31,11 @@ exec_signals-prep:
 	$(CC) -o exec_signals_child exec_signals_child.c
 	$(CC) -o exec_signals_prepare exec_signals_prepare.c
 
-.PHONY: 4850
-4850:
-	$(RM) 4850.o 4850.hi 4850$(exeext)
-	"$(TEST_HC)" $(TEST_HC_OPTS) -v0 -rtsopts -debug -threaded --make 4850
-	./4850 +RTS -s 2>&1 | grep TASKS | sed 's/^ *TASKS: *\([0-9]*\).*$$/\1/'
+.PHONY: T4850
+T4850:
+	$(RM) T4850.o T4850.hi T4850$(exeext)
+	"$(TEST_HC)" $(TEST_HC_OPTS) -v0 -rtsopts -debug -threaded --make T4850
+	./T4850 +RTS -s 2>&1 | grep TASKS | sed 's/^ *TASKS: *\([0-9]*\).*$$/\1/'
 
 .PHONY: T5423
 T5423:
diff --git a/tests/rts/2047.hs b/tests/rts/T2047.hs
similarity index 100%
rename from tests/rts/2047.hs
rename to tests/rts/T2047.hs
diff --git a/tests/rts/2783.hs b/tests/rts/T2783.hs
similarity index 100%
rename from tests/rts/2783.hs
rename to tests/rts/T2783.hs
diff --git a/tests/rts/T2783.stderr b/tests/rts/T2783.stderr
new file mode 100644
index 000000000..4ea4fc816
--- /dev/null
+++ b/tests/rts/T2783.stderr
@@ -0,0 +1 @@
+T2783: <<loop>>
diff --git a/tests/rts/3236.c b/tests/rts/T3236.c
similarity index 100%
rename from tests/rts/3236.c
rename to tests/rts/T3236.c
diff --git a/tests/rts/3236.stderr b/tests/rts/T3236.stderr
similarity index 100%
rename from tests/rts/3236.stderr
rename to tests/rts/T3236.stderr
diff --git a/tests/rts/3424.hs b/tests/rts/T3424.hs
similarity index 100%
rename from tests/rts/3424.hs
rename to tests/rts/T3424.hs
diff --git a/tests/rts/3424.stdout b/tests/rts/T3424.stdout
similarity index 100%
rename from tests/rts/3424.stdout
rename to tests/rts/T3424.stdout
diff --git a/tests/rts/4850.hs b/tests/rts/T4850.hs
similarity index 100%
rename from tests/rts/4850.hs
rename to tests/rts/T4850.hs
diff --git a/tests/rts/4850.stdout b/tests/rts/T4850.stdout
similarity index 100%
rename from tests/rts/4850.stdout
rename to tests/rts/T4850.stdout
diff --git a/tests/rts/5250.hs b/tests/rts/T5250.hs
similarity index 100%
rename from tests/rts/5250.hs
rename to tests/rts/T5250.hs
diff --git a/tests/rts/5644/Conf.hs b/tests/rts/T5644/Conf.hs
similarity index 100%
rename from tests/rts/5644/Conf.hs
rename to tests/rts/T5644/Conf.hs
diff --git a/tests/rts/5644/Makefile b/tests/rts/T5644/Makefile
similarity index 100%
rename from tests/rts/5644/Makefile
rename to tests/rts/T5644/Makefile
diff --git a/tests/rts/5644/ManyQueue.hs b/tests/rts/T5644/ManyQueue.hs
similarity index 100%
rename from tests/rts/5644/ManyQueue.hs
rename to tests/rts/T5644/ManyQueue.hs
diff --git a/tests/rts/5644/5644.stderr b/tests/rts/T5644/T5644.stderr
similarity index 79%
rename from tests/rts/5644/5644.stderr
rename to tests/rts/T5644/T5644.stderr
index c0e6e69be..198dceb2b 100644
--- a/tests/rts/5644/5644.stderr
+++ b/tests/rts/T5644/T5644.stderr
@@ -1,3 +1,3 @@
-5644: Heap exhausted;
+T5644: Heap exhausted;
 Current maximum heap size is 20971520 bytes (20 MB);
 use `+RTS -M<size>' to increase it.
diff --git a/tests/rts/5644/Util.hs b/tests/rts/T5644/Util.hs
similarity index 100%
rename from tests/rts/5644/Util.hs
rename to tests/rts/T5644/Util.hs
diff --git a/tests/rts/T5644/all.T b/tests/rts/T5644/all.T
new file mode 100644
index 000000000..4b2332bbc
--- /dev/null
+++ b/tests/rts/T5644/all.T
@@ -0,0 +1,7 @@
+test('T5644', [
+                only_ways(['optasm','threaded1','threaded2']),
+                extra_run_opts('+RTS -M20m -RTS'),
+                exit_code(251) # RTS exit code for "out of memory"
+              ],
+              multimod_compile_and_run,
+              ['heap-overflow.hs','-O'])
diff --git a/tests/rts/5644/heap-overflow.hs b/tests/rts/T5644/heap-overflow.hs
similarity index 100%
rename from tests/rts/5644/heap-overflow.hs
rename to tests/rts/T5644/heap-overflow.hs
diff --git a/tests/rts/5993.hs b/tests/rts/T5993.hs
similarity index 100%
rename from tests/rts/5993.hs
rename to tests/rts/T5993.hs
diff --git a/tests/rts/5993.stdout b/tests/rts/T5993.stdout
similarity index 100%
rename from tests/rts/5993.stdout
rename to tests/rts/T5993.stdout
diff --git a/tests/rts/7087.hs b/tests/rts/T7087.hs
similarity index 100%
rename from tests/rts/7087.hs
rename to tests/rts/T7087.hs
diff --git a/tests/rts/T7087.stderr b/tests/rts/T7087.stderr
new file mode 100644
index 000000000..5754987f4
--- /dev/null
+++ b/tests/rts/T7087.stderr
@@ -0,0 +1 @@
+T7087: thread killed
diff --git a/tests/rts/all.T b/tests/rts/all.T
index d69d211ed..18617bd74 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -42,12 +42,12 @@ test('outofmem', if_os('darwin', skip),
 test('outofmem2', extra_run_opts('+RTS -M5m -RTS'),
                   run_command, ['$MAKE -s --no-print-directory outofmem2'])
 
-test('2047', compose(ignore_output, extra_run_opts('+RTS -c -RTS')),
-             compile_and_run, ['-package containers'])
+test('T2047', compose(ignore_output, extra_run_opts('+RTS -c -RTS')),
+              compile_and_run, ['-package containers'])
 
 # Blackhole-detection test.
 # Skip GHCi due to #2786
-test('2783', [ omit_ways(['ghci']), exit_code(1) ], compile_and_run, [''])
+test('T2783', [ omit_ways(['ghci']), exit_code(1) ], compile_and_run, [''])
 
 # Test the work-stealing deque implementation.  We run this test in
 # both threaded1 (-threaded -debug) and threaded2 (-threaded) ways.
@@ -55,7 +55,7 @@ test('testwsdeque', [unless_in_tree_compiler(skip),
                     c_src, only_ways(['threaded1', 'threaded2'])],
                     compile_and_run, ['-I../../../rts'])
 
-test('3236', [c_src, only_ways(['normal','threaded1']), exit_code(1)], compile_and_run, [''])
+test('T3236', [c_src, only_ways(['normal','threaded1']), exit_code(1)], compile_and_run, [''])
 
 test('stack001', extra_run_opts('+RTS -K32m -RTS'), compile_and_run, [''])
 test('stack002', extra_run_opts('+RTS -K32m -k4m -RTS'), compile_and_run, [''])
@@ -68,9 +68,9 @@ test('stack003', [ omit_ways('ghci'), # uses unboxed tuples
 
 test('atomicinc', [ c_src, only_ways(['normal']) ], compile_and_run, [''])
 
-test('3424', # it's slow:
-             [ skip_if_fast, only_ways(['normal','threaded1','ghci']) ],
-             compile_and_run, [''])
+test('T3424', # it's slow:
+              [ skip_if_fast, only_ways(['normal','threaded1','ghci']) ],
+              compile_and_run, [''])
 
 # Test for out-of-range heap size
 test('rtsflags001', [ only_ways(['normal']), exit_code(1), extra_run_opts('+RTS -H0m -RTS') ], compile_and_run, [''])
@@ -112,28 +112,28 @@ test('exec_signals', [
 
 test('return_mem_to_os', normal, compile_and_run, [''])
 
-test('4850', extra_clean(['4850.o','4850.hi','4850']),
-             run_command, ['$MAKE -s --no-print-directory 4850'])
+test('T4850', extra_clean(['T4850.o','T4850.hi','T4850']),
+             run_command, ['$MAKE -s --no-print-directory T4850'])
 
-def config_5250(opts):
+def config_T5250(opts):
     if not (config.arch in ['i386','x86_64']):
         opts.skip = 1;
 
-test('5250', [ config_5250,
-               # stack ptr is not 16-byte aligned on 32-bit Windows
-               if_platform('i386-unknown-mingw32', expect_fail),
-               if_platform('i386-unknown-linux',
-                           expect_broken_for(4211,['llvm'])),
-               extra_clean(['spalign.o']),
-               omit_ways(['ghci']) ],
-             compile_and_run, ['spalign.c'])
+test('T5250', [ config_T5250,
+                # stack ptr is not 16-byte aligned on 32-bit Windows
+                if_platform('i386-unknown-mingw32', expect_fail),
+                if_platform('i386-unknown-linux',
+                            expect_broken_for(4211,['llvm'])),
+                extra_clean(['spalign.o']),
+                omit_ways(['ghci']) ],
+              compile_and_run, ['spalign.c'])
 
 test('T5423',
      extra_clean(['T5423_cmm.o']),
      run_command,
      ['$MAKE -s --no-print-directory T5423'])
 
-test('5993', extra_run_opts('+RTS -k8 -RTS'), compile_and_run, [''])
+test('T5993', extra_run_opts('+RTS -k8 -RTS'), compile_and_run, [''])
 
 test('T6006', [ omit_ways(prof_ways + ['ghci']),
                  extra_clean(['T6006_c.o']),
@@ -148,7 +148,7 @@ test('T7037',
      run_command,
      ['$MAKE -s --no-print-directory T7037'])
 
-test('7087', exit_code(1), compile_and_run, [''])
+test('T7087', exit_code(1), compile_and_run, [''])
 test('T7160', normal, compile_and_run, [''])
 
 test('T7040', [ extra_clean(['T7040_c.o']), omit_ways(['ghci']) ],
-- 
GitLab


From 85608fe66b06cb617092aa353fcdf4d358c36381 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 14:50:49 +0000
Subject: [PATCH 043/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/ghci/scripts/{1914.script => T1914.script} |  0
 tests/ghci/scripts/{1914.stderr => T1914.stderr} |  0
 tests/ghci/scripts/{1914.stdout => T1914.stdout} |  0
 tests/ghci/scripts/{2452.script => T2452.script} |  0
 tests/ghci/scripts/{2452.stderr => T2452.stderr} |  0
 tests/ghci/scripts/{2816.script => T2816.script} |  0
 tests/ghci/scripts/{2816.stderr => T2816.stderr} |  0
 tests/ghci/scripts/{2816.stdout => T2816.stdout} |  0
 tests/ghci/scripts/{2976.script => T2976.script} |  0
 tests/ghci/scripts/{2976.stdout => T2976.stdout} |  0
 tests/ghci/scripts/{4051.hs => T4051.hs}         |  0
 tests/ghci/scripts/{4051.script => T4051.script} |  2 +-
 tests/ghci/scripts/{4051.stdout => T4051.stdout} |  0
 tests/ghci/scripts/all.T                         | 12 ++++++------
 14 files changed, 7 insertions(+), 7 deletions(-)
 rename tests/ghci/scripts/{1914.script => T1914.script} (100%)
 rename tests/ghci/scripts/{1914.stderr => T1914.stderr} (100%)
 rename tests/ghci/scripts/{1914.stdout => T1914.stdout} (100%)
 rename tests/ghci/scripts/{2452.script => T2452.script} (100%)
 rename tests/ghci/scripts/{2452.stderr => T2452.stderr} (100%)
 rename tests/ghci/scripts/{2816.script => T2816.script} (100%)
 rename tests/ghci/scripts/{2816.stderr => T2816.stderr} (100%)
 rename tests/ghci/scripts/{2816.stdout => T2816.stdout} (100%)
 rename tests/ghci/scripts/{2976.script => T2976.script} (100%)
 rename tests/ghci/scripts/{2976.stdout => T2976.stdout} (100%)
 rename tests/ghci/scripts/{4051.hs => T4051.hs} (100%)
 rename tests/ghci/scripts/{4051.script => T4051.script} (55%)
 rename tests/ghci/scripts/{4051.stdout => T4051.stdout} (100%)

diff --git a/tests/ghci/scripts/1914.script b/tests/ghci/scripts/T1914.script
similarity index 100%
rename from tests/ghci/scripts/1914.script
rename to tests/ghci/scripts/T1914.script
diff --git a/tests/ghci/scripts/1914.stderr b/tests/ghci/scripts/T1914.stderr
similarity index 100%
rename from tests/ghci/scripts/1914.stderr
rename to tests/ghci/scripts/T1914.stderr
diff --git a/tests/ghci/scripts/1914.stdout b/tests/ghci/scripts/T1914.stdout
similarity index 100%
rename from tests/ghci/scripts/1914.stdout
rename to tests/ghci/scripts/T1914.stdout
diff --git a/tests/ghci/scripts/2452.script b/tests/ghci/scripts/T2452.script
similarity index 100%
rename from tests/ghci/scripts/2452.script
rename to tests/ghci/scripts/T2452.script
diff --git a/tests/ghci/scripts/2452.stderr b/tests/ghci/scripts/T2452.stderr
similarity index 100%
rename from tests/ghci/scripts/2452.stderr
rename to tests/ghci/scripts/T2452.stderr
diff --git a/tests/ghci/scripts/2816.script b/tests/ghci/scripts/T2816.script
similarity index 100%
rename from tests/ghci/scripts/2816.script
rename to tests/ghci/scripts/T2816.script
diff --git a/tests/ghci/scripts/2816.stderr b/tests/ghci/scripts/T2816.stderr
similarity index 100%
rename from tests/ghci/scripts/2816.stderr
rename to tests/ghci/scripts/T2816.stderr
diff --git a/tests/ghci/scripts/2816.stdout b/tests/ghci/scripts/T2816.stdout
similarity index 100%
rename from tests/ghci/scripts/2816.stdout
rename to tests/ghci/scripts/T2816.stdout
diff --git a/tests/ghci/scripts/2976.script b/tests/ghci/scripts/T2976.script
similarity index 100%
rename from tests/ghci/scripts/2976.script
rename to tests/ghci/scripts/T2976.script
diff --git a/tests/ghci/scripts/2976.stdout b/tests/ghci/scripts/T2976.stdout
similarity index 100%
rename from tests/ghci/scripts/2976.stdout
rename to tests/ghci/scripts/T2976.stdout
diff --git a/tests/ghci/scripts/4051.hs b/tests/ghci/scripts/T4051.hs
similarity index 100%
rename from tests/ghci/scripts/4051.hs
rename to tests/ghci/scripts/T4051.hs
diff --git a/tests/ghci/scripts/4051.script b/tests/ghci/scripts/T4051.script
similarity index 55%
rename from tests/ghci/scripts/4051.script
rename to tests/ghci/scripts/T4051.script
index 545ce8b4d..9c4dd1d1b 100644
--- a/tests/ghci/scripts/4051.script
+++ b/tests/ghci/scripts/T4051.script
@@ -1,4 +1,4 @@
-:l 4051.hs
+:l T4051.hs
 :m -X'
 :m X'
 x
diff --git a/tests/ghci/scripts/4051.stdout b/tests/ghci/scripts/T4051.stdout
similarity index 100%
rename from tests/ghci/scripts/4051.stdout
rename to tests/ghci/scripts/T4051.stdout
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index 317a34605..e44aa6c34 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -84,19 +84,19 @@ test('ghci056',
 
 test('ghci057', normal, ghci_script, ['ghci057.script'])
 
-test('2452', normal, ghci_script, ['2452.script'])
+test('T2452', normal, ghci_script, ['T2452.script'])
 test('T2766', normal, ghci_script, ['T2766.script'])
 
-test('1914',
+test('T1914',
      extra_clean(['T1914A.hs', 'T1914B.hs']),
      ghci_script,
-     ['1914.script'])
+     ['T1914.script'])
 
-test('2976', normal, ghci_script, ['2976.script'])
-test('2816', normal, ghci_script, ['2816.script'])
+test('T2976', normal, ghci_script, ['T2976.script'])
+test('T2816', normal, ghci_script, ['T2816.script'])
 test('T789', normal, ghci_script, ['T789.script'])
 test('T3263', normal, ghci_script, ['T3263.script'])
-test('4051', normal, ghci_script, ['4051.script'])
+test('T4051', normal, ghci_script, ['T4051.script'])
 test('T4087', normal, ghci_script, ['T4087.script'])
 test('T4015', normal, ghci_script, ['T4015.script'])
 test('T4127', normal, ghci_script, ['T4127.script'])
-- 
GitLab


From ebeb2f31d1d5c75c4462f839f92875e2735ab2fb Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 15:21:05 +0000
Subject: [PATCH 044/223] Rename some numeric tests: nnnn -> Tnnnn

---
 .../ffi/should_compile/{1357.hs => T1357.hs}  |  0
 .../{1357.stderr => T1357.stderr}             |  2 +-
 .../ffi/should_compile/{3624.hs => T3624.hs}  |  0
 .../ffi/should_compile/{3742.hs => T3742.hs}  |  0
 tests/ffi/should_compile/all.T                |  6 +-
 tests/ffi/should_run/7170.stderr              |  1 -
 tests/ffi/should_run/Makefile                 | 16 ++--
 tests/ffi/should_run/{1288.hs => T1288.hs}    |  0
 .../should_run/{1288.stdout => T1288.stdout}  |  0
 tests/ffi/should_run/{1288_c.c => T1288_c.c}  |  0
 .../{1288_ghci.hs => T1288_ghci.hs}           |  0
 .../{1288_ghci.stdout => T1288_ghci.stdout}   |  0
 .../{1288_ghci_c.c => T1288_ghci_c.c}         |  0
 tests/ffi/should_run/{1679.hs => T1679.hs}    |  0
 .../should_run/{1679.stdout => T1679.stdout}  |  0
 tests/ffi/should_run/{2276.hs => T2276.hs}    |  0
 .../should_run/{2276.stdout => T2276.stdout}  |  0
 tests/ffi/should_run/{2276_c.c => T2276_c.c}  |  0
 .../{2276_ghci.hs => T2276_ghci.hs}           |  0
 .../{2276_ghci.stdout => T2276_ghci.stdout}   |  0
 .../{2276_ghci_c.c => T2276_ghci_c.c}         |  0
 tests/ffi/should_run/{2469.hs => T2469.hs}    |  0
 tests/ffi/should_run/{2594.hs => T2594.hs}    |  0
 .../should_run/{2594.stdout => T2594.stdout}  |  0
 tests/ffi/should_run/{2594_c.c => T2594_c.c}  |  2 +-
 tests/ffi/should_run/{2594_c.h => T2594_c.h}  |  0
 tests/ffi/should_run/{2917a.hs => T2917a.hs}  |  0
 tests/ffi/should_run/{4038.hs => T4038.hs}    |  0
 .../should_run/{4038.stdout => T4038.stdout}  |  0
 tests/ffi/should_run/{4221.hs => T4221.hs}    |  0
 .../should_run/{4221.stdout => T4221.stdout}  |  0
 tests/ffi/should_run/{4221_c.c => T4221_c.c}  |  0
 tests/ffi/should_run/{5402.hs => T5402.hs}    |  0
 .../should_run/{5402_main.c => T5402_main.c}  |  2 +-
 tests/ffi/should_run/{5594.hs => T5594.hs}    |  0
 .../should_run/{5594.stdout => T5594.stdout}  |  0
 tests/ffi/should_run/{5594_c.c => T5594_c.c}  |  2 +-
 tests/ffi/should_run/{7170.hs => T7170.hs}    |  0
 tests/ffi/should_run/T7170.stderr             |  1 +
 .../should_run/{7170.stdout => T7170.stdout}  |  0
 tests/ffi/should_run/all.T                    | 96 +++++++++----------
 41 files changed, 64 insertions(+), 64 deletions(-)
 rename tests/ffi/should_compile/{1357.hs => T1357.hs} (100%)
 rename tests/ffi/should_compile/{1357.stderr => T1357.stderr} (81%)
 rename tests/ffi/should_compile/{3624.hs => T3624.hs} (100%)
 rename tests/ffi/should_compile/{3742.hs => T3742.hs} (100%)
 delete mode 100644 tests/ffi/should_run/7170.stderr
 rename tests/ffi/should_run/{1288.hs => T1288.hs} (100%)
 rename tests/ffi/should_run/{1288.stdout => T1288.stdout} (100%)
 rename tests/ffi/should_run/{1288_c.c => T1288_c.c} (100%)
 rename tests/ffi/should_run/{1288_ghci.hs => T1288_ghci.hs} (100%)
 rename tests/ffi/should_run/{1288_ghci.stdout => T1288_ghci.stdout} (100%)
 rename tests/ffi/should_run/{1288_ghci_c.c => T1288_ghci_c.c} (100%)
 rename tests/ffi/should_run/{1679.hs => T1679.hs} (100%)
 rename tests/ffi/should_run/{1679.stdout => T1679.stdout} (100%)
 rename tests/ffi/should_run/{2276.hs => T2276.hs} (100%)
 rename tests/ffi/should_run/{2276.stdout => T2276.stdout} (100%)
 rename tests/ffi/should_run/{2276_c.c => T2276_c.c} (100%)
 rename tests/ffi/should_run/{2276_ghci.hs => T2276_ghci.hs} (100%)
 rename tests/ffi/should_run/{2276_ghci.stdout => T2276_ghci.stdout} (100%)
 rename tests/ffi/should_run/{2276_ghci_c.c => T2276_ghci_c.c} (100%)
 rename tests/ffi/should_run/{2469.hs => T2469.hs} (100%)
 rename tests/ffi/should_run/{2594.hs => T2594.hs} (100%)
 rename tests/ffi/should_run/{2594.stdout => T2594.stdout} (100%)
 rename tests/ffi/should_run/{2594_c.c => T2594_c.c} (88%)
 rename tests/ffi/should_run/{2594_c.h => T2594_c.h} (100%)
 rename tests/ffi/should_run/{2917a.hs => T2917a.hs} (100%)
 rename tests/ffi/should_run/{4038.hs => T4038.hs} (100%)
 rename tests/ffi/should_run/{4038.stdout => T4038.stdout} (100%)
 rename tests/ffi/should_run/{4221.hs => T4221.hs} (100%)
 rename tests/ffi/should_run/{4221.stdout => T4221.stdout} (100%)
 rename tests/ffi/should_run/{4221_c.c => T4221_c.c} (100%)
 rename tests/ffi/should_run/{5402.hs => T5402.hs} (100%)
 rename tests/ffi/should_run/{5402_main.c => T5402_main.c} (89%)
 rename tests/ffi/should_run/{5594.hs => T5594.hs} (100%)
 rename tests/ffi/should_run/{5594.stdout => T5594.stdout} (100%)
 rename tests/ffi/should_run/{5594_c.c => T5594_c.c} (85%)
 rename tests/ffi/should_run/{7170.hs => T7170.hs} (100%)
 create mode 100644 tests/ffi/should_run/T7170.stderr
 rename tests/ffi/should_run/{7170.stdout => T7170.stdout} (100%)

diff --git a/tests/ffi/should_compile/1357.hs b/tests/ffi/should_compile/T1357.hs
similarity index 100%
rename from tests/ffi/should_compile/1357.hs
rename to tests/ffi/should_compile/T1357.hs
diff --git a/tests/ffi/should_compile/1357.stderr b/tests/ffi/should_compile/T1357.stderr
similarity index 81%
rename from tests/ffi/should_compile/1357.stderr
rename to tests/ffi/should_compile/T1357.stderr
index cd1cb7031..6678973fe 100644
--- a/tests/ffi/should_compile/1357.stderr
+++ b/tests/ffi/should_compile/T1357.stderr
@@ -1,3 +1,3 @@
 
-1357.hs:5:1:
+T1357.hs:5:1:
     Warning: possible missing & in foreign import of FunPtr
diff --git a/tests/ffi/should_compile/3624.hs b/tests/ffi/should_compile/T3624.hs
similarity index 100%
rename from tests/ffi/should_compile/3624.hs
rename to tests/ffi/should_compile/T3624.hs
diff --git a/tests/ffi/should_compile/3742.hs b/tests/ffi/should_compile/T3742.hs
similarity index 100%
rename from tests/ffi/should_compile/3742.hs
rename to tests/ffi/should_compile/T3742.hs
diff --git a/tests/ffi/should_compile/all.T b/tests/ffi/should_compile/all.T
index f4b4cdd5c..99c5eef8f 100644
--- a/tests/ffi/should_compile/all.T
+++ b/tests/ffi/should_compile/all.T
@@ -33,8 +33,8 @@ test('cc013', normal, compile, [''])
 test('cc014', normal, compile, [''])
 test('ffi-deriv1', normal, compile, [''])
 
-test('1357', normal, compile, [''])
-test('3624', normal, compile, [''])
-test('3742', normal, compile, [''])
+test('T1357', normal, compile, [''])
+test('T3624', normal, compile, [''])
+test('T3742', normal, compile, [''])
 test('cc015', normal, compile, [''])
 test('cc016', normal, compile, [''])
diff --git a/tests/ffi/should_run/7170.stderr b/tests/ffi/should_run/7170.stderr
deleted file mode 100644
index 3223f224b..000000000
--- a/tests/ffi/should_run/7170.stderr
+++ /dev/null
@@ -1 +0,0 @@
-7170: thread blocked indefinitely in an MVar operation
diff --git a/tests/ffi/should_run/Makefile b/tests/ffi/should_run/Makefile
index 80ff28647..7f846ce53 100644
--- a/tests/ffi/should_run/Makefile
+++ b/tests/ffi/should_run/Makefile
@@ -5,20 +5,20 @@ include $(TOP)/mk/test.mk
 ffi018_ghci_setup :
 	'$(TEST_HC)' $(TEST_HC_OPTS) -c ffi018_ghci_c.c
 
-1288_ghci_setup :
-	'$(TEST_HC)' $(TEST_HC_OPTS) -c 1288_ghci_c.c
+T1288_ghci_setup :
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c T1288_ghci_c.c
 
-2276_ghci_setup :
-	'$(TEST_HC)' $(TEST_HC_OPTS) -c 2276_ghci_c.c
+T2276_ghci_setup :
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c T2276_ghci_c.c
 
 ffi002_setup :
 	'$(TEST_HC)' $(TEST_HC_OPTS) -c ffi002.hs
 
-5402_setup :
-	'$(TEST_HC)' $(TEST_HC_OPTS) -c 5402.hs
+T5402_setup :
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c T5402.hs
 
-5594_setup :
-	'$(TEST_HC)' $(TEST_HC_OPTS) -c 5594.hs
+T5594_setup :
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c T5594.hs
 
 .PHONY: Capi_Ctype_001
 Capi_Ctype_001:
diff --git a/tests/ffi/should_run/1288.hs b/tests/ffi/should_run/T1288.hs
similarity index 100%
rename from tests/ffi/should_run/1288.hs
rename to tests/ffi/should_run/T1288.hs
diff --git a/tests/ffi/should_run/1288.stdout b/tests/ffi/should_run/T1288.stdout
similarity index 100%
rename from tests/ffi/should_run/1288.stdout
rename to tests/ffi/should_run/T1288.stdout
diff --git a/tests/ffi/should_run/1288_c.c b/tests/ffi/should_run/T1288_c.c
similarity index 100%
rename from tests/ffi/should_run/1288_c.c
rename to tests/ffi/should_run/T1288_c.c
diff --git a/tests/ffi/should_run/1288_ghci.hs b/tests/ffi/should_run/T1288_ghci.hs
similarity index 100%
rename from tests/ffi/should_run/1288_ghci.hs
rename to tests/ffi/should_run/T1288_ghci.hs
diff --git a/tests/ffi/should_run/1288_ghci.stdout b/tests/ffi/should_run/T1288_ghci.stdout
similarity index 100%
rename from tests/ffi/should_run/1288_ghci.stdout
rename to tests/ffi/should_run/T1288_ghci.stdout
diff --git a/tests/ffi/should_run/1288_ghci_c.c b/tests/ffi/should_run/T1288_ghci_c.c
similarity index 100%
rename from tests/ffi/should_run/1288_ghci_c.c
rename to tests/ffi/should_run/T1288_ghci_c.c
diff --git a/tests/ffi/should_run/1679.hs b/tests/ffi/should_run/T1679.hs
similarity index 100%
rename from tests/ffi/should_run/1679.hs
rename to tests/ffi/should_run/T1679.hs
diff --git a/tests/ffi/should_run/1679.stdout b/tests/ffi/should_run/T1679.stdout
similarity index 100%
rename from tests/ffi/should_run/1679.stdout
rename to tests/ffi/should_run/T1679.stdout
diff --git a/tests/ffi/should_run/2276.hs b/tests/ffi/should_run/T2276.hs
similarity index 100%
rename from tests/ffi/should_run/2276.hs
rename to tests/ffi/should_run/T2276.hs
diff --git a/tests/ffi/should_run/2276.stdout b/tests/ffi/should_run/T2276.stdout
similarity index 100%
rename from tests/ffi/should_run/2276.stdout
rename to tests/ffi/should_run/T2276.stdout
diff --git a/tests/ffi/should_run/2276_c.c b/tests/ffi/should_run/T2276_c.c
similarity index 100%
rename from tests/ffi/should_run/2276_c.c
rename to tests/ffi/should_run/T2276_c.c
diff --git a/tests/ffi/should_run/2276_ghci.hs b/tests/ffi/should_run/T2276_ghci.hs
similarity index 100%
rename from tests/ffi/should_run/2276_ghci.hs
rename to tests/ffi/should_run/T2276_ghci.hs
diff --git a/tests/ffi/should_run/2276_ghci.stdout b/tests/ffi/should_run/T2276_ghci.stdout
similarity index 100%
rename from tests/ffi/should_run/2276_ghci.stdout
rename to tests/ffi/should_run/T2276_ghci.stdout
diff --git a/tests/ffi/should_run/2276_ghci_c.c b/tests/ffi/should_run/T2276_ghci_c.c
similarity index 100%
rename from tests/ffi/should_run/2276_ghci_c.c
rename to tests/ffi/should_run/T2276_ghci_c.c
diff --git a/tests/ffi/should_run/2469.hs b/tests/ffi/should_run/T2469.hs
similarity index 100%
rename from tests/ffi/should_run/2469.hs
rename to tests/ffi/should_run/T2469.hs
diff --git a/tests/ffi/should_run/2594.hs b/tests/ffi/should_run/T2594.hs
similarity index 100%
rename from tests/ffi/should_run/2594.hs
rename to tests/ffi/should_run/T2594.hs
diff --git a/tests/ffi/should_run/2594.stdout b/tests/ffi/should_run/T2594.stdout
similarity index 100%
rename from tests/ffi/should_run/2594.stdout
rename to tests/ffi/should_run/T2594.stdout
diff --git a/tests/ffi/should_run/2594_c.c b/tests/ffi/should_run/T2594_c.c
similarity index 88%
rename from tests/ffi/should_run/2594_c.c
rename to tests/ffi/should_run/T2594_c.c
index f0dd3007f..34d633edb 100644
--- a/tests/ffi/should_run/2594_c.c
+++ b/tests/ffi/should_run/T2594_c.c
@@ -1,5 +1,5 @@
 
-#include "2594_c.h"
+#include "T2594_c.h"
 
 void call8 (funtype8 fun)  { fun(-1); }
 void call16(funtype16 fun) { fun(-1); }
diff --git a/tests/ffi/should_run/2594_c.h b/tests/ffi/should_run/T2594_c.h
similarity index 100%
rename from tests/ffi/should_run/2594_c.h
rename to tests/ffi/should_run/T2594_c.h
diff --git a/tests/ffi/should_run/2917a.hs b/tests/ffi/should_run/T2917a.hs
similarity index 100%
rename from tests/ffi/should_run/2917a.hs
rename to tests/ffi/should_run/T2917a.hs
diff --git a/tests/ffi/should_run/4038.hs b/tests/ffi/should_run/T4038.hs
similarity index 100%
rename from tests/ffi/should_run/4038.hs
rename to tests/ffi/should_run/T4038.hs
diff --git a/tests/ffi/should_run/4038.stdout b/tests/ffi/should_run/T4038.stdout
similarity index 100%
rename from tests/ffi/should_run/4038.stdout
rename to tests/ffi/should_run/T4038.stdout
diff --git a/tests/ffi/should_run/4221.hs b/tests/ffi/should_run/T4221.hs
similarity index 100%
rename from tests/ffi/should_run/4221.hs
rename to tests/ffi/should_run/T4221.hs
diff --git a/tests/ffi/should_run/4221.stdout b/tests/ffi/should_run/T4221.stdout
similarity index 100%
rename from tests/ffi/should_run/4221.stdout
rename to tests/ffi/should_run/T4221.stdout
diff --git a/tests/ffi/should_run/4221_c.c b/tests/ffi/should_run/T4221_c.c
similarity index 100%
rename from tests/ffi/should_run/4221_c.c
rename to tests/ffi/should_run/T4221_c.c
diff --git a/tests/ffi/should_run/5402.hs b/tests/ffi/should_run/T5402.hs
similarity index 100%
rename from tests/ffi/should_run/5402.hs
rename to tests/ffi/should_run/T5402.hs
diff --git a/tests/ffi/should_run/5402_main.c b/tests/ffi/should_run/T5402_main.c
similarity index 89%
rename from tests/ffi/should_run/5402_main.c
rename to tests/ffi/should_run/T5402_main.c
index 6ef2c651a..efabfbcfa 100644
--- a/tests/ffi/should_run/5402_main.c
+++ b/tests/ffi/should_run/T5402_main.c
@@ -1,7 +1,7 @@
 #include "HsFFI.h"
 #include <stdio.h>
 #include <stdlib.h>
-#include "5402_stub.h"
+#include "T5402_stub.h"
 
 int main (int argc, char *argv[])
 {
diff --git a/tests/ffi/should_run/5594.hs b/tests/ffi/should_run/T5594.hs
similarity index 100%
rename from tests/ffi/should_run/5594.hs
rename to tests/ffi/should_run/T5594.hs
diff --git a/tests/ffi/should_run/5594.stdout b/tests/ffi/should_run/T5594.stdout
similarity index 100%
rename from tests/ffi/should_run/5594.stdout
rename to tests/ffi/should_run/T5594.stdout
diff --git a/tests/ffi/should_run/5594_c.c b/tests/ffi/should_run/T5594_c.c
similarity index 85%
rename from tests/ffi/should_run/5594_c.c
rename to tests/ffi/should_run/T5594_c.c
index 5de1f4d4c..9ef22e8ef 100644
--- a/tests/ffi/should_run/5594_c.c
+++ b/tests/ffi/should_run/T5594_c.c
@@ -1,5 +1,5 @@
 #include <stdio.h>
-#include "5594_stub.h"
+#include "T5594_stub.h"
 
 #include "HsFFI.h"
 
diff --git a/tests/ffi/should_run/7170.hs b/tests/ffi/should_run/T7170.hs
similarity index 100%
rename from tests/ffi/should_run/7170.hs
rename to tests/ffi/should_run/T7170.hs
diff --git a/tests/ffi/should_run/T7170.stderr b/tests/ffi/should_run/T7170.stderr
new file mode 100644
index 000000000..4ea63ebc4
--- /dev/null
+++ b/tests/ffi/should_run/T7170.stderr
@@ -0,0 +1 @@
+T7170: thread blocked indefinitely in an MVar operation
diff --git a/tests/ffi/should_run/7170.stdout b/tests/ffi/should_run/T7170.stdout
similarity index 100%
rename from tests/ffi/should_run/7170.stdout
rename to tests/ffi/should_run/T7170.stdout
diff --git a/tests/ffi/should_run/all.T b/tests/ffi/should_run/all.T
index e170db0db..772749265 100644
--- a/tests/ffi/should_run/all.T
+++ b/tests/ffi/should_run/all.T
@@ -116,30 +116,30 @@ test('ffi018_ghci', [ only_ways(['ghci']),
 test('ffi019', normal, compile_and_run, [''])
 
 # This one originally failed only GHCi, but doesn't hurt to test all ways.
-test('1679', normal, compile_and_run, [''])
-
-test('1288', [ omit_ways(['ghci']),
-               extra_clean(['1288_c.o']) ],
-             compile_and_run, ['1288_c.c'])
-test('1288_ghci', [ only_ways(['ghci']),
-                    cmd_prefix('$MAKE --no-print-directory 1288_ghci_setup && '),
-                    extra_clean(['1288_ghci_c.o']) ],
-                  compile_and_run, ['1288_ghci_c.o'])
-
-test('2276', [ omit_ways(['ghci']), 
-               extra_clean(['2276_c.o']) ],
-             compile_and_run, ['2276_c.c'])
-test('2276_ghci', [ only_ways(['ghci']),
-                    cmd_prefix('$MAKE --no-print-directory 2276_ghci_setup && '),
-                    extra_clean(['2276_ghci_c.o']) ],
-                  compile_and_run, ['-fobject-code 2276_ghci_c.o'])
-
-test('2469', normal, compile_and_run, ['-optc-std=gnu99'])
-
-test('2594',
-     [extra_clean(['2594_c.o']), omit_ways(['ghci'])],
+test('T1679', normal, compile_and_run, [''])
+
+test('T1288', [ omit_ways(['ghci']),
+                extra_clean(['T1288_c.o']) ],
+              compile_and_run, ['T1288_c.c'])
+test('T1288_ghci', [ only_ways(['ghci']),
+                     cmd_prefix('$MAKE --no-print-directory T1288_ghci_setup && '),
+                     extra_clean(['T1288_ghci_c.o']) ],
+                   compile_and_run, ['T1288_ghci_c.o'])
+
+test('T2276', [ omit_ways(['ghci']), 
+                extra_clean(['T2276_c.o']) ],
+              compile_and_run, ['T2276_c.c'])
+test('T2276_ghci', [ only_ways(['ghci']),
+                     cmd_prefix('$MAKE --no-print-directory T2276_ghci_setup && '),
+                     extra_clean(['T2276_ghci_c.o']) ],
+                   compile_and_run, ['-fobject-code T2276_ghci_c.o'])
+
+test('T2469', normal, compile_and_run, ['-optc-std=gnu99'])
+
+test('T2594',
+     [extra_clean(['T2594_c.o']), omit_ways(['ghci'])],
      compile_and_run,
-     ['2594_c.c'])
+     ['T2594_c.c'])
 
 test('fptr01', [ omit_ways(['ghci']), extra_clean(['fptr01_c.o']) ],
                compile_and_run, ['fptr01_c.c'])
@@ -149,7 +149,7 @@ test('fptrfail01', [ compose(omit_ways(['ghci']), exit_code(1)),
                      extra_clean(['fptrfail01_c.o']) ],
                    compile_and_run, ['fptrfail01_c.c'])
 
-test('2917a', normal, compile_and_run, [''])
+test('T2917a', normal, compile_and_run, [''])
 
 # omit prof ways, because this test causes the RTS to exit (correctly)
 # without generating profiling information.
@@ -163,30 +163,30 @@ test('ffi022', normal, compile_and_run, [''])
 
 if config.os == 'mingw32':
     # This test needs a larger C stack than we get by default on Windows
-	flagsFor4038 = ['-optl-Wl,--stack,10485760']
+	flagsForT4038 = ['-optl-Wl,--stack,10485760']
 else:
-	flagsFor4038 = ['']
-test('4038', normal, compile_and_run, flagsFor4038)
-
-test('4221', [ omit_ways(['ghci']), extra_clean(['4221_c.o']) ],
-               compile_and_run, ['4221_c.c'])
-
-test('5402', [ omit_ways(['ghci']),
-               exit_code(42),
-               extra_clean(['5402_main.o']),
-                 # The 5402_setup hack is to ensure that we generate
-                 # 5402_stub.h before compiling 5402_main.c, which
-                 # needs it.
-               compile_cmd_prefix('$MAKE --no-print-directory 5402_setup && ') ],
-             compile_and_run, ["-no-hs-main 5402_main.c"])
-
-test('5594', [ omit_ways(['ghci']),
-               extra_clean(['5594_c.o']),
-               compile_cmd_prefix('$MAKE --no-print-directory 5594_setup && ') ],
-               # The 5594_setup hack is to ensure that we generate
-               # 5594_stub.h before compiling 5594_c.c, which
-               # needs it.
-               compile_and_run, ['5594_c.c -no-hs-main'])
+	flagsForT4038 = ['']
+test('T4038', normal, compile_and_run, flagsForT4038)
+
+test('T4221', [ omit_ways(['ghci']), extra_clean(['T4221_c.o']) ],
+                compile_and_run, ['T4221_c.c'])
+
+test('T5402', [ omit_ways(['ghci']),
+                exit_code(42),
+                extra_clean(['T5402_main.o']),
+                  # The T5402_setup hack is to ensure that we generate
+                  # T5402_stub.h before compiling T5402_main.c, which
+                  # needs it.
+                compile_cmd_prefix('$MAKE --no-print-directory T5402_setup && ') ],
+              compile_and_run, ["-no-hs-main T5402_main.c"])
+
+test('T5594', [ omit_ways(['ghci']),
+                extra_clean(['T5594_c.o']),
+                compile_cmd_prefix('$MAKE --no-print-directory T5594_setup && ') ],
+                # The T5594_setup hack is to ensure that we generate
+                # T5594_stub.h before compiling T5594_c.c, which
+                # needs it.
+                compile_and_run, ['T5594_c.c -no-hs-main'])
 
 test('Capi_Ctype_001',
      extra_clean(['Capi_Ctype_A_001.o', 'Capi_Ctype_A_001.hi',
@@ -211,7 +211,7 @@ test('capi_value',
      compile_and_run,
      ['capi_value_c.c'])
 
-test('7170', exit_code(1), compile_and_run, [''])
+test('T7170', exit_code(1), compile_and_run, [''])
 
 test('T4012',
      [extra_clean(['T4012_A.hi', 'T4012_A.o', 'T4012_B.hi', 'T4012_B.o']),
-- 
GitLab


From 44dee8961cfa075ecb022c6745210ee2652aa1be Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 15:56:17 +0000
Subject: [PATCH 045/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/ghc-e/should_run/Makefile                      | 12 ++++++------
 tests/ghc-e/should_run/{2228.hs => T2228.hs}         |  0
 tests/ghc-e/should_run/{2228.stdout => T2228.stdout} |  0
 tests/ghc-e/should_run/{2636.hs => T2636.hs}         |  0
 tests/ghc-e/should_run/{2636.stderr => T2636.stderr} |  2 +-
 tests/ghc-e/should_run/{3890.hs => T3890.hs}         |  0
 tests/ghc-e/should_run/{3890.stdout => T3890.stdout} |  0
 tests/ghc-e/should_run/all.T                         |  8 ++++----
 8 files changed, 11 insertions(+), 11 deletions(-)
 rename tests/ghc-e/should_run/{2228.hs => T2228.hs} (100%)
 rename tests/ghc-e/should_run/{2228.stdout => T2228.stdout} (100%)
 rename tests/ghc-e/should_run/{2636.hs => T2636.hs} (100%)
 rename tests/ghc-e/should_run/{2636.stderr => T2636.stderr} (87%)
 rename tests/ghc-e/should_run/{3890.hs => T3890.hs} (100%)
 rename tests/ghc-e/should_run/{3890.stdout => T3890.stdout} (100%)

diff --git a/tests/ghc-e/should_run/Makefile b/tests/ghc-e/should_run/Makefile
index 3596f0262..1971004d4 100644
--- a/tests/ghc-e/should_run/Makefile
+++ b/tests/ghc-e/should_run/Makefile
@@ -18,14 +18,14 @@ ghc-e004:
 ghc-e005:
 	'$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -main-is foo ghc-e005.hs -e ":set prog ghc-e005-prog" -e ":main [\"the\",\"args\"]"; echo $$?
 
-2228:
-	'$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e ":main" 2228.hs
+T2228:
+	'$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e ":main" T2228.hs
 
-2636:
-	'$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e ":main" 2636.hs; if [ "$?" != 0 ]; then true; else false; fi
+T2636:
+	'$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e ":main" T2636.hs; if [ "$?" != 0 ]; then true; else false; fi
 
-3890:
-	'$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e ":main" 3890.hs | cat
+T3890:
+	'$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e ":main" T3890.hs | cat
 
 T7299:
 	'$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "Control.Concurrent.threadDelay (1000 * 1000)"
diff --git a/tests/ghc-e/should_run/2228.hs b/tests/ghc-e/should_run/T2228.hs
similarity index 100%
rename from tests/ghc-e/should_run/2228.hs
rename to tests/ghc-e/should_run/T2228.hs
diff --git a/tests/ghc-e/should_run/2228.stdout b/tests/ghc-e/should_run/T2228.stdout
similarity index 100%
rename from tests/ghc-e/should_run/2228.stdout
rename to tests/ghc-e/should_run/T2228.stdout
diff --git a/tests/ghc-e/should_run/2636.hs b/tests/ghc-e/should_run/T2636.hs
similarity index 100%
rename from tests/ghc-e/should_run/2636.hs
rename to tests/ghc-e/should_run/T2636.hs
diff --git a/tests/ghc-e/should_run/2636.stderr b/tests/ghc-e/should_run/T2636.stderr
similarity index 87%
rename from tests/ghc-e/should_run/2636.stderr
rename to tests/ghc-e/should_run/T2636.stderr
index e69b54b36..369890fa2 100644
--- a/tests/ghc-e/should_run/2636.stderr
+++ b/tests/ghc-e/should_run/T2636.stderr
@@ -1,4 +1,4 @@
 
-2636.hs:1:8:
+T2636.hs:1:8:
     Could not find module `MissingModule'
     Use -v to see a list of the files searched for.
diff --git a/tests/ghc-e/should_run/3890.hs b/tests/ghc-e/should_run/T3890.hs
similarity index 100%
rename from tests/ghc-e/should_run/3890.hs
rename to tests/ghc-e/should_run/T3890.hs
diff --git a/tests/ghc-e/should_run/3890.stdout b/tests/ghc-e/should_run/T3890.stdout
similarity index 100%
rename from tests/ghc-e/should_run/3890.stdout
rename to tests/ghc-e/should_run/T3890.stdout
diff --git a/tests/ghc-e/should_run/all.T b/tests/ghc-e/should_run/all.T
index e5a252978..da14b703c 100644
--- a/tests/ghc-e/should_run/all.T
+++ b/tests/ghc-e/should_run/all.T
@@ -7,10 +7,10 @@ test('ghc-e003', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e0
 test('ghc-e004', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e004'])
 test('ghc-e005', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e005'])
 
-test('2228',
+test('T2228',
      [req_interp, if_ghci_dynamic(expect_broken(7298))],
      run_command,
-     ['$MAKE --no-print-directory -s 2228'])
-test('2636', req_interp, run_command, ['$MAKE --no-print-directory -s 2636'])
-test('3890', req_interp, run_command, ['$MAKE --no-print-directory -s 3890'])
+     ['$MAKE --no-print-directory -s T2228'])
+test('T2636', req_interp, run_command, ['$MAKE --no-print-directory -s T2636'])
+test('T3890', req_interp, run_command, ['$MAKE --no-print-directory -s T3890'])
 test('T7299', req_interp, run_command, ['$MAKE --no-print-directory -s T7299'])
-- 
GitLab


From ffeb5011e5eabcdd50bda9163b4ca4bb47803140 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:00:09 +0000
Subject: [PATCH 046/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/cabal/1750.stderr  |  5 -----
 tests/cabal/1750.stdout  |  4 ----
 tests/cabal/1750A.pkg    |  4 ----
 tests/cabal/1750B.pkg    |  4 ----
 tests/cabal/Makefile     | 22 +++++++++++-----------
 tests/cabal/T1750.stderr |  5 +++++
 tests/cabal/T1750.stdout |  4 ++++
 tests/cabal/T1750A.pkg   |  4 ++++
 tests/cabal/T1750B.pkg   |  4 ++++
 tests/cabal/all.T        | 10 +++++-----
 10 files changed, 33 insertions(+), 33 deletions(-)
 delete mode 100644 tests/cabal/1750.stderr
 delete mode 100644 tests/cabal/1750.stdout
 delete mode 100644 tests/cabal/1750A.pkg
 delete mode 100644 tests/cabal/1750B.pkg
 create mode 100644 tests/cabal/T1750.stderr
 create mode 100644 tests/cabal/T1750.stdout
 create mode 100644 tests/cabal/T1750A.pkg
 create mode 100644 tests/cabal/T1750B.pkg

diff --git a/tests/cabal/1750.stderr b/tests/cabal/1750.stderr
deleted file mode 100644
index 71bed0745..000000000
--- a/tests/cabal/1750.stderr
+++ /dev/null
@@ -1,5 +0,0 @@
-WARNING: there are broken packages.  Run 'ghc-pkg check' for more details.
-<command line>: cannot satisfy -package 1750A: 
-    1750A-1-XXX is unusable due to missing or recursive dependencies:
-      1750B-1-XXX
-    (use -v for more information)
diff --git a/tests/cabal/1750.stdout b/tests/cabal/1750.stdout
deleted file mode 100644
index dac998e2a..000000000
--- a/tests/cabal/1750.stdout
+++ /dev/null
@@ -1,4 +0,0 @@
-local1750.package.conf:
-    {1750A-1}
-    {1750B-1}
-
diff --git a/tests/cabal/1750A.pkg b/tests/cabal/1750A.pkg
deleted file mode 100644
index e32c97ff8..000000000
--- a/tests/cabal/1750A.pkg
+++ /dev/null
@@ -1,4 +0,0 @@
-name: 1750A
-version: 1
-id: 1750A-1-XXX
-depends: 1750B-1-XXX
diff --git a/tests/cabal/1750B.pkg b/tests/cabal/1750B.pkg
deleted file mode 100644
index 5e9ff1f56..000000000
--- a/tests/cabal/1750B.pkg
+++ /dev/null
@@ -1,4 +0,0 @@
-name: 1750B
-version: 1
-id: 1750B-1-XXX
-depends: 1750A-1-XXX
diff --git a/tests/cabal/Makefile b/tests/cabal/Makefile
index 769a50d3f..f0091bcee 100644
--- a/tests/cabal/Makefile
+++ b/tests/cabal/Makefile
@@ -110,20 +110,20 @@ ghcpkg06 :
 	if $(LOCAL_GHC_PKG06) register testdup.pkg; then false else true; fi
 	$(LOCAL_GHC_PKG06) register --force testdup.pkg
 
-PKGCONF1750=local1750.package.conf
-LOCAL_GHC_PKG1750 = '$(GHC_PKG)' --no-user-package-db -f $(PKGCONF1750)
-
-1750:
-	rm -rf $(PKGCONF1750) 1750.hs 1750.o 1750.hi 1750.out
-	$(LOCAL_GHC_PKG1750) init $(PKGCONF1750)
-	$(LOCAL_GHC_PKG1750) register --force 1750A.pkg >1750.out 2>&1
-	$(LOCAL_GHC_PKG1750) register --force 1750B.pkg >1750.out 2>&1
-	GHC_PACKAGE_PATH=$(PKGCONF1750) '$(GHC_PKG)' --no-user-package-db list
+PKGCONFT1750=localT1750.package.conf
+LOCAL_GHC_PKGT1750 = '$(GHC_PKG)' --no-user-package-db -f $(PKGCONFT1750)
+
+T1750:
+	rm -rf $(PKGCONFT1750) T1750.hs T1750.o T1750.hi T1750.out
+	$(LOCAL_GHC_PKGT1750) init $(PKGCONFT1750)
+	$(LOCAL_GHC_PKGT1750) register --force T1750A.pkg >T1750.out 2>&1
+	$(LOCAL_GHC_PKGT1750) register --force T1750B.pkg >T1750.out 2>&1
+	GHC_PACKAGE_PATH=$(PKGCONFT1750) '$(GHC_PKG)' --no-user-package-db list
 # GHC_PACKAGE_PATH trick is to make this work with 6.8.2 which doesn't have
 # the patch "Change the command-line semantics for query commands" to
 # ghc-pkg
-	echo "main = return ()" >1750.hs
-	'$(TEST_HC)' $(TEST_HC_OPTS) -package-db $(PKGCONF1750) -package 1750A 1750.hs || true
+	echo "main = return ()" >T1750.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -package-db $(PKGCONFT1750) -package T1750A T1750.hs || true
 
 PKGCONFSHADOW1=localshadow1.package.conf
 PKGCONFSHADOW2=localshadow2.package.conf
diff --git a/tests/cabal/T1750.stderr b/tests/cabal/T1750.stderr
new file mode 100644
index 000000000..1809d5b05
--- /dev/null
+++ b/tests/cabal/T1750.stderr
@@ -0,0 +1,5 @@
+WARNING: there are broken packages.  Run 'ghc-pkg check' for more details.
+<command line>: cannot satisfy -package T1750A: 
+    T1750A-1-XXX is unusable due to missing or recursive dependencies:
+      T1750B-1-XXX
+    (use -v for more information)
diff --git a/tests/cabal/T1750.stdout b/tests/cabal/T1750.stdout
new file mode 100644
index 000000000..62d032334
--- /dev/null
+++ b/tests/cabal/T1750.stdout
@@ -0,0 +1,4 @@
+localT1750.package.conf:
+    {T1750A-1}
+    {T1750B-1}
+
diff --git a/tests/cabal/T1750A.pkg b/tests/cabal/T1750A.pkg
new file mode 100644
index 000000000..9bda51eea
--- /dev/null
+++ b/tests/cabal/T1750A.pkg
@@ -0,0 +1,4 @@
+name: T1750A
+version: 1
+id: T1750A-1-XXX
+depends: T1750B-1-XXX
diff --git a/tests/cabal/T1750B.pkg b/tests/cabal/T1750B.pkg
new file mode 100644
index 000000000..479ce7092
--- /dev/null
+++ b/tests/cabal/T1750B.pkg
@@ -0,0 +1,4 @@
+name: T1750B
+version: 1
+id: T1750B-1-XXX
+depends: T1750A-1-XXX
diff --git a/tests/cabal/all.T b/tests/cabal/all.T
index f84688cbb..04e918d23 100644
--- a/tests/cabal/all.T
+++ b/tests/cabal/all.T
@@ -51,11 +51,11 @@ test('ghcpkg06',
 # (this was disallowed in GHC 6.4 and earlier)
 test('pkg01', normal, compile, [''])
 
-test('1750',
-     extra_clean(['1750.hs', '1750.out',
-                  'local1750.package.conf',
-                  'local1750.package.conf.old']),
-     run_command, ['$MAKE -s --no-print-directory 1750'])
+test('T1750',
+     extra_clean(['T1750.hs', 'T1750.out',
+                  'localT1750.package.conf',
+                  'localT1750.package.conf.old']),
+     run_command, ['$MAKE -s --no-print-directory T1750'])
 
 test('shadow',
      extra_clean(['shadow.out', 'shadow.hs', 'shadow.hi',
-- 
GitLab


From e140c4366288cc83f7c9ee920efa2ac94f3ad49d Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:02:36 +0000
Subject: [PATCH 047/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/ghci.debugger/scripts/{2740.hs => T2740.hs}         | 0
 tests/ghci.debugger/scripts/{2740.script => T2740.script} | 2 +-
 tests/ghci.debugger/scripts/{2740.stdout => T2740.stdout} | 4 ++--
 tests/ghci.debugger/scripts/all.T                         | 2 +-
 4 files changed, 4 insertions(+), 4 deletions(-)
 rename tests/ghci.debugger/scripts/{2740.hs => T2740.hs} (100%)
 rename tests/ghci.debugger/scripts/{2740.script => T2740.script} (88%)
 rename tests/ghci.debugger/scripts/{2740.stdout => T2740.stdout} (60%)

diff --git a/tests/ghci.debugger/scripts/2740.hs b/tests/ghci.debugger/scripts/T2740.hs
similarity index 100%
rename from tests/ghci.debugger/scripts/2740.hs
rename to tests/ghci.debugger/scripts/T2740.hs
diff --git a/tests/ghci.debugger/scripts/2740.script b/tests/ghci.debugger/scripts/T2740.script
similarity index 88%
rename from tests/ghci.debugger/scripts/2740.script
rename to tests/ghci.debugger/scripts/T2740.script
index ac4561618..a7bd83369 100644
--- a/tests/ghci.debugger/scripts/2740.script
+++ b/tests/ghci.debugger/scripts/T2740.script
@@ -1,5 +1,5 @@
 :seti -XMonomorphismRestriction
-:l 2740.hs
+:l T2740.hs
 :step f 1 2 3
 :step
 :print x
diff --git a/tests/ghci.debugger/scripts/2740.stdout b/tests/ghci.debugger/scripts/T2740.stdout
similarity index 60%
rename from tests/ghci.debugger/scripts/2740.stdout
rename to tests/ghci.debugger/scripts/T2740.stdout
index 68be6cb07..c6733bca9 100644
--- a/tests/ghci.debugger/scripts/2740.stdout
+++ b/tests/ghci.debugger/scripts/T2740.stdout
@@ -1,6 +1,6 @@
-Stopped at 2740.hs:(3,1)-(4,25)
+Stopped at T2740.hs:(3,1)-(4,25)
 _result :: a = _
-Stopped at 2740.hs:3:11-13
+Stopped at T2740.hs:3:11-13
 _result :: Bool = _
 x :: Integer = 1
 y :: Integer = 2
diff --git a/tests/ghci.debugger/scripts/all.T b/tests/ghci.debugger/scripts/all.T
index a78a6f21a..9eef1f62b 100644
--- a/tests/ghci.debugger/scripts/all.T
+++ b/tests/ghci.debugger/scripts/all.T
@@ -83,7 +83,7 @@ test('listCommand002', normal, ghci_script, ['listCommand002.script'])
 
 test('hist001', normal, ghci_script, ['hist001.script'])
 
-test('2740', normal, ghci_script, ['2740.script'])
+test('T2740', normal, ghci_script, ['T2740.script'])
 
 test('getargs', normal, ghci_script, ['getargs.script'])
 test('T7386', normal, ghci_script, ['T7386.script'])
-- 
GitLab


From 13b81c976eedb974b9c34842c6cf6557a96aeee3 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:06:30 +0000
Subject: [PATCH 048/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/profiling/should_compile/{2410.hs => T2410.hs}     | 0
 tests/profiling/should_compile/all.T                     | 2 +-
 tests/profiling/should_run/{2592.hs => T2592.hs}         | 0
 tests/profiling/should_run/{2592.stderr => T2592.stderr} | 2 +-
 tests/profiling/should_run/{5314.hs => T5314.hs}         | 0
 tests/profiling/should_run/{5314.stdout => T5314.stdout} | 0
 tests/profiling/should_run/all.T                         | 4 ++--
 7 files changed, 4 insertions(+), 4 deletions(-)
 rename tests/profiling/should_compile/{2410.hs => T2410.hs} (100%)
 rename tests/profiling/should_run/{2592.hs => T2592.hs} (100%)
 rename tests/profiling/should_run/{2592.stderr => T2592.stderr} (79%)
 rename tests/profiling/should_run/{5314.hs => T5314.hs} (100%)
 rename tests/profiling/should_run/{5314.stdout => T5314.stdout} (100%)

diff --git a/tests/profiling/should_compile/2410.hs b/tests/profiling/should_compile/T2410.hs
similarity index 100%
rename from tests/profiling/should_compile/2410.hs
rename to tests/profiling/should_compile/T2410.hs
diff --git a/tests/profiling/should_compile/all.T b/tests/profiling/should_compile/all.T
index b9539038b..cf7d48dad 100644
--- a/tests/profiling/should_compile/all.T
+++ b/tests/profiling/should_compile/all.T
@@ -4,5 +4,5 @@
 test('prof001', compose(only_ways(['normal']), req_profiling), compile_and_run, ['-prof -caf-all'])
 test('prof002', compose(only_ways(['normal']), req_profiling), compile_and_run, ['-prof -caf-all'])
 
-test('2410', compose(only_ways(['normal']), req_profiling), compile, ['-O2 -prof -caf-all'])
+test('T2410', compose(only_ways(['normal']), req_profiling), compile, ['-O2 -prof -caf-all'])
 
diff --git a/tests/profiling/should_run/2592.hs b/tests/profiling/should_run/T2592.hs
similarity index 100%
rename from tests/profiling/should_run/2592.hs
rename to tests/profiling/should_run/T2592.hs
diff --git a/tests/profiling/should_run/2592.stderr b/tests/profiling/should_run/T2592.stderr
similarity index 79%
rename from tests/profiling/should_run/2592.stderr
rename to tests/profiling/should_run/T2592.stderr
index 478676340..724ef0ec6 100644
--- a/tests/profiling/should_run/2592.stderr
+++ b/tests/profiling/should_run/T2592.stderr
@@ -1,3 +1,3 @@
-2592: Heap exhausted;
+T2592: Heap exhausted;
 Current maximum heap size is 1048576 bytes (1 MB);
 use `+RTS -M<size>' to increase it.
diff --git a/tests/profiling/should_run/5314.hs b/tests/profiling/should_run/T5314.hs
similarity index 100%
rename from tests/profiling/should_run/5314.hs
rename to tests/profiling/should_run/T5314.hs
diff --git a/tests/profiling/should_run/5314.stdout b/tests/profiling/should_run/T5314.stdout
similarity index 100%
rename from tests/profiling/should_run/5314.stdout
rename to tests/profiling/should_run/T5314.stdout
diff --git a/tests/profiling/should_run/all.T b/tests/profiling/should_run/all.T
index 539e0e787..3722209d9 100644
--- a/tests/profiling/should_run/all.T
+++ b/tests/profiling/should_run/all.T
@@ -9,7 +9,7 @@ test('heapprof001',
                extra_run_opts('7')]),
      compile_and_run, [''])
 
-test('2592',
+test('T2592',
      [only_ways(['profasm']), req_profiling,
       extra_run_opts('+RTS -M1m -RTS'), exit_code(251)],
      compile_and_run, [''])
@@ -43,7 +43,7 @@ test('scc004', [req_profiling,
      compile_and_run,
      [''])
 
-test('5314',
+test('T5314',
      [ only_ways(prof_ways),
        extra_ways(extra_prof_ways),
        req_profiling ],
-- 
GitLab


From 1a9586c0627696652cb486dffcfa4aa0981b2b1c Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:07:13 +0000
Subject: [PATCH 049/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/perf/should_run/{3586.hs => T3586.hs}         | 0
 tests/perf/should_run/{3586.stdout => T3586.stdout} | 0
 tests/perf/should_run/all.T                         | 2 +-
 3 files changed, 1 insertion(+), 1 deletion(-)
 rename tests/perf/should_run/{3586.hs => T3586.hs} (100%)
 rename tests/perf/should_run/{3586.stdout => T3586.stdout} (100%)

diff --git a/tests/perf/should_run/3586.hs b/tests/perf/should_run/T3586.hs
similarity index 100%
rename from tests/perf/should_run/3586.hs
rename to tests/perf/should_run/T3586.hs
diff --git a/tests/perf/should_run/3586.stdout b/tests/perf/should_run/T3586.stdout
similarity index 100%
rename from tests/perf/should_run/3586.stdout
rename to tests/perf/should_run/T3586.stdout
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index d7fe600f5..9d1c0adcd 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -3,7 +3,7 @@
 # fortunately the values here are mostly independent of the wordsize,
 # because the test allocates an unboxed array of doubles.
 
-test('3586',
+test('T3586',
      [stats_num_field('peak_megabytes_allocated', 17,
                                                   18),
                                      # expected value: 17 (amd64/Linux)
-- 
GitLab


From 79880ace1bd1882ef16a81e403aac4d786da85f0 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:09:12 +0000
Subject: [PATCH 050/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/th/{2014 => T2014}/A.hs      | 0
 tests/th/{2014 => T2014}/A.hs-boot | 0
 tests/th/{2014 => T2014}/B.hs      | 0
 tests/th/{2014 => T2014}/C.hs      | 0
 tests/th/{2014 => T2014}/Makefile  | 2 +-
 tests/th/{2014 => T2014}/all.T     | 4 ++--
 6 files changed, 3 insertions(+), 3 deletions(-)
 rename tests/th/{2014 => T2014}/A.hs (100%)
 rename tests/th/{2014 => T2014}/A.hs-boot (100%)
 rename tests/th/{2014 => T2014}/B.hs (100%)
 rename tests/th/{2014 => T2014}/C.hs (100%)
 rename tests/th/{2014 => T2014}/Makefile (97%)
 rename tests/th/{2014 => T2014}/all.T (75%)

diff --git a/tests/th/2014/A.hs b/tests/th/T2014/A.hs
similarity index 100%
rename from tests/th/2014/A.hs
rename to tests/th/T2014/A.hs
diff --git a/tests/th/2014/A.hs-boot b/tests/th/T2014/A.hs-boot
similarity index 100%
rename from tests/th/2014/A.hs-boot
rename to tests/th/T2014/A.hs-boot
diff --git a/tests/th/2014/B.hs b/tests/th/T2014/B.hs
similarity index 100%
rename from tests/th/2014/B.hs
rename to tests/th/T2014/B.hs
diff --git a/tests/th/2014/C.hs b/tests/th/T2014/C.hs
similarity index 100%
rename from tests/th/2014/C.hs
rename to tests/th/T2014/C.hs
diff --git a/tests/th/2014/Makefile b/tests/th/T2014/Makefile
similarity index 97%
rename from tests/th/2014/Makefile
rename to tests/th/T2014/Makefile
index eafbcfb7e..72607a588 100644
--- a/tests/th/2014/Makefile
+++ b/tests/th/T2014/Makefile
@@ -2,7 +2,7 @@ TOP=../../..
 include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk
 
-2014 :
+T2014 :
 	'$(TEST_HC)' $(TEST_HC_OPTS) -fforce-recomp -c A.hs-boot
 	'$(TEST_HC)' $(TEST_HC_OPTS) -fforce-recomp -c A.hs
 	'$(TEST_HC)' $(TEST_HC_OPTS) -fforce-recomp -c B.hs
diff --git a/tests/th/2014/all.T b/tests/th/T2014/all.T
similarity index 75%
rename from tests/th/2014/all.T
rename to tests/th/T2014/all.T
index c6792677d..212690d6f 100644
--- a/tests/th/2014/all.T
+++ b/tests/th/T2014/all.T
@@ -1,8 +1,8 @@
 setTestOpts(if_compiler_profiled(skip))
 
-test('2014',
+test('T2014',
      [req_interp,
       extra_clean(['A.hi-boot','A.hi','A.o','A.o-boot',
                    'B.hi', 'B.o', 'C.hi', 'C.o'])],
      run_command,
-     ['$MAKE -s --no-print-directory 2014'])
+     ['$MAKE -s --no-print-directory T2014'])
-- 
GitLab


From 1c004a7a6a081d6849cace650a838607d9fd7ea4 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:11:06 +0000
Subject: [PATCH 051/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/parser/unicode/2302.stderr                   | 2 --
 tests/parser/unicode/{1103.hs => T1103.hs}         | 0
 tests/parser/unicode/{1744.hs => T1744.hs}         | 0
 tests/parser/unicode/{1744.stdout => T1744.stdout} | 0
 tests/parser/unicode/{2302.hs => T2302.hs}         | 0
 tests/parser/unicode/T2302.stderr                  | 2 ++
 tests/parser/unicode/{4373.hs => T4373.hs}         | 0
 tests/parser/unicode/all.T                         | 8 ++++----
 8 files changed, 6 insertions(+), 6 deletions(-)
 delete mode 100644 tests/parser/unicode/2302.stderr
 rename tests/parser/unicode/{1103.hs => T1103.hs} (100%)
 rename tests/parser/unicode/{1744.hs => T1744.hs} (100%)
 rename tests/parser/unicode/{1744.stdout => T1744.stdout} (100%)
 rename tests/parser/unicode/{2302.hs => T2302.hs} (100%)
 create mode 100644 tests/parser/unicode/T2302.stderr
 rename tests/parser/unicode/{4373.hs => T4373.hs} (100%)

diff --git a/tests/parser/unicode/2302.stderr b/tests/parser/unicode/2302.stderr
deleted file mode 100644
index 608c9ef0b..000000000
--- a/tests/parser/unicode/2302.stderr
+++ /dev/null
@@ -1,2 +0,0 @@
-
-2302.hs:1:5: Not in scope: data constructor `À'
diff --git a/tests/parser/unicode/1103.hs b/tests/parser/unicode/T1103.hs
similarity index 100%
rename from tests/parser/unicode/1103.hs
rename to tests/parser/unicode/T1103.hs
diff --git a/tests/parser/unicode/1744.hs b/tests/parser/unicode/T1744.hs
similarity index 100%
rename from tests/parser/unicode/1744.hs
rename to tests/parser/unicode/T1744.hs
diff --git a/tests/parser/unicode/1744.stdout b/tests/parser/unicode/T1744.stdout
similarity index 100%
rename from tests/parser/unicode/1744.stdout
rename to tests/parser/unicode/T1744.stdout
diff --git a/tests/parser/unicode/2302.hs b/tests/parser/unicode/T2302.hs
similarity index 100%
rename from tests/parser/unicode/2302.hs
rename to tests/parser/unicode/T2302.hs
diff --git a/tests/parser/unicode/T2302.stderr b/tests/parser/unicode/T2302.stderr
new file mode 100644
index 000000000..9718423be
--- /dev/null
+++ b/tests/parser/unicode/T2302.stderr
@@ -0,0 +1,2 @@
+
+T2302.hs:1:5: Not in scope: data constructor `À'
diff --git a/tests/parser/unicode/4373.hs b/tests/parser/unicode/T4373.hs
similarity index 100%
rename from tests/parser/unicode/4373.hs
rename to tests/parser/unicode/T4373.hs
diff --git a/tests/parser/unicode/all.T b/tests/parser/unicode/all.T
index e5375a361..c8ca793f7 100644
--- a/tests/parser/unicode/all.T
+++ b/tests/parser/unicode/all.T
@@ -16,7 +16,7 @@ test('utf8_022', normal, compile_fail, [''])
 
 test('utf8_024', normal, compile_and_run, [''])
 
-test('1744', normal, compile_and_run, [''])
-test('1103', normal, compile, [''])
-test('2302', only_ways(['normal']), compile_fail, [''])
-test('4373', normal, compile, [''])
+test('T1744', normal, compile_and_run, [''])
+test('T1103', normal, compile, [''])
+test('T2302', only_ways(['normal']), compile_fail, [''])
+test('T4373', normal, compile, [''])
-- 
GitLab


From f6257a22ab0a5de0716a1de279a67fcef4d317cb Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:13:28 +0000
Subject: [PATCH 052/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/llvm/should_compile/{5054.hs => T5054.hs}     |  0
 tests/llvm/should_compile/{5054_2.hs => T5054_2.hs} |  0
 tests/llvm/should_compile/{5486.hs => T5486.hs}     |  0
 tests/llvm/should_compile/{5681.hs => T5681.hs}     |  0
 tests/llvm/should_compile/{6158.hs => T6158.hs}     |  0
 tests/llvm/should_compile/all.T                     | 10 +++++-----
 6 files changed, 5 insertions(+), 5 deletions(-)
 rename tests/llvm/should_compile/{5054.hs => T5054.hs} (100%)
 rename tests/llvm/should_compile/{5054_2.hs => T5054_2.hs} (100%)
 rename tests/llvm/should_compile/{5486.hs => T5486.hs} (100%)
 rename tests/llvm/should_compile/{5681.hs => T5681.hs} (100%)
 rename tests/llvm/should_compile/{6158.hs => T6158.hs} (100%)

diff --git a/tests/llvm/should_compile/5054.hs b/tests/llvm/should_compile/T5054.hs
similarity index 100%
rename from tests/llvm/should_compile/5054.hs
rename to tests/llvm/should_compile/T5054.hs
diff --git a/tests/llvm/should_compile/5054_2.hs b/tests/llvm/should_compile/T5054_2.hs
similarity index 100%
rename from tests/llvm/should_compile/5054_2.hs
rename to tests/llvm/should_compile/T5054_2.hs
diff --git a/tests/llvm/should_compile/5486.hs b/tests/llvm/should_compile/T5486.hs
similarity index 100%
rename from tests/llvm/should_compile/5486.hs
rename to tests/llvm/should_compile/T5486.hs
diff --git a/tests/llvm/should_compile/5681.hs b/tests/llvm/should_compile/T5681.hs
similarity index 100%
rename from tests/llvm/should_compile/5681.hs
rename to tests/llvm/should_compile/T5681.hs
diff --git a/tests/llvm/should_compile/6158.hs b/tests/llvm/should_compile/T6158.hs
similarity index 100%
rename from tests/llvm/should_compile/6158.hs
rename to tests/llvm/should_compile/T6158.hs
diff --git a/tests/llvm/should_compile/all.T b/tests/llvm/should_compile/all.T
index 41167377f..61d0f3f61 100644
--- a/tests/llvm/should_compile/all.T
+++ b/tests/llvm/should_compile/all.T
@@ -5,10 +5,10 @@ def f( opts ):
 
 setTestOpts(f)
 
-test('5054', reqlib('hmatrix'), compile, ['-package hmatrix'])
-test('5054_2', reqlib('hmatrix'), compile, ['-package hmatrix'])
-test('5486', normal, compile, [''])
-test('5681', normal, compile, [''])
-test('6158', [reqlib('vector'), reqlib('primitive')], compile, ['-package vector -package primitive'])
+test('T5054', reqlib('hmatrix'), compile, ['-package hmatrix'])
+test('T5054_2', reqlib('hmatrix'), compile, ['-package hmatrix'])
+test('T5486', normal, compile, [''])
+test('T5681', normal, compile, [''])
+test('T6158', [reqlib('vector'), reqlib('primitive')], compile, ['-package vector -package primitive'])
 test('T7571', cmm_src, compile, [''])
 test('T7575', unless_wordsize(32, skip), compile, [''])
-- 
GitLab


From ffcccd06bbbc1a08c39bb788aeef52a88ad4fdc8 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:17:58 +0000
Subject: [PATCH 053/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/ghci/should_run/Makefile                      | 2 +-
 tests/ghci/should_run/{2589.hs => T2589.hs}         | 0
 tests/ghci/should_run/{2589.stdout => T2589.stdout} | 0
 tests/ghci/should_run/{2881.hs => T2881.hs}         | 0
 tests/ghci/should_run/{2881.stdout => T2881.stdout} | 0
 tests/ghci/should_run/{3171.stdout => T3171.stdout} | 0
 tests/ghci/should_run/all.T                         | 8 ++++----
 7 files changed, 5 insertions(+), 5 deletions(-)
 rename tests/ghci/should_run/{2589.hs => T2589.hs} (100%)
 rename tests/ghci/should_run/{2589.stdout => T2589.stdout} (100%)
 rename tests/ghci/should_run/{2881.hs => T2881.hs} (100%)
 rename tests/ghci/should_run/{2881.stdout => T2881.stdout} (100%)
 rename tests/ghci/should_run/{3171.stdout => T3171.stdout} (100%)

diff --git a/tests/ghci/should_run/Makefile b/tests/ghci/should_run/Makefile
index c61de9789..2558b54d0 100644
--- a/tests/ghci/should_run/Makefile
+++ b/tests/ghci/should_run/Makefile
@@ -3,7 +3,7 @@ include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk
 
 # Test that threadDelay can be interrupted by ^C.
-3171:
+T3171:
 	echo "do Control.Concurrent.threadDelay 3000000; putStrLn \"threadDelay was not interrupted\"" | \
 	"$(TEST_HC)" $(TEST_HC_OPTS) -ignore-dot-ghci -v0 --interactive & \
 	sleep 2; kill -INT $$!; wait
diff --git a/tests/ghci/should_run/2589.hs b/tests/ghci/should_run/T2589.hs
similarity index 100%
rename from tests/ghci/should_run/2589.hs
rename to tests/ghci/should_run/T2589.hs
diff --git a/tests/ghci/should_run/2589.stdout b/tests/ghci/should_run/T2589.stdout
similarity index 100%
rename from tests/ghci/should_run/2589.stdout
rename to tests/ghci/should_run/T2589.stdout
diff --git a/tests/ghci/should_run/2881.hs b/tests/ghci/should_run/T2881.hs
similarity index 100%
rename from tests/ghci/should_run/2881.hs
rename to tests/ghci/should_run/T2881.hs
diff --git a/tests/ghci/should_run/2881.stdout b/tests/ghci/should_run/T2881.stdout
similarity index 100%
rename from tests/ghci/should_run/2881.stdout
rename to tests/ghci/should_run/T2881.stdout
diff --git a/tests/ghci/should_run/3171.stdout b/tests/ghci/should_run/T3171.stdout
similarity index 100%
rename from tests/ghci/should_run/3171.stdout
rename to tests/ghci/should_run/T3171.stdout
diff --git a/tests/ghci/should_run/all.T b/tests/ghci/should_run/all.T
index 527461af2..d34eade39 100644
--- a/tests/ghci/should_run/all.T
+++ b/tests/ghci/should_run/all.T
@@ -8,14 +8,14 @@ def just_ghci( opts ):
 test('ghcirun001', just_ghci, compile_and_run, [''])
 test('ghcirun002', just_ghci, compile_and_run, [''])
 test('ghcirun003', just_ghci, compile_and_run, [''])
-test('2589',    just_ghci, compile_and_run, [''])
-test('2881',    just_ghci, compile_and_run, [''])
+test('T2589',      just_ghci, compile_and_run, [''])
+test('T2881',      just_ghci, compile_and_run, [''])
 
-test('3171',
+test('T3171',
      [if_os('mingw32',skip),
       req_interp,
       combined_output],
      run_command,
-     ['$MAKE -s --no-print-directory 3171'])
+     ['$MAKE -s --no-print-directory T3171'])
 
 test('ghcirun004', just_ghci, compile_and_run, [''])
-- 
GitLab


From 1e581ccef6cfa0d7ca533bcd1612802c1d3e0e07 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:20:52 +0000
Subject: [PATCH 054/223] Rename some numeric tests: nnnn -> Tnnnn

---
 tests/concurrent/{2317 => T2317}/Makefile                 | 0
 tests/concurrent/{2317/2317.hs => T2317/T2317.hs}         | 0
 tests/concurrent/{2317/2317.stdout => T2317/T2317.stdout} | 0
 tests/concurrent/{2317 => T2317}/all.T                    | 4 ++--
 tests/hsc2hs/Makefile                                     | 4 ++--
 tests/hsc2hs/{3837.hsc => T3837.hsc}                      | 0
 tests/hsc2hs/all.T                                        | 6 +++---
 tests/rename/should_compile/{2334.hs => T2334.hs}         | 0
 tests/rename/should_compile/all.T                         | 2 +-
 9 files changed, 8 insertions(+), 8 deletions(-)
 rename tests/concurrent/{2317 => T2317}/Makefile (100%)
 rename tests/concurrent/{2317/2317.hs => T2317/T2317.hs} (100%)
 rename tests/concurrent/{2317/2317.stdout => T2317/T2317.stdout} (100%)
 rename tests/concurrent/{2317 => T2317}/all.T (74%)
 rename tests/hsc2hs/{3837.hsc => T3837.hsc} (100%)
 rename tests/rename/should_compile/{2334.hs => T2334.hs} (100%)

diff --git a/tests/concurrent/2317/Makefile b/tests/concurrent/T2317/Makefile
similarity index 100%
rename from tests/concurrent/2317/Makefile
rename to tests/concurrent/T2317/Makefile
diff --git a/tests/concurrent/2317/2317.hs b/tests/concurrent/T2317/T2317.hs
similarity index 100%
rename from tests/concurrent/2317/2317.hs
rename to tests/concurrent/T2317/T2317.hs
diff --git a/tests/concurrent/2317/2317.stdout b/tests/concurrent/T2317/T2317.stdout
similarity index 100%
rename from tests/concurrent/2317/2317.stdout
rename to tests/concurrent/T2317/T2317.stdout
diff --git a/tests/concurrent/2317/all.T b/tests/concurrent/T2317/all.T
similarity index 74%
rename from tests/concurrent/2317/all.T
rename to tests/concurrent/T2317/all.T
index ab4e89072..0ad9db3dc 100644
--- a/tests/concurrent/2317/all.T
+++ b/tests/concurrent/T2317/all.T
@@ -1,5 +1,5 @@
-test('2317',
+test('T2317',
      [skip_if_fast,
       reqlib('parallel'), reqlib('random')],
      multimod_compile_and_run,
-     ['2317',''])
+     ['T2317',''])
diff --git a/tests/hsc2hs/Makefile b/tests/hsc2hs/Makefile
index 9fbd62c98..ec16b1647 100644
--- a/tests/hsc2hs/Makefile
+++ b/tests/hsc2hs/Makefile
@@ -24,7 +24,7 @@ hsc2hs004:
 	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 --make $@
 	./$@
 
-.PHONY: 3837
-3837:
+.PHONY: T3837
+T3837:
 	LANG=C '$(HSC2HS)' $@.hsc
 	'$(TEST_HC)' $(TEST_HC_OPTS) -c $@.hs
diff --git a/tests/hsc2hs/3837.hsc b/tests/hsc2hs/T3837.hsc
similarity index 100%
rename from tests/hsc2hs/3837.hsc
rename to tests/hsc2hs/T3837.hsc
diff --git a/tests/hsc2hs/all.T b/tests/hsc2hs/all.T
index b358dc409..b0957911b 100644
--- a/tests/hsc2hs/all.T
+++ b/tests/hsc2hs/all.T
@@ -20,8 +20,8 @@ test('hsc2hs004',
      ['$MAKE -s --no-print-directory hsc2hs004'])
 
 
-test('3837',
-     [extra_clean(['3837.hs', '3837_hsc_make.c'])],
+test('T3837',
+     [extra_clean(['T3837.hs', 'T3837_hsc_make.c'])],
      run_command,
-     ['$MAKE -s --no-print-directory 3837'])
+     ['$MAKE -s --no-print-directory T3837'])
 
diff --git a/tests/rename/should_compile/2334.hs b/tests/rename/should_compile/T2334.hs
similarity index 100%
rename from tests/rename/should_compile/2334.hs
rename to tests/rename/should_compile/T2334.hs
diff --git a/tests/rename/should_compile/all.T b/tests/rename/should_compile/all.T
index 0a51cd71d..f31b0a0e3 100644
--- a/tests/rename/should_compile/all.T
+++ b/tests/rename/should_compile/all.T
@@ -113,7 +113,7 @@ test('rn067',
 test('T1972', normal, compile, [''])
 test('T2205', normal, compile, [''])
 
-test('2334', normal, compile, [''])
+test('T2334', normal, compile, [''])
 test('T2506', normal, compile, [''])
 test('T2914', normal, compile, [''])
 test('T3221', normal, compile, [''])
-- 
GitLab


From 0d29b1bf960023caa91f68dba21fb7b26a419e8e Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:32:26 +0000
Subject: [PATCH 055/223] Make numeric-only test names a framework failure

---
 driver/testlib.py | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 0c8e1f340..40ecf86d6 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -645,7 +645,7 @@ def test (name, setup, func, args):
     global allTestNames
     if name in allTestNames:
         framework_fail(name, 'duplicate', 'There are multiple tests with this name')
-    if not re.match('^[a-zA-Z0-9][a-zA-Z0-9._-]*$', name):
+    if not re.match('^[0-9]*[a-zA-Z][a-zA-Z0-9._-]*$', name):
         framework_fail(name, 'bad_name', 'This test has an invalid name')
     myTestOpts = copy.copy(thisdir_testopts)
 
-- 
GitLab


From 6be3a5db40ce1f862d8b5647844eadf1bef3ea56 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 16:38:43 +0000
Subject: [PATCH 056/223] Rename a test that shared its name with another test

---
 .../indexed-types/should_fail/{T2334.hs => T2334A.hs}  |  0
 .../should_fail/{T2334.stderr => T2334A.stderr}        | 10 +++++-----
 tests/indexed-types/should_fail/all.T                  |  2 +-
 3 files changed, 6 insertions(+), 6 deletions(-)
 rename tests/indexed-types/should_fail/{T2334.hs => T2334A.hs} (100%)
 rename tests/indexed-types/should_fail/{T2334.stderr => T2334A.stderr} (74%)

diff --git a/tests/indexed-types/should_fail/T2334.hs b/tests/indexed-types/should_fail/T2334A.hs
similarity index 100%
rename from tests/indexed-types/should_fail/T2334.hs
rename to tests/indexed-types/should_fail/T2334A.hs
diff --git a/tests/indexed-types/should_fail/T2334.stderr b/tests/indexed-types/should_fail/T2334A.stderr
similarity index 74%
rename from tests/indexed-types/should_fail/T2334.stderr
rename to tests/indexed-types/should_fail/T2334A.stderr
index b8efc5938..16ad7b047 100644
--- a/tests/indexed-types/should_fail/T2334.stderr
+++ b/tests/indexed-types/should_fail/T2334A.stderr
@@ -1,17 +1,17 @@
 
-T2334.hs:9:26:
+T2334A.hs:9:26:
     The constructor of a newtype must have exactly one field
       but `F' has two
     In the definition of data constructor `F'
     In the newtype instance declaration for `F'
 
-T2334.hs:10:27:
+T2334A.hs:10:27:
     The constructor of a newtype must have exactly one field
       but `H' has none
     In the definition of data constructor `H'
     In the newtype instance declaration for `F'
 
-T2334.hs:12:15:
+T2334A.hs:12:15:
     Conflicting family instance declarations:
-      F Bool -- Defined at T2334.hs:12:15
-      F Bool -- Defined at T2334.hs:13:15
+      F Bool -- Defined at T2334A.hs:12:15
+      F Bool -- Defined at T2334A.hs:13:15
diff --git a/tests/indexed-types/should_fail/all.T b/tests/indexed-types/should_fail/all.T
index 316e1ff0f..82c1bcecc 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -41,7 +41,7 @@ test('Over',
 
 test('SkolemOccursLoop', expect_fail, compile_fail, [''])
 
-test('T2334', normal, compile_fail, [''])
+test('T2334A', normal, compile_fail, [''])
 test('T1900', normal, compile_fail, [''])
 test('T2157', normal, compile_fail, [''])
 test('T2203a', normal, compile_fail, [''])
-- 
GitLab


From 6b5cec37f62bc41f12dd614a534c2aa2f79c7cf7 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 22:57:19 +0000
Subject: [PATCH 057/223] Revert "fix runtests to set LD_LIBRARY_PATH
 environment variable."

This reverts commit d262089127c54bfe81963628ac70a309f8133492.

We shouldn't need to do this on Linux.
---
 driver/runtests.py | 48 +++++++++++++++++++++-------------------------
 1 file changed, 22 insertions(+), 26 deletions(-)

diff --git a/driver/runtests.py b/driver/runtests.py
index d2b5c7849..66e3bf4d5 100644
--- a/driver/runtests.py
+++ b/driver/runtests.py
@@ -181,32 +181,28 @@ from testlib import *
 
 # On Windows we need to set $PATH to include the paths to all the DLLs
 # in order for the dynamic library tests to work.
-# if windows or darwin:
-pkginfo = getStdout([config.ghc_pkg, 'dump'])
-topdir = config.libdir
-for line in pkginfo.split('\n'):
-    if line.startswith('library-dirs:'):
-        path = line.rstrip()
-        path = re.sub('^library-dirs: ', '', path)
-        path = re.sub('\\$topdir', topdir, path)
-        if path.startswith('"'):
-            path = re.sub('^"(.*)"$', '\\1', path)
-            path = re.sub('\\\\(.)', '\\1', path)
-        if windows:
-            if config.cygwin:
-                # On cygwin we can't put "c:\foo" in $PATH, as : is a
-                # field separator. So convert to /cygdrive/c/foo instead.
-                # Other pythons use ; as the separator, so no problem.
-                path = re.sub('([a-zA-Z]):', '/cygdrive/\\1', path)
-                path = re.sub('\\\\', '/', path)
-            os.environ['PATH'] = os.pathsep.join([path, os.environ.get("PATH", "")])
-        elif darwin:
-            # darwin
-            os.environ['DYLD_LIBRARY_PATH'] = os.pathsep.join([path, os.environ.get("DYLD_LIBRARY_PATH", "")])
-        else:
-            # unix
-            os.environ['LD_LIBRARY_PATH'] = os.pathsep.join([path, os.environ.get("LD_LIBRARY_PATH", "")])
-
+if windows or darwin:
+    pkginfo = getStdout([config.ghc_pkg, 'dump'])
+    topdir = config.libdir
+    for line in pkginfo.split('\n'):
+        if line.startswith('library-dirs:'):
+            path = line.rstrip()
+            path = re.sub('^library-dirs: ', '', path)
+            path = re.sub('\\$topdir', topdir, path)
+            if path.startswith('"'):
+                path = re.sub('^"(.*)"$', '\\1', path)
+                path = re.sub('\\\\(.)', '\\1', path)
+            if windows:
+                if config.cygwin:
+                    # On cygwin we can't put "c:\foo" in $PATH, as : is a
+                    # field separator. So convert to /cygdrive/c/foo instead.
+                    # Other pythons use ; as the separator, so no problem.
+                    path = re.sub('([a-zA-Z]):', '/cygdrive/\\1', path)
+                    path = re.sub('\\\\', '/', path)
+                os.environ['PATH'] = os.pathsep.join([path, os.environ.get("PATH", "")])
+            else:
+                # darwin
+                os.environ['DYLD_LIBRARY_PATH'] = os.pathsep.join([path, os.environ.get("DYLD_LIBRARY_PATH", "")])
 
 global testopts_local
 testopts_local.x = TestOptions()
-- 
GitLab


From 07ce09b959e56c7f3cb248c57ba7ebe684351f7d Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Fri, 25 Jan 2013 16:57:31 +0000
Subject: [PATCH 058/223] numrun012(ghci) now passes on Windows

I don't know why it started working, but we didn't know why it didn't work
before either.
---
 tests/numeric/should_run/all.T | 7 +------
 1 file changed, 1 insertion(+), 6 deletions(-)

diff --git a/tests/numeric/should_run/all.T b/tests/numeric/should_run/all.T
index beee59da8..b2109de9e 100644
--- a/tests/numeric/should_run/all.T
+++ b/tests/numeric/should_run/all.T
@@ -35,12 +35,7 @@ test('arith015', normal, compile_and_run, [''])
 test('numrun009', normal, compile_and_run, [''])
 test('numrun010', normal, compile_and_run, [''])
 test('numrun011', normal, compile_and_run, [''])
-test('numrun012',
-        if_os('mingw32',expect_fail_for('ghci')),
-        # on Windows, GHCi says that "logBase 2 (2^31)" is "31.0", but
-        # other platforms (and compiled on Windows) reports 31.000000000000004
-        # I have no idea where the discrepancy comes from.  --SDM
-        compile_and_run, [''])
+test('numrun012', normal, compile_and_run, [''])
 test('numrun013', normal, compile_and_run, [''])
 test('numrun014', normal, compile_and_run, [''])
 test('arith016', compose(normal,only_compiler_types(['ghc'])), compile_and_run, [''])
-- 
GitLab


From 0a1e0e63b1294ee3498b15a3e5de752b3caa2c15 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Fri, 25 Jan 2013 19:11:00 +0000
Subject: [PATCH 059/223] Handles TEST_HC=c:/... on Windows

---
 mk/boilerplate.mk | 16 ++++++++++++++--
 1 file changed, 14 insertions(+), 2 deletions(-)

diff --git a/mk/boilerplate.mk b/mk/boilerplate.mk
index f1cd6c813..f9ed52ee0 100644
--- a/mk/boilerplate.mk
+++ b/mk/boilerplate.mk
@@ -66,9 +66,21 @@ IN_TREE_COMPILER = NO
 # passed in by the user, but
 #     which ghc          == /usr/bin/ghc
 #     which /usr/bin/ghc == /usr/bin/ghc
-# so we can just always 'which' it. We need to use 'override' in order
-# to override a value given on the commandline.
+# so on unix-like platforms we can just always 'which' it.
+# However, on cygwin, we can't just use which:
+#     $ which c:/ghc/ghc-7.4.1/bin/ghc.exe
+#     which: no ghc.exe in (./c:/ghc/ghc-7.4.1/bin)
+# so we start off by using realpath, and if that succeeds then we use
+# that value. Otherwise we fall back on 'which'.
+#
+# Note also that we need to use 'override' in order to override a
+# value given on the commandline.
+TEST_HC_REALPATH := $(realpath $(TEST_HC))
+ifeq "$(TEST_HC_REALPATH)" ""
 override TEST_HC := $(shell which '$(TEST_HC)')
+else
+override TEST_HC := $(TEST_HC_REALPATH)
+endif
 endif
 
 # We can't use $(dir ...) here as TEST_HC might be in a path
-- 
GitLab


From 07076dcf291c76e8e92da8201fddf019c16446c8 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Fri, 25 Jan 2013 20:17:45 +0000
Subject: [PATCH 060/223] Fix T7037 on Windows

---
 tests/rts/T7037_main.c | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/tests/rts/T7037_main.c b/tests/rts/T7037_main.c
index 91f3130a4..cca668179 100644
--- a/tests/rts/T7037_main.c
+++ b/tests/rts/T7037_main.c
@@ -1,6 +1,7 @@
+#include <stddef.h>
 #include <unistd.h>
 
 int main(int argc, char *argv[]) {
-    char *args[1] = {NULL};
+    const char *args[2] = {"T7037", NULL};
     execv("./T7037", args);
 }
-- 
GitLab


From 7ba16b1cafe036579158d4501085cfa10da3e5fa Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Fri, 25 Jan 2013 20:35:16 +0000
Subject: [PATCH 061/223] Tweak a comment to help vim's syntax highlighting

---
 tests/ghci/scripts/all.T | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index e44aa6c34..659a27566 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -12,7 +12,7 @@ test('ghci007', combined_output, ghci_script, ['ghci007.script'])
 test('ghci008', combined_output, ghci_script, ['ghci008.script'])
 test('ghci009', combined_output, ghci_script, ['ghci009.script'])
 
-# Skip this test: deadlock can't be detected now, because we wait for
+# Skip this test: deadlock cannot be detected now, because we wait for
 # signals to arrive if there are signal handlers installed, and GHCi
 # has a ^C handler installed.
 test('ghci010', skip, ghci_script, ['ghci010.script'])
-- 
GitLab


From e00e0ddb6fec558e0e4c881f3314eca125db5656 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Fri, 25 Jan 2013 20:55:09 +0000
Subject: [PATCH 062/223] dynCompileExpr(dyn) fails on Windows as ghc isn't
 built the dyn way

---
 tests/ghc-api/dynCompileExpr/all.T | 1 +
 1 file changed, 1 insertion(+)

diff --git a/tests/ghc-api/dynCompileExpr/all.T b/tests/ghc-api/dynCompileExpr/all.T
index 108b96407..b466a3a59 100644
--- a/tests/ghc-api/dynCompileExpr/all.T
+++ b/tests/ghc-api/dynCompileExpr/all.T
@@ -1,4 +1,5 @@
 test('dynCompileExpr',
      [ extra_run_opts('"' + config.libdir + '"'),
+       if_os('mingw32', expect_broken_for(5987, ['dyn'])),
        omit_ways(prof_ways) ], # cannot run interpreted code with -prof
      compile_and_run, ['-package ghc'])
-- 
GitLab


From 6870a4896bfac33e93f300c44841e28403c653ed Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 25 Jan 2013 23:35:28 +0000
Subject: [PATCH 063/223] Make T7037 work on both Windows and other platforms

---
 tests/rts/T7037_main.c | 5 ++++-
 1 file changed, 4 insertions(+), 1 deletion(-)

diff --git a/tests/rts/T7037_main.c b/tests/rts/T7037_main.c
index cca668179..c19583465 100644
--- a/tests/rts/T7037_main.c
+++ b/tests/rts/T7037_main.c
@@ -2,6 +2,9 @@
 #include <unistd.h>
 
 int main(int argc, char *argv[]) {
-    const char *args[2] = {"T7037", NULL};
+#ifdef __MINGW32__
+    const
+#endif
+    char * args[2] = {"T7037", NULL};
     execv("./T7037", args);
 }
-- 
GitLab


From bd0f7424562965419f1cc0cea9c9aedb8acd9ce2 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Mon, 28 Jan 2013 09:28:40 +0000
Subject: [PATCH 064/223] test for #2435

---
 tests/rename/should_compile/T2435.hs    | 4 ++++
 tests/rename/should_compile/T2435Foo.hs | 3 +++
 tests/rename/should_compile/all.T       | 2 ++
 3 files changed, 9 insertions(+)
 create mode 100644 tests/rename/should_compile/T2435.hs
 create mode 100644 tests/rename/should_compile/T2435Foo.hs

diff --git a/tests/rename/should_compile/T2435.hs b/tests/rename/should_compile/T2435.hs
new file mode 100644
index 000000000..ab58f2bb7
--- /dev/null
+++ b/tests/rename/should_compile/T2435.hs
@@ -0,0 +1,4 @@
+{-# LANGUAGE TypeFamilies #-}
+module Bar where
+import qualified T2435Foo as Foo
+instance Foo.C Int where type T Int = Int
diff --git a/tests/rename/should_compile/T2435Foo.hs b/tests/rename/should_compile/T2435Foo.hs
new file mode 100644
index 000000000..47fba68e6
--- /dev/null
+++ b/tests/rename/should_compile/T2435Foo.hs
@@ -0,0 +1,3 @@
+{-# LANGUAGE TypeFamilies #-}
+module T2435Foo where
+class C a where type T a
diff --git a/tests/rename/should_compile/all.T b/tests/rename/should_compile/all.T
index f31b0a0e3..a1f1965bd 100644
--- a/tests/rename/should_compile/all.T
+++ b/tests/rename/should_compile/all.T
@@ -202,3 +202,5 @@ test('dodgy',
      ['dodgy', '-v0'])
 test('T7167', normal, compile, [''])
 test('T7336', normal, compile, ['-Wall'])
+
+test('T2435', normal, multimod_compile, ['T2435','-v0'])
-- 
GitLab


From cf6e54d4ca28243121ebbab7bdeaaeac5ae3d8a1 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Mon, 28 Jan 2013 18:13:11 +0000
Subject: [PATCH 065/223] Debug output wibbles

---
 tests/indexed-types/should_compile/T3017.stderr | 2 +-
 tests/typecheck/should_compile/tc231.stderr     | 2 +-
 2 files changed, 2 insertions(+), 2 deletions(-)

diff --git a/tests/indexed-types/should_compile/T3017.stderr b/tests/indexed-types/should_compile/T3017.stderr
index 28ddc1452..a6b44e3ad 100644
--- a/tests/indexed-types/should_compile/T3017.stderr
+++ b/tests/indexed-types/should_compile/T3017.stderr
@@ -15,7 +15,7 @@ TYPE CONSTRUCTORS
       = L :: forall a. [a] -> ListColl a Stricts: _
       FamilyInstance: none
 COERCION AXIOMS
-  axiom Foo.TFCo:R:ElemListColl :: forall a. Elem (ListColl a) ~# a
+  axiom Foo.TFCo:R:ElemListColl :: Elem (ListColl a) = a
 INSTANCES
   instance Coll (ListColl a) -- Defined at T3017.hs:12:11
 FAMILY INSTANCES
diff --git a/tests/typecheck/should_compile/tc231.stderr b/tests/typecheck/should_compile/tc231.stderr
index 99f7dfdb2..e8ebcc7ba 100644
--- a/tests/typecheck/should_compile/tc231.stderr
+++ b/tests/typecheck/should_compile/tc231.stderr
@@ -24,6 +24,6 @@ TYPE CONSTRUCTORS
       huh :: forall chain. Q s a chain -> ST s ()
 COERCION AXIOMS
   axiom ShouldCompile.NTCo:Zork ::
-    forall s a b. Zork s a b ~# (forall chain. Q s a chain -> ST s ())
+    Zork s a b = forall chain. Q s a chain -> ST s ()
 Dependent modules: []
 Dependent packages: [base, ghc-prim, integer-gmp]
-- 
GitLab


From bacd25d94cac74d1100b8350c00c7876e2fbcf03 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Mon, 28 Jan 2013 21:04:23 +0000
Subject: [PATCH 066/223] Test Trac #7524

---
 tests/polykinds/T7524.hs     | 6 ++++++
 tests/polykinds/T7524.stderr | 5 +++++
 tests/polykinds/all.T        | 1 +
 3 files changed, 12 insertions(+)
 create mode 100644 tests/polykinds/T7524.hs
 create mode 100644 tests/polykinds/T7524.stderr

diff --git a/tests/polykinds/T7524.hs b/tests/polykinds/T7524.hs
new file mode 100644
index 000000000..52b24282b
--- /dev/null
+++ b/tests/polykinds/T7524.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE TypeFamilies, PolyKinds #-}
+module T7524 where
+
+type family F (a :: k1) (b :: k2)
+type instance F a a = Int
+type instance F a b = Bool
diff --git a/tests/polykinds/T7524.stderr b/tests/polykinds/T7524.stderr
new file mode 100644
index 000000000..5d909593e
--- /dev/null
+++ b/tests/polykinds/T7524.stderr
@@ -0,0 +1,5 @@
+
+T7524.hs:5:15:
+    Conflicting family instance declarations:
+      F k k a a -- Defined at T7524.hs:5:15
+      F k k1 a b -- Defined at T7524.hs:6:15
diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T
index d84048f1c..575c43eb3 100644
--- a/tests/polykinds/all.T
+++ b/tests/polykinds/all.T
@@ -83,3 +83,4 @@ test('T7404', normal, compile_fail,[''])
 test('T7502', normal, compile,[''])
 test('T7488', normal, compile,[''])
 test('T7594', normal, compile_fail,[''])
+test('T7524', normal, compile_fail,[''])
-- 
GitLab


From 01f5abf3fbe8d1199a68cf4b42af0b47f416fe54 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Tue, 29 Jan 2013 08:52:33 +0000
Subject: [PATCH 067/223] SimpleFail9 now passes, which is actually fine

---
 tests/indexed-types/should_fail/SimpleFail9.hs     | 4 +++-
 tests/indexed-types/should_fail/SimpleFail9.stderr | 7 -------
 tests/indexed-types/should_fail/all.T              | 2 +-
 3 files changed, 4 insertions(+), 9 deletions(-)
 delete mode 100644 tests/indexed-types/should_fail/SimpleFail9.stderr

diff --git a/tests/indexed-types/should_fail/SimpleFail9.hs b/tests/indexed-types/should_fail/SimpleFail9.hs
index d45c9830a..927c60caf 100644
--- a/tests/indexed-types/should_fail/SimpleFail9.hs
+++ b/tests/indexed-types/should_fail/SimpleFail9.hs
@@ -8,6 +8,8 @@ class C7 a b where
 instance C7 Char (a, Bool) where
   data S7 (a, Bool) = S7_1
 
--- must fail: type indexes don't match the instance types
+-- Used to fail, but now passes: 
+-- type indexes don't match the instance types by name
+-- but do by structure
 instance C7 Char (a, Int) where
   data S7 (b, Int) = S7_2
diff --git a/tests/indexed-types/should_fail/SimpleFail9.stderr b/tests/indexed-types/should_fail/SimpleFail9.stderr
deleted file mode 100644
index 4d6ea1c94..000000000
--- a/tests/indexed-types/should_fail/SimpleFail9.stderr
+++ /dev/null
@@ -1,7 +0,0 @@
-
-SimpleFail9.hs:13:3:
-    Type indexes must match class instance head
-    Found `(b, Int)' but expected `(a, Int)'
-    In the data declaration for `S7'
-    In the data instance declaration for `S7'
-    In the instance declaration for `C7 Char (a, Int)'
diff --git a/tests/indexed-types/should_fail/all.T b/tests/indexed-types/should_fail/all.T
index 82c1bcecc..19b05e63d 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -12,7 +12,7 @@ test('SimpleFail5b', normal, compile_fail, [''])
 test('SimpleFail6', normal, compile_fail, [''])
 test('SimpleFail7', normal, compile_fail, [''])
 test('SimpleFail8', normal, compile_fail, [''])
-test('SimpleFail9', normal, compile_fail, [''])
+test('SimpleFail9', normal, compile, [''])
 test('SimpleFail10', normal, compile, [''])
 test('SimpleFail11a', normal, compile_fail, [''])
 test('SimpleFail11b', normal, compile_fail, [''])
-- 
GitLab


From 43e279b84bc9ab1cbd0fa850ff3cd45754db1f99 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Tue, 29 Jan 2013 09:55:18 +0000
Subject: [PATCH 068/223] update haddock.base figures

---
 tests/perf/haddock/all.T | 6 ++++--
 1 file changed, 4 insertions(+), 2 deletions(-)

diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T
index 5104ea9d1..07942bd66 100644
--- a/tests/perf/haddock/all.T
+++ b/tests/perf/haddock/all.T
@@ -2,21 +2,23 @@
 test('haddock.base',
      [unless_in_tree_compiler(skip)
      ,if_wordsize(64,
-          stats_range_field('peak_megabytes_allocated', 249, 10))
+          stats_range_field('peak_megabytes_allocated', 274, 10))
                                         # 2012-08-14: 240 (amd64/Linux)
                                         # 2012-09-18: 237 (amd64/Linux)
                                         # 2012-11-12: 249 (amd64/Linux)
+                                        # 2013-01-29: 274 (amd64/Linux)
      ,if_wordsize(32,
           stats_num_field('peak_megabytes_allocated', 110,
                                                       115))
                                         # 2012-08-14: 144 (x86/OSX)
                                         # 2012-10-30: 113 (x86/Windows)
      ,if_wordsize(64,
-          stats_range_field('max_bytes_used', 87265136, 10))
+          stats_range_field('max_bytes_used', 96022312, 10))
                                 # 2012-08-14: 87374568 (amd64/Linux)
                                 # 2012-08-21: 86428216 (amd64/Linux)
                                 # 2012-09-20: 84794136 (amd64/Linux)
                                 # 2012-11-12: 87265136 (amd64/Linux)
+                                # 2013-01-29: 96022312 (amd64/Linux)
      ,if_wordsize(32,
           stats_range_field('max_bytes_used', 45574928, 1))
                                 # 2012-08-14: 45574928 (x86/OSX)
-- 
GitLab


From b06fbe7c956ac1ea2babc242bc2602800a7ea0ac Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Tue, 29 Jan 2013 09:59:10 +0000
Subject: [PATCH 069/223] T5113 is passing, remove expect_broken, see comment
 on #7046

---
 tests/perf/should_run/all.T | 4 +++-
 1 file changed, 3 insertions(+), 1 deletion(-)

diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 9d1c0adcd..b201bb1b1 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -120,7 +120,9 @@ test('T5113',
           stats_num_field('bytes allocated', 8000000,
                                              9000000)),
       only_ways(['normal']),
-      expect_broken(7046)
+      normal
+      # WAS: expect_broken(7046)
+      # but it started working again around 01/2013, see #7046
       ],
      compile_and_run,
      ['-O'])
-- 
GitLab


From 15822dbd37773c55fb354bc515da0a32495216cf Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 26 Jan 2013 15:58:19 +0000
Subject: [PATCH 070/223] Remove some redundant 'extra cleaning' in T4850

---
 tests/rts/all.T | 3 +--
 1 file changed, 1 insertion(+), 2 deletions(-)

diff --git a/tests/rts/all.T b/tests/rts/all.T
index 18617bd74..50c6b3b00 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -112,8 +112,7 @@ test('exec_signals', [
 
 test('return_mem_to_os', normal, compile_and_run, [''])
 
-test('T4850', extra_clean(['T4850.o','T4850.hi','T4850']),
-             run_command, ['$MAKE -s --no-print-directory T4850'])
+test('T4850', normal, run_command, ['$MAKE -s --no-print-directory T4850'])
 
 def config_T5250(opts):
     if not (config.arch in ['i386','x86_64']):
-- 
GitLab


From bdcc18611862283aa4bf55afebda65a0f85e06a5 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 30 Jan 2013 08:24:11 +0000
Subject: [PATCH 071/223] Test Trac #7609

---
 tests/typecheck/should_fail/T7609.hs     | 8 ++++++++
 tests/typecheck/should_fail/T7609.stderr | 6 ++++++
 tests/typecheck/should_fail/all.T        | 1 +
 3 files changed, 15 insertions(+)
 create mode 100644 tests/typecheck/should_fail/T7609.hs
 create mode 100644 tests/typecheck/should_fail/T7609.stderr

diff --git a/tests/typecheck/should_fail/T7609.hs b/tests/typecheck/should_fail/T7609.hs
new file mode 100644
index 000000000..242fa94a9
--- /dev/null
+++ b/tests/typecheck/should_fail/T7609.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE TypeOperators #-}
+
+module T7609 where
+
+data X a b
+
+f :: (a `X` a, Maybe)
+f = undefined
diff --git a/tests/typecheck/should_fail/T7609.stderr b/tests/typecheck/should_fail/T7609.stderr
new file mode 100644
index 000000000..d3430db3e
--- /dev/null
+++ b/tests/typecheck/should_fail/T7609.stderr
@@ -0,0 +1,6 @@
+
+T7609.hs:7:16:
+    Expecting one more argument to `Maybe'
+    The second argument of a tuple should have kind `*',
+      but `Maybe' has kind `* -> *'
+    In the type signature for `f': f :: (a `X` a, Maybe)
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index ad62ce75f..1241e587f 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -294,3 +294,4 @@ test('T7368a', normal, compile_fail, [''])
 test('T7545', normal, compile_fail, [''])
 test('T7279', normal, compile_fail, [''])
 test('T2247', normal, compile_fail, [''])
+test('T7609', normal, compile_fail, [''])
-- 
GitLab


From 7c5c2ae6d92a26062d73dca294839f30f5495500 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 30 Jan 2013 08:24:59 +0000
Subject: [PATCH 072/223] Interface files now include promotion flags

---
 tests/rename/should_fail/rnfail055.stderr | 218 +++++++++++-----------
 1 file changed, 109 insertions(+), 109 deletions(-)

diff --git a/tests/rename/should_fail/rnfail055.stderr b/tests/rename/should_fail/rnfail055.stderr
index a468cc063..cd559cca9 100644
--- a/tests/rename/should_fail/rnfail055.stderr
+++ b/tests/rename/should_fail/rnfail055.stderr
@@ -1,109 +1,109 @@
-
-RnFail055.hs:1:73: Warning:
-    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
-
-RnFail055.hs-boot:1:73: Warning:
-    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
-
-RnFail055.hs-boot:4:1:
-    Identifier `f1' has conflicting definitions in the module and its hs-boot file
-    Main module: f1 :: Int -> Float
-    Boot file:   f1 :: Float -> Int
-
-RnFail055.hs-boot:6:6:
-    Type constructor `S1' has conflicting definitions in the module and its hs-boot file
-    Main module: type S1 a b = (a, b)
-    Boot file:   type S1 a b c = (a, b)
-
-RnFail055.hs-boot:8:6:
-    Type constructor `S2' has conflicting definitions in the module and its hs-boot file
-    Main module: type S2 a b = forall a1. (a1, b)
-    Boot file:   type S2 a b = forall b1. (a, b1)
-
-RnFail055.hs-boot:12:6:
-    Type constructor `T1' has conflicting definitions in the module and its hs-boot file
-    Main module: data T1 a b
-                     No C type associated
-                     RecFlag Recursive
-                     = T1 :: forall a b. [b] -> [a] -> T1 a b Stricts: _ _
-                     FamilyInstance: none
-    Boot file:   data T1 a b
-                     No C type associated
-                     RecFlag NonRecursive
-                     = T1 :: forall a b. [a] -> [b] -> T1 a b Stricts: _ _
-                     FamilyInstance: none
-
-RnFail055.hs-boot:14:16:
-    Type constructor `T2' has conflicting definitions in the module and its hs-boot file
-    Main module: data Eq b => T2 a b
-                     No C type associated
-                     RecFlag Recursive
-                     = T2 :: forall a b. a -> T2 a b Stricts: _
-                     FamilyInstance: none
-    Boot file:   data Eq a => T2 a b
-                     No C type associated
-                     RecFlag NonRecursive
-                     = T2 :: forall a b. a -> T2 a b Stricts: _
-                     FamilyInstance: none
-
-RnFail055.hs-boot:16:11:
-    T3 is exported by the hs-boot file, but not exported by the module
-
-RnFail055.hs-boot:17:12:
-    T3' is exported by the hs-boot file, but not exported by the module
-
-RnFail055.hs-boot:21:6:
-    Type constructor `T5' has conflicting definitions in the module and its hs-boot file
-    Main module: data T5 a
-                     No C type associated
-                     RecFlag Recursive
-                     = T5 :: forall a. a -> T5 a Stricts: _ Fields: field5
-                     FamilyInstance: none
-    Boot file:   data T5 a
-                     No C type associated
-                     RecFlag NonRecursive
-                     = T5 :: forall a. a -> T5 a Stricts: _
-                     FamilyInstance: none
-
-RnFail055.hs-boot:23:6:
-    Type constructor `T6' has conflicting definitions in the module and its hs-boot file
-    Main module: data T6
-                     No C type associated
-                     RecFlag Recursive
-                     = T6 :: Int -> T6 Stricts: _
-                     FamilyInstance: none
-    Boot file:   data T6
-                     No C type associated
-                     RecFlag NonRecursive
-                     = T6 :: Int -> T6 HasWrapper Stricts: !
-                     FamilyInstance: none
-
-RnFail055.hs-boot:25:6:
-    Type constructor `T7' has conflicting definitions in the module and its hs-boot file
-    Main module: data T7 a
-                     No C type associated
-                     RecFlag Recursive
-                     = T7 :: forall a a1. a1 -> T7 a Stricts: _
-                     FamilyInstance: none
-    Boot file:   data T7 a
-                     No C type associated
-                     RecFlag NonRecursive
-                     = T7 :: forall a b. a -> T7 a Stricts: _
-                     FamilyInstance: none
-
-RnFail055.hs-boot:27:22:
-    RnFail055.m1 is exported by the hs-boot file, but not exported by the module
-
-RnFail055.hs-boot:28:7:
-    Class `C2' has conflicting definitions in the module and its hs-boot file
-    Main module: class C2 a b
-                     RecFlag Recursive
-                     m2 :: a -> b m2' :: a -> b
-    Boot file:   class C2 a b
-                     RecFlag NonRecursive
-                     m2 :: a -> b
-
-RnFail055.hs-boot:29:24:
-    Class `C3' has conflicting definitions in the module and its hs-boot file
-    Main module: class (Eq a, Ord a) => C3 a RecFlag Recursive
-    Boot file:   class (Ord a, Eq a) => C3 a RecFlag NonRecursive
+
+RnFail055.hs:1:73: Warning:
+    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
+
+RnFail055.hs-boot:1:73: Warning:
+    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
+
+RnFail055.hs-boot:4:1:
+    Identifier `f1' has conflicting definitions in the module and its hs-boot file
+    Main module: f1 :: Int -> Float
+    Boot file:   f1 :: Float -> Int
+
+RnFail055.hs-boot:6:6:
+    Type constructor `S1' has conflicting definitions in the module and its hs-boot file
+    Main module: type S1 a b = (a, b)
+    Boot file:   type S1 a b c = (a, b)
+
+RnFail055.hs-boot:8:6:
+    Type constructor `S2' has conflicting definitions in the module and its hs-boot file
+    Main module: type S2 a b = forall a1. (a1, b)
+    Boot file:   type S2 a b = forall b1. (a, b1)
+
+RnFail055.hs-boot:12:6:
+    Type constructor `T1' has conflicting definitions in the module and its hs-boot file
+    Main module: data T1 a b
+                     No C type associated
+                     RecFlag Recursive, Promotable
+                     = T1 :: forall a b. [b] -> [a] -> T1 a b Stricts: _ _
+                     FamilyInstance: none
+    Boot file:   data T1 a b
+                     No C type associated
+                     RecFlag NonRecursive, Promotable
+                     = T1 :: forall a b. [a] -> [b] -> T1 a b Stricts: _ _
+                     FamilyInstance: none
+
+RnFail055.hs-boot:14:16:
+    Type constructor `T2' has conflicting definitions in the module and its hs-boot file
+    Main module: data Eq b => T2 a b
+                     No C type associated
+                     RecFlag Recursive, Promotable
+                     = T2 :: forall a b. a -> T2 a b Stricts: _
+                     FamilyInstance: none
+    Boot file:   data Eq a => T2 a b
+                     No C type associated
+                     RecFlag NonRecursive, Promotable
+                     = T2 :: forall a b. a -> T2 a b Stricts: _
+                     FamilyInstance: none
+
+RnFail055.hs-boot:16:11:
+    T3 is exported by the hs-boot file, but not exported by the module
+
+RnFail055.hs-boot:17:12:
+    T3' is exported by the hs-boot file, but not exported by the module
+
+RnFail055.hs-boot:21:6:
+    Type constructor `T5' has conflicting definitions in the module and its hs-boot file
+    Main module: data T5 a
+                     No C type associated
+                     RecFlag Recursive, Promotable
+                     = T5 :: forall a. a -> T5 a Stricts: _ Fields: field5
+                     FamilyInstance: none
+    Boot file:   data T5 a
+                     No C type associated
+                     RecFlag NonRecursive, Promotable
+                     = T5 :: forall a. a -> T5 a Stricts: _
+                     FamilyInstance: none
+
+RnFail055.hs-boot:23:6:
+    Type constructor `T6' has conflicting definitions in the module and its hs-boot file
+    Main module: data T6
+                     No C type associated
+                     RecFlag Recursive, Not promotable
+                     = T6 :: Int -> T6 Stricts: _
+                     FamilyInstance: none
+    Boot file:   data T6
+                     No C type associated
+                     RecFlag NonRecursive, Not promotable
+                     = T6 :: Int -> T6 HasWrapper Stricts: !
+                     FamilyInstance: none
+
+RnFail055.hs-boot:25:6:
+    Type constructor `T7' has conflicting definitions in the module and its hs-boot file
+    Main module: data T7 a
+                     No C type associated
+                     RecFlag Recursive, Promotable
+                     = T7 :: forall a a1. a1 -> T7 a Stricts: _
+                     FamilyInstance: none
+    Boot file:   data T7 a
+                     No C type associated
+                     RecFlag NonRecursive, Promotable
+                     = T7 :: forall a b. a -> T7 a Stricts: _
+                     FamilyInstance: none
+
+RnFail055.hs-boot:27:22:
+    RnFail055.m1 is exported by the hs-boot file, but not exported by the module
+
+RnFail055.hs-boot:28:7:
+    Class `C2' has conflicting definitions in the module and its hs-boot file
+    Main module: class C2 a b
+                     RecFlag Recursive
+                     m2 :: a -> b m2' :: a -> b
+    Boot file:   class C2 a b
+                     RecFlag NonRecursive
+                     m2 :: a -> b
+
+RnFail055.hs-boot:29:24:
+    Class `C3' has conflicting definitions in the module and its hs-boot file
+    Main module: class (Eq a, Ord a) => C3 a RecFlag Recursive
+    Boot file:   class (Ord a, Eq a) => C3 a RecFlag NonRecursive
-- 
GitLab


From abd5bada38011648173afcceaf93409b0684fdc5 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 30 Jan 2013 08:26:33 +0000
Subject: [PATCH 073/223] Improve test

---
 tests/typecheck/should_fail/T7609.hs     | 3 +++
 tests/typecheck/should_fail/T7609.stderr | 5 +++++
 2 files changed, 8 insertions(+)

diff --git a/tests/typecheck/should_fail/T7609.hs b/tests/typecheck/should_fail/T7609.hs
index 242fa94a9..9e9ebe1a5 100644
--- a/tests/typecheck/should_fail/T7609.hs
+++ b/tests/typecheck/should_fail/T7609.hs
@@ -6,3 +6,6 @@ data X a b
 
 f :: (a `X` a, Maybe)
 f = undefined
+
+g :: (a `X` a) => Maybe
+g = undefined
\ No newline at end of file
diff --git a/tests/typecheck/should_fail/T7609.stderr b/tests/typecheck/should_fail/T7609.stderr
index d3430db3e..1431bcb7c 100644
--- a/tests/typecheck/should_fail/T7609.stderr
+++ b/tests/typecheck/should_fail/T7609.stderr
@@ -4,3 +4,8 @@ T7609.hs:7:16:
     The second argument of a tuple should have kind `*',
       but `Maybe' has kind `* -> *'
     In the type signature for `f': f :: (a `X` a, Maybe)
+
+T7609.hs:10:19:
+    Expecting one more argument to `Maybe'
+    Expected a type, but `Maybe' has kind `* -> *'
+    In the type signature for `g': g :: a `X` a => Maybe
-- 
GitLab


From 6d60454bba3578e286c29854b25970e535bb2a07 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 30 Jan 2013 08:29:15 +0000
Subject: [PATCH 074/223] Test Trac #7282

---
 tests/indexed-types/should_compile/T7282.hs | 9 +++++++++
 tests/indexed-types/should_compile/all.T    | 1 +
 2 files changed, 10 insertions(+)
 create mode 100644 tests/indexed-types/should_compile/T7282.hs

diff --git a/tests/indexed-types/should_compile/T7282.hs b/tests/indexed-types/should_compile/T7282.hs
new file mode 100644
index 000000000..a357d1764
--- /dev/null
+++ b/tests/indexed-types/should_compile/T7282.hs
@@ -0,0 +1,9 @@
+ {-# OPTIONS -XTypeFamilies -XDataKinds -XPolyKinds #-}
+
+module T7282 where
+
+class Foo (xs :: [k]) where
+     type Bar xs :: *
+
+instance Foo '[] where
+     type Bar '[] = Int
diff --git a/tests/indexed-types/should_compile/all.T b/tests/indexed-types/should_compile/all.T
index b8edf95d4..019c5aca4 100644
--- a/tests/indexed-types/should_compile/all.T
+++ b/tests/indexed-types/should_compile/all.T
@@ -207,4 +207,5 @@ test('T7280', normal, compile, [''])
 test('T7474', normal, compile, [''])
 test('T7489', normal, compile, [''])
 test('T7585', normal, compile, [''])
+test('T7282', normal, compile, [''])
 
-- 
GitLab


From 26beb302008c4aa9cc3a216afabf5ed00c3787ef Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 30 Jan 2013 08:32:40 +0000
Subject: [PATCH 075/223] Test Trac #7601

---
 tests/polykinds/T7601.hs | 12 ++++++++++++
 tests/polykinds/all.T    |  1 +
 2 files changed, 13 insertions(+)
 create mode 100644 tests/polykinds/T7601.hs

diff --git a/tests/polykinds/T7601.hs b/tests/polykinds/T7601.hs
new file mode 100644
index 000000000..f2325abc7
--- /dev/null
+++ b/tests/polykinds/T7601.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE PolyKinds              #-}
+{-# LANGUAGE TypeFamilies           #-}
+
+module T7601 where
+
+import GHC.Exts
+
+class C (a :: k) where
+   type F (a :: k)
+
+class Category (c :: k -> k -> *) where
+   type Ob c :: k -> Constraint
\ No newline at end of file
diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T
index 575c43eb3..d492a54ca 100644
--- a/tests/polykinds/all.T
+++ b/tests/polykinds/all.T
@@ -84,3 +84,4 @@ test('T7502', normal, compile,[''])
 test('T7488', normal, compile,[''])
 test('T7594', normal, compile_fail,[''])
 test('T7524', normal, compile_fail,[''])
+test('T7601', normal, compile,[''])
-- 
GitLab


From 21c308157ce83674ba6785d766f5223c6ba819ef Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 30 Jan 2013 10:03:39 +0000
Subject: [PATCH 076/223] Error messsage wibbles

---
 tests/simplCore/should_compile/T3717.stderr   |  8 ++--
 tests/simplCore/should_compile/T4908.stderr   |  4 +-
 tests/simplCore/should_compile/T7360.stderr   |  2 +-
 .../should_compile/spec-inline.stderr         |  2 +-
 tests/typecheck/should_compile/holes.hs       |  4 +-
 tests/typecheck/should_compile/holes.stderr   | 20 +++++-----
 tests/typecheck/should_compile/holes2.hs      |  4 +-
 tests/typecheck/should_compile/holes2.stderr  | 38 +++++++++----------
 tests/typecheck/should_compile/holes3.hs      | 10 ++---
 tests/typecheck/should_compile/holes3.stderr  | 36 +++++++++---------
 10 files changed, 61 insertions(+), 67 deletions(-)

diff --git a/tests/simplCore/should_compile/T3717.stderr b/tests/simplCore/should_compile/T3717.stderr
index d66812280..445e2b819 100644
--- a/tests/simplCore/should_compile/T3717.stderr
+++ b/tests/simplCore/should_compile/T3717.stderr
@@ -22,13 +22,13 @@ T3717.foo [InlPrag=INLINE[0]] :: GHC.Types.Int -> GHC.Types.Int
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
          Tmpl= \ (w [Occ=Once!] :: GHC.Types.Int) ->
-                 case w of _ { GHC.Types.I# ww [Occ=Once] ->
-                 case T3717.$wfoo ww of ww1 { __DEFAULT -> GHC.Types.I# ww1 }
+                 case w of _ { GHC.Types.I# ww1 [Occ=Once] ->
+                 case T3717.$wfoo ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 }
                  }}]
 T3717.foo =
   \ (w :: GHC.Types.Int) ->
-    case w of _ { GHC.Types.I# ww ->
-    case T3717.$wfoo ww of ww1 { __DEFAULT -> GHC.Types.I# ww1 }
+    case w of _ { GHC.Types.I# ww1 ->
+    case T3717.$wfoo ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 }
     }
 
 
diff --git a/tests/simplCore/should_compile/T4908.stderr b/tests/simplCore/should_compile/T4908.stderr
index 8f6952b2c..9af872363 100644
--- a/tests/simplCore/should_compile/T4908.stderr
+++ b/tests/simplCore/should_compile/T4908.stderr
@@ -58,10 +58,10 @@ T4908.f [InlPrag=INLINE[0]]
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
          Tmpl= \ (w [Occ=Once!] :: GHC.Types.Int)
                  (w1 [Occ=Once] :: (GHC.Types.Int, GHC.Types.Int)) ->
-                 case w of _ { GHC.Types.I# ww [Occ=Once] -> T4908.$wf ww w1 }}]
+                 case w of _ { GHC.Types.I# ww1 [Occ=Once] -> T4908.$wf ww1 w1 }}]
 T4908.f =
   \ (w :: GHC.Types.Int) (w1 :: (GHC.Types.Int, GHC.Types.Int)) ->
-    case w of _ { GHC.Types.I# ww -> T4908.$wf ww w1 }
+    case w of _ { GHC.Types.I# ww1 -> T4908.$wf ww1 w1 }
 
 
 ------ Local rules for imported ids --------
diff --git a/tests/simplCore/should_compile/T7360.stderr b/tests/simplCore/should_compile/T7360.stderr
index f8d0e9179..d48570395 100644
--- a/tests/simplCore/should_compile/T7360.stderr
+++ b/tests/simplCore/should_compile/T7360.stderr
@@ -6,7 +6,7 @@ T7360.$WFoo3 [InlPrag=INLINE] :: GHC.Types.Int -> T7360.Foo
 [GblId[DataConWrapper],
  Arity=1,
  Caf=NoCafRefs,
- Str=DmdType <S,U>,
+ Str=DmdType <S,U>m3,
  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=False,boring_ok=False)
diff --git a/tests/simplCore/should_compile/spec-inline.stderr b/tests/simplCore/should_compile/spec-inline.stderr
index 0d7172dd6..d3fa84e9e 100644
--- a/tests/simplCore/should_compile/spec-inline.stderr
+++ b/tests/simplCore/should_compile/spec-inline.stderr
@@ -116,7 +116,7 @@ Roman.foo2 = GHC.Types.I# 6
 Roman.foo1 :: Data.Maybe.Maybe GHC.Types.Int
 [GblId,
  Caf=NoCafRefs,
- Str=DmdType,
+ Str=DmdType m2,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=IF_ARGS [] 10 20}]
diff --git a/tests/typecheck/should_compile/holes.hs b/tests/typecheck/should_compile/holes.hs
index fa5a892aa..eee68bcfd 100644
--- a/tests/typecheck/should_compile/holes.hs
+++ b/tests/typecheck/should_compile/holes.hs
@@ -1,8 +1,6 @@
 {-# LANGUAGE TypeHoles #-}
 
-module Main where
-
-main = return ()
+module Holes where
 
 f = _
 
diff --git a/tests/typecheck/should_compile/holes.stderr b/tests/typecheck/should_compile/holes.stderr
index 626230fbf..b04bb8f8e 100644
--- a/tests/typecheck/should_compile/holes.stderr
+++ b/tests/typecheck/should_compile/holes.stderr
@@ -1,25 +1,25 @@
 
-holes.hs:7:5: Warning:
-    Found hole `_' with type t
+holes.hs:5:5: Warning:
+    Found hole `_' with type: t
     Where: `t' is a rigid type variable bound by
-               the inferred type of f :: t at holes.hs:7:1
-    Relevant bindings include f :: t (bound at holes.hs:7:1)
+               the inferred type of f :: t at holes.hs:5:1
+    Relevant bindings include f :: t (bound at holes.hs:5:1)
     In the expression: _
     In an equation for `f': f = _
 
-holes.hs:10:7: Warning:
-    Found hole `_' with type Char
+holes.hs:8:7: Warning:
+    Found hole `_' with type: Char
     In the expression: _
     In an equation for `g': g x = _
 
-holes.hs:12:5: Warning:
-    Found hole `_' with type [Char]
+holes.hs:10:5: Warning:
+    Found hole `_' with type: [Char]
     In the first argument of `(++)', namely `_'
     In the expression: _ ++ "a"
     In an equation for `h': h = _ ++ "a"
 
-holes.hs:15:15: Warning:
-    Found hole `_' with type b0
+holes.hs:13:15: Warning:
+    Found hole `_' with type: b0
     Where: `b0' is an ambiguous type variable
     In the second argument of `const', namely `_'
     In the expression: const y _
diff --git a/tests/typecheck/should_compile/holes2.hs b/tests/typecheck/should_compile/holes2.hs
index 56614c7ec..7b909d94b 100644
--- a/tests/typecheck/should_compile/holes2.hs
+++ b/tests/typecheck/should_compile/holes2.hs
@@ -1,7 +1,5 @@
 {-# LANGUAGE TypeHoles #-}
 
-module Main where
-
-main = return ()
+module Holes2 where
 
 f = show _
diff --git a/tests/typecheck/should_compile/holes2.stderr b/tests/typecheck/should_compile/holes2.stderr
index 13604264e..9945d288f 100644
--- a/tests/typecheck/should_compile/holes2.stderr
+++ b/tests/typecheck/should_compile/holes2.stderr
@@ -1,19 +1,19 @@
-
-holes2.hs:7:5: Warning:
-    No instance for (Show a0) arising from a use of `show'
-    The type variable `a0' is ambiguous
-    Note: there are several potential instances:
-      instance Show Double -- Defined in `GHC.Float'
-      instance Show Float -- Defined in `GHC.Float'
-      instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
-      ...plus 23 others
-    In the expression: show _
-    In an equation for `f': f = show _
-
-holes2.hs:7:10: Warning:
-    Found hole `_' with type a0
-    Where: `a0' is an ambiguous type variable
-    In the first argument of `show', namely `_'
-    In the expression: show _
-    In an equation for `f': f = show _
+
+holes2.hs:5:5: Warning:
+    No instance for (Show a0) arising from a use of `show'
+    The type variable `a0' is ambiguous
+    Note: there are several potential instances:
+      instance Show Double -- Defined in `GHC.Float'
+      instance Show Float -- Defined in `GHC.Float'
+      instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
+        -- Defined in `GHC.Real'
+      ...plus 23 others
+    In the expression: show _
+    In an equation for `f': f = show _
+
+holes2.hs:5:10: Warning:
+    Found hole `_' with type: a0
+    Where: `a0' is an ambiguous type variable
+    In the first argument of `show', namely `_'
+    In the expression: show _
+    In an equation for `f': f = show _
diff --git a/tests/typecheck/should_compile/holes3.hs b/tests/typecheck/should_compile/holes3.hs
index fa5a892aa..802133b64 100644
--- a/tests/typecheck/should_compile/holes3.hs
+++ b/tests/typecheck/should_compile/holes3.hs
@@ -1,15 +1,13 @@
 {-# LANGUAGE TypeHoles #-}
 
-module Main where
-
-main = return ()
+module Holes3 where
 
 f = _
 
 g :: Int -> Char
-g x = _
+g x = _gr
 
-h = _ ++ "a"
+h = _aa ++ "a"
 
 z :: [a] -> [a]
-z y = const y _
+z y = const y _x
diff --git a/tests/typecheck/should_compile/holes3.stderr b/tests/typecheck/should_compile/holes3.stderr
index 3bdba50f7..87c80fe30 100644
--- a/tests/typecheck/should_compile/holes3.stderr
+++ b/tests/typecheck/should_compile/holes3.stderr
@@ -1,26 +1,26 @@
 
-holes3.hs:7:5:
-    Found hole `_' with type t
+holes3.hs:5:5:
+    Found hole `_' with type: t
     Where: `t' is a rigid type variable bound by
-               the inferred type of f :: t at holes3.hs:7:1
-    Relevant bindings include f :: t (bound at holes3.hs:7:1)
+               the inferred type of f :: t at holes3.hs:5:1
+    Relevant bindings include f :: t (bound at holes3.hs:5:1)
     In the expression: _
     In an equation for `f': f = _
 
-holes3.hs:10:7:
-    Found hole `_' with type Char
-    In the expression: _
-    In an equation for `g': g x = _
+holes3.hs:8:7:
+    Found hole `_gr' with type: Char
+    In the expression: _gr
+    In an equation for `g': g x = _gr
 
-holes3.hs:12:5:
-    Found hole `_' with type [Char]
-    In the first argument of `(++)', namely `_'
-    In the expression: _ ++ "a"
-    In an equation for `h': h = _ ++ "a"
+holes3.hs:10:5:
+    Found hole `_aa' with type: [Char]
+    In the first argument of `(++)', namely `_aa'
+    In the expression: _aa ++ "a"
+    In an equation for `h': h = _aa ++ "a"
 
-holes3.hs:15:15:
-    Found hole `_' with type b0
+holes3.hs:13:15:
+    Found hole `_x' with type: b0
     Where: `b0' is an ambiguous type variable
-    In the second argument of `const', namely `_'
-    In the expression: const y _
-    In an equation for `z': z y = const y _
+    In the second argument of `const', namely `_x'
+    In the expression: const y _x
+    In an equation for `z': z y = const y _x
-- 
GitLab


From cf16aa686760d2a4170c9a5033257668f802f02c Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 1 Feb 2013 15:26:06 +0000
Subject: [PATCH 077/223] Add a test for #984

---
 tests/parser/should_fail/T984.hs     | 9 +++++++++
 tests/parser/should_fail/T984.stderr | 4 ++++
 tests/parser/should_fail/all.T       | 1 +
 3 files changed, 14 insertions(+)
 create mode 100644 tests/parser/should_fail/T984.hs
 create mode 100644 tests/parser/should_fail/T984.stderr

diff --git a/tests/parser/should_fail/T984.hs b/tests/parser/should_fail/T984.hs
new file mode 100644
index 000000000..ba2e282d5
--- /dev/null
+++ b/tests/parser/should_fail/T984.hs
@@ -0,0 +1,9 @@
+
+module T984 where
+
+f _ = do
+        x <- computation
+        case () of
+                _ ->
+                        result <- computation
+                        case () of () -> undefined
diff --git a/tests/parser/should_fail/T984.stderr b/tests/parser/should_fail/T984.stderr
new file mode 100644
index 000000000..4c723a786
--- /dev/null
+++ b/tests/parser/should_fail/T984.stderr
@@ -0,0 +1,4 @@
+
+T984.hs:6:9:
+    Parse error in pattern: case () of { _ -> result }
+    Possibly caused by a missing 'do'?
diff --git a/tests/parser/should_fail/all.T b/tests/parser/should_fail/all.T
index 355961dd4..114524aff 100644
--- a/tests/parser/should_fail/all.T
+++ b/tests/parser/should_fail/all.T
@@ -76,3 +76,4 @@ test('ParserNoLambdaCase', if_compiler_lt('ghc', '7.5', skip), compile_fail, [''
 test('ParserNoMultiWayIf', if_compiler_lt('ghc', '7.5', skip), compile_fail, [''])
 
 test('T5425', normal, compile_fail, [''])
+test('T984', normal, compile_fail, [''])
-- 
GitLab


From 889ba83ac636c39e57d59ced699f602c2eb490a7 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 1 Feb 2013 15:34:09 +0000
Subject: [PATCH 078/223] Accept output for readFail007

---
 tests/parser/should_fail/readFail007.stderr | 4 +++-
 1 file changed, 3 insertions(+), 1 deletion(-)

diff --git a/tests/parser/should_fail/readFail007.stderr b/tests/parser/should_fail/readFail007.stderr
index 3236824a7..bd6d92ed5 100644
--- a/tests/parser/should_fail/readFail007.stderr
+++ b/tests/parser/should_fail/readFail007.stderr
@@ -1,2 +1,4 @@
 
-readFail007.hs:6:4: Parse error in pattern: 2 + 2
+readFail007.hs:6:4:
+    Parse error in pattern: 2 + 2
+    Possibly caused by a missing 'do'?
-- 
GitLab


From 96f71821f88d190d88798904fdc1fe2150b8eaf9 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 1 Feb 2013 18:15:40 +0000
Subject: [PATCH 079/223] Add a test for #2222

---
 tests/th/T2222.hs     | 36 ++++++++++++++++++++++++++++++++++++
 tests/th/T2222.stderr |  5 +++++
 tests/th/all.T        |  1 +
 3 files changed, 42 insertions(+)
 create mode 100644 tests/th/T2222.hs
 create mode 100644 tests/th/T2222.stderr

diff --git a/tests/th/T2222.hs b/tests/th/T2222.hs
new file mode 100644
index 000000000..9a97c0d4d
--- /dev/null
+++ b/tests/th/T2222.hs
@@ -0,0 +1,36 @@
+
+{-# LANGUAGE TemplateHaskell #-}
+module ReifyPlusTypeInferenceBugs where
+
+import Language.Haskell.TH
+import System.IO
+
+a = 1
+
+b = $(do VarI _ t _ _ <- reify 'a
+         runIO $ putStrLn ("inside b: " ++ pprint t)
+         [| undefined |]) 
+
+c = $([| True |])
+
+d = $(do VarI _ t _ _ <- reify 'c
+         runIO $ putStrLn ("inside d: " ++ pprint t)
+         [| undefined |] )
+
+$(do VarI _ t _ _ <- reify 'c
+     runIO $ putStrLn ("type of c: " ++ pprint t)
+     return [] )
+
+e = $([| True |])
+
+f = $(do VarI _ t _ _ <- reify 'e
+         runIO $ putStrLn ("inside f: " ++ pprint t)
+         [| undefined |] )
+
+$(do VarI _ t _ _ <- reify 'e
+     runIO $ putStrLn ("type of e: " ++ pprint t)
+     return [] )
+
+$( runIO $ do hFlush stdout
+              hFlush stderr
+              return [] )
diff --git a/tests/th/T2222.stderr b/tests/th/T2222.stderr
new file mode 100644
index 000000000..7d90eb3e9
--- /dev/null
+++ b/tests/th/T2222.stderr
@@ -0,0 +1,5 @@
+inside d: t_0
+inside b: a_0
+type of c: GHC.Types.Bool
+inside f: GHC.Types.Bool
+type of e: GHC.Types.Bool
diff --git a/tests/th/all.T b/tests/th/all.T
index 21464d2bb..9eedda7a3 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -267,3 +267,4 @@ test('T7532',
      extra_clean(['T7532a.hi', 'T7532a.o']),
      multimod_compile,
      ['T7532', '-v0'])
+test('T2222', normal, compile, ['-v0'])
-- 
GitLab


From c525c266cdf56200b6d8e29b08b35cda8a2c44e4 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 1 Feb 2013 20:41:37 +0000
Subject: [PATCH 080/223] T5113 is failing again

---
 tests/perf/should_run/all.T | 4 +---
 1 file changed, 1 insertion(+), 3 deletions(-)

diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index b201bb1b1..9d1c0adcd 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -120,9 +120,7 @@ test('T5113',
           stats_num_field('bytes allocated', 8000000,
                                              9000000)),
       only_ways(['normal']),
-      normal
-      # WAS: expect_broken(7046)
-      # but it started working again around 01/2013, see #7046
+      expect_broken(7046)
       ],
      compile_and_run,
      ['-O'])
-- 
GitLab


From 97ff37de2bc40994b21a4c4011f587b0973d3090 Mon Sep 17 00:00:00 2001
From: Gabor Greif <ggreif@gmail.com>
Date: Fri, 1 Feb 2013 14:52:06 +0100
Subject: [PATCH 081/223] spelling

---
 tests/codeGen/should_run/cgrun055.hs                            | 2 +-
 tests/gadt/gadt-escape1.hs                                      | 2 +-
 .../should_compile_noflag_haddock/haddockSimplUtilsBug.hs       | 2 +-
 tests/simplCore/should_run/simplrun004.hs                       | 2 +-
 tests/typecheck/should_compile/tc167.hs                         | 2 +-
 tests/typecheck/should_fail/tcfail032.hs                        | 2 +-
 tests/typecheck/should_fail/tcfail132.hs                        | 2 +-
 tests/typecheck/should_fail/tcfail181.hs                        | 2 +-
 8 files changed, 8 insertions(+), 8 deletions(-)

diff --git a/tests/codeGen/should_run/cgrun055.hs b/tests/codeGen/should_run/cgrun055.hs
index 737632748..f824e1b9f 100644
--- a/tests/codeGen/should_run/cgrun055.hs
+++ b/tests/codeGen/should_run/cgrun055.hs
@@ -1,4 +1,4 @@
--- This program broke GHC 6.3, becuase dataToTag was called with
+-- This program broke GHC 6.3, because dataToTag was called with
 -- an unevaluated argument
 
 module Main where
diff --git a/tests/gadt/gadt-escape1.hs b/tests/gadt/gadt-escape1.hs
index d90d6a951..05579f9f0 100644
--- a/tests/gadt/gadt-escape1.hs
+++ b/tests/gadt/gadt-escape1.hs
@@ -10,7 +10,7 @@ data Hidden = forall t . Hidden (ExpGADT t) (ExpGADT t)
 hval = Hidden (ExpInt 0) (ExpInt 1)
 
 -- With the type sig this is ok, but without it maybe
--- should be rejected becuase the result type is wobbly
+-- should be rejected because the result type is wobbly
 --    weird1 :: ExpGADT Int
 --
 -- And indeed it is rejected by GHC 7.8 because OutsideIn
diff --git a/tests/haddock/should_compile_noflag_haddock/haddockSimplUtilsBug.hs b/tests/haddock/should_compile_noflag_haddock/haddockSimplUtilsBug.hs
index a62020f50..2f5e9ca68 100644
--- a/tests/haddock/should_compile_noflag_haddock/haddockSimplUtilsBug.hs
+++ b/tests/haddock/should_compile_noflag_haddock/haddockSimplUtilsBug.hs
@@ -4,7 +4,7 @@ postInlineUnconditionally
   = case Just "Hey" of
 	-- The point of examining occ_info here is that for *non-values* 
 	-- that occur outside a lambda, the call-site inliner won't have
-	-- a chance (becuase it doesn't know that the thing
+	-- a chance (because it doesn't know that the thing
 	-- only occurs once).   The pre-inliner won't have gotten
 	-- it either, if the thing occurs in more than one branch
 	-- So the main target is things like
diff --git a/tests/simplCore/should_run/simplrun004.hs b/tests/simplCore/should_run/simplrun004.hs
index 16e7566ee..e76274f97 100644
--- a/tests/simplCore/should_run/simplrun004.hs
+++ b/tests/simplCore/should_run/simplrun004.hs
@@ -23,7 +23,7 @@ sucW = gen_sucW (\ g x -> map (+x) [fst g..snd g]) f (11,500000)
 
 main = print (sum $ sucW 11,sum $ sucW 12)
 
--- Becuase this version uses a case expression, the bug 
+-- Because this version uses a case expression, the bug 
 -- doesn't happen and execution is much faster
 gen_sucC grow c g = case c g of 
            check -> \ x -> grow g x >>= \ y -> do guard $ check y; return y
diff --git a/tests/typecheck/should_compile/tc167.hs b/tests/typecheck/should_compile/tc167.hs
index b31776383..cadb1a7fb 100644
--- a/tests/typecheck/should_compile/tc167.hs
+++ b/tests/typecheck/should_compile/tc167.hs
@@ -17,7 +17,7 @@ f x = x
 -- You might think that (->) should have type (? -> ? -> *), and you'd be right
 -- But if we do that we get kind errors when saying
 --	instance Control.Arrow (->)
--- becuase the expected kind is (*->*->*).  The trouble is that the
+-- because the expected kind is (*->*->*).  The trouble is that the
 -- expected/actual stuff in the unifier does not go contra-variant, whereas
 -- the kind sub-typing does.  Sigh.  It really only matters if you use (->) in
 -- a prefix way, thus:  (->) Int# Int#.  And this is unusual.
diff --git a/tests/typecheck/should_fail/tcfail032.hs b/tests/typecheck/should_fail/tcfail032.hs
index 595006465..8c6bdd46c 100644
--- a/tests/typecheck/should_fail/tcfail032.hs
+++ b/tests/typecheck/should_fail/tcfail032.hs
@@ -6,7 +6,7 @@
 
 It *is* an error, because x does not have the polytype 
 	forall a. Eq a => a -> Int
-becuase it is monomorphic, but the error message isn't very illuminating.
+because it is monomorphic, but the error message isn't very illuminating.
 -}
 
 module ShouldFail where
diff --git a/tests/typecheck/should_fail/tcfail132.hs b/tests/typecheck/should_fail/tcfail132.hs
index cc933dc6e..dd8d644ab 100644
--- a/tests/typecheck/should_fail/tcfail132.hs
+++ b/tests/typecheck/should_fail/tcfail132.hs
@@ -4,7 +4,7 @@
 --    Kind error: Expecting kind `k_a1JA -> k_a1JE -> k_a1JI -> *',
 --	          but `DUnit t' has kind `k_a1JA -> k_a1JE -> *'
 --
--- as we couldn't tidy kinds, becuase they didn't have OccNames.
+-- as we couldn't tidy kinds, because they didn't have OccNames.
 -- This test recalls the bad error message.
 
 module ShouldFail where
diff --git a/tests/typecheck/should_fail/tcfail181.hs b/tests/typecheck/should_fail/tcfail181.hs
index 01d06599e..ca96a2c07 100644
--- a/tests/typecheck/should_fail/tcfail181.hs
+++ b/tests/typecheck/should_fail/tcfail181.hs
@@ -4,7 +4,7 @@
 --	     (Monad GHC.Prim.Any1, Monad m) =>
 --	     t -> Something (m Bool) e
 --
--- The stupid 'GHC.Prim.Any1' arose becuase of type ambiguity
+-- The stupid 'GHC.Prim.Any1' arose because of type ambiguity
 -- which should be reported, and wasn't.
 
 module ShouldFail where
-- 
GitLab


From f062d930392a56ad2482b4472d0e64787f6c073b Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 2 Feb 2013 16:34:53 +0000
Subject: [PATCH 082/223] Add a test for #1849

---
 tests/th/T1849.script | 10 ++++++++++
 tests/th/T1849.stdout |  6 ++++++
 tests/th/all.T        |  1 +
 3 files changed, 17 insertions(+)
 create mode 100644 tests/th/T1849.script
 create mode 100644 tests/th/T1849.stdout

diff --git a/tests/th/T1849.script b/tests/th/T1849.script
new file mode 100644
index 000000000..861b8d43d
--- /dev/null
+++ b/tests/th/T1849.script
@@ -0,0 +1,10 @@
+:set -XTemplateHaskell
+import Language.Haskell.TH
+let seeType n = do VarI _ t _ _ <- reify n; runIO $ putStrLn $ show t; [| return True |]
+let f = undefined :: Int -> Int
+let g = undefined :: [Int]
+let h = undefined :: (Int, Int)
+$(seeType (mkName "f"))
+$(seeType (mkName "g"))
+$(seeType (mkName "h"))
+
diff --git a/tests/th/T1849.stdout b/tests/th/T1849.stdout
new file mode 100644
index 000000000..3d48e778a
--- /dev/null
+++ b/tests/th/T1849.stdout
@@ -0,0 +1,6 @@
+AppT (AppT ArrowT (ConT GHC.Types.Int)) (ConT GHC.Types.Int)
+True
+AppT ListT (ConT GHC.Types.Int)
+True
+AppT (AppT (TupleT 2) (ConT GHC.Types.Int)) (ConT GHC.Types.Int)
+True
diff --git a/tests/th/all.T b/tests/th/all.T
index 9eedda7a3..2d190dd5c 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -268,3 +268,4 @@ test('T7532',
      multimod_compile,
      ['T7532', '-v0'])
 test('T2222', normal, compile, ['-v0'])
+test('T1849', normal, ghci_script, ['T1849.script'])
-- 
GitLab


From 816fbcd235dda239fec9df9f053fcb04ded74d43 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 2 Feb 2013 19:04:18 +0000
Subject: [PATCH 083/223] When the testsuite is ^Ced, print the summary anyway

---
 driver/runtests.py |  4 ++++
 driver/testlib.py  | 15 ++++++++++++++-
 2 files changed, 18 insertions(+), 1 deletion(-)

diff --git a/driver/runtests.py b/driver/runtests.py
index 66e3bf4d5..f6581db8b 100644
--- a/driver/runtests.py
+++ b/driver/runtests.py
@@ -261,6 +261,8 @@ for file in t_files:
 if config.use_threads:
     t.running_threads=0
 for oneTest in parallelTests:
+    if stopping():
+        break
     oneTest()
 if config.use_threads:
     t.thread_pool.acquire()
@@ -269,6 +271,8 @@ if config.use_threads:
     t.thread_pool.release()
 config.use_threads = False
 for oneTest in aloneTests:
+    if stopping():
+        break
     oneTest()
         
 summary(t, sys.stdout)
diff --git a/driver/testlib.py b/driver/testlib.py
index 40ecf86d6..9f1f75964 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -32,6 +32,14 @@ if config.use_threads:
     import threading
     import thread
 
+global wantToStop
+wantToStop = False
+def stopNow():
+    global wantToStop
+    wantToStop = True
+def stopping():
+    return wantToStop
+
 # Options valid for all the tests in the current "directory".  After
 # each test, we reset the options to these.  To change the options for
 # multiple tests, the function setTestOpts() below can be used to alter
@@ -726,6 +734,8 @@ def test_common_work (name, opts, func, args):
         if not config.clean_only:
             # Run the required tests...
             for way in do_ways:
+                if stopping():
+                    break
                 do_test (name, way, func, args)
 
             for way in all_ways:
@@ -888,7 +898,7 @@ def do_test(name, way, func, args):
         else:
             framework_fail(name, way, 'bad result ' + passFail)
     except KeyboardInterrupt:
-        raise
+        stopNow()
     except:
         framework_fail(name, way, 'do_test exception')
         traceback.print_exc()
@@ -2249,6 +2259,9 @@ def summary(t, file):
     if config.check_files_written:
         checkForFilesWrittenProblems(file)
 
+    if stopping():
+        file.write('WARNING: Testsuite run was terminated early\n')
+
 def printPassingTestInfosSummary(file, testInfos):
     directories = testInfos.keys()
     directories.sort()
-- 
GitLab


From 1121e3e673417d7b64444336e17556893c28f650 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 2 Feb 2013 19:53:46 +0000
Subject: [PATCH 084/223] Handle ^C better when threads are being used too

---
 driver/testlib.py  | 20 ++++++++---
 timeout/timeout.py | 85 +++++++++++++++++++++++++---------------------
 2 files changed, 61 insertions(+), 44 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 9f1f75964..54bae8369 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -1871,6 +1871,15 @@ def rawSystem(cmd_and_args):
     else:
         return os.spawnv(os.P_WAIT, cmd_and_args[0], cmd_and_args)
 
+# Note that this doesn't handle the timeout itself; it is just used for
+# commands that have timeout handling built-in.
+def rawSystemWithTimeout(cmd_and_args):
+    r = rawSystem(cmd_and_args)
+    if r == 98:
+        # The python timeout program uses 98 to signal that ^C was pressed
+        stopNow()
+    return r
+
 # cmd is a complex command in Bourne-shell syntax
 # e.g (cd . && 'c:/users/simonpj/darcs/HEAD/compiler/stage1/ghc-inplace' ...etc)
 # Hence it must ultimately be run by a Bourne shell
@@ -1890,7 +1899,7 @@ def runCmd( cmd ):
         assert config.timeout_prog!=''
 
     if config.timeout_prog != '':
-        r = rawSystem([config.timeout_prog, str(config.timeout), cmd])
+        r = rawSystemWithTimeout([config.timeout_prog, str(config.timeout), cmd])
     else:
         r = os.system(cmd)
     return r << 8
@@ -1906,13 +1915,14 @@ def runCmdFor( name, cmd, timeout_multiplier=1.0 ):
     if config.timeout_prog != '':
         if config.check_files_written:
             fn = name + ".strace"
-            r = rawSystem(["strace", "-o", fn, "-fF", "-e", "creat,open,chdir,clone,vfork",
-                           config.timeout_prog, str(timeout),
-                           cmd])
+            r = rawSystemWithTimeout(
+                    ["strace", "-o", fn, "-fF",
+                               "-e", "creat,open,chdir,clone,vfork",
+                     config.timeout_prog, str(timeout), cmd])
             addTestFilesWritten(name, fn)
             rm_no_fail(fn)
         else:
-            r = rawSystem([config.timeout_prog, str(timeout), cmd])
+            r = rawSystemWithTimeout([config.timeout_prog, str(timeout), cmd])
     else:
         r = os.system(cmd)
     return r << 8
diff --git a/timeout/timeout.py b/timeout/timeout.py
index 76660a739..6a57ac2f8 100644
--- a/timeout/timeout.py
+++ b/timeout/timeout.py
@@ -1,46 +1,53 @@
 #!/usr/bin/env python
 
-import errno
-import os
-import signal
-import sys
-import time
+try:
 
-secs = int(sys.argv[1])
-cmd = sys.argv[2]
+    import errno
+    import os
+    import signal
+    import sys
+    import time
 
-def killProcess(pid):
-    os.killpg(pid, signal.SIGKILL)
-    for x in range(10):
-        try:
-            time.sleep(0.3)
-            r = os.waitpid(pid, os.WNOHANG)
-            if r == (0, 0):
-                os.killpg(pid, signal.SIGKILL)
-            else:
-                return
-        except OSError, e:
-            if e.errno == errno.ECHILD:
-                return
-            else:
-                raise e
+    secs = int(sys.argv[1])
+    cmd = sys.argv[2]
 
-pid = os.fork()
-if pid == 0:
-    # child
-    os.setpgrp()
-    os.execvp('/bin/sh', ['/bin/sh', '-c', cmd])
-else:
-    # parent
-    def handler(signum, frame):
-        sys.stderr.write('Timeout happened...killing process...\n')
-        killProcess(pid)
-        sys.exit(99)
-    old = signal.signal(signal.SIGALRM, handler)
-    signal.alarm(secs)
-    (pid2, res) = os.waitpid(pid, 0)
-    if (os.WIFEXITED(res)):
-        sys.exit(os.WEXITSTATUS(res))
+    def killProcess(pid):
+        os.killpg(pid, signal.SIGKILL)
+        for x in range(10):
+            try:
+                time.sleep(0.3)
+                r = os.waitpid(pid, os.WNOHANG)
+                if r == (0, 0):
+                    os.killpg(pid, signal.SIGKILL)
+                else:
+                    return
+            except OSError, e:
+                if e.errno == errno.ECHILD:
+                    return
+                else:
+                    raise e
+
+    pid = os.fork()
+    if pid == 0:
+        # child
+        os.setpgrp()
+        os.execvp('/bin/sh', ['/bin/sh', '-c', cmd])
     else:
-        sys.exit(res)
+        # parent
+        def handler(signum, frame):
+            sys.stderr.write('Timeout happened...killing process...\n')
+            killProcess(pid)
+            sys.exit(99)
+        old = signal.signal(signal.SIGALRM, handler)
+        signal.alarm(secs)
+        (pid2, res) = os.waitpid(pid, 0)
+        if (os.WIFEXITED(res)):
+            sys.exit(os.WEXITSTATUS(res))
+        else:
+            sys.exit(res)
+
+except KeyboardInterrupt:
+    sys.exit(98)
+except:
+    raise
 
-- 
GitLab


From aefd2d98db99a38dcd09b5106b6428abdc879556 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Sun, 3 Feb 2013 16:21:43 +0000
Subject: [PATCH 085/223] Fix shared001

---
 tests/driver/Makefile | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/tests/driver/Makefile b/tests/driver/Makefile
index bd24b2e88..5152061f2 100644
--- a/tests/driver/Makefile
+++ b/tests/driver/Makefile
@@ -17,6 +17,7 @@ OBJSUFFIX = .o
 # -fforce-recomp makes lots of driver tests trivially pass, so we
 # filter it out from $(TEST_HC_OPTS).
 TEST_HC_OPTS_NO_RECOMP = $(filter-out -fforce-recomp,$(TEST_HC_OPTS))
+TEST_HC_OPTS_NO_RECOMP_NO_RTSOPTS = $(filter-out -rtsopts,$(TEST_HC_OPTS_NO_RECOMP))
 
 # -----------------------------------------------------------------------------
 # One-shot compilations, non-hierarchical modules
@@ -435,7 +436,7 @@ mode001:
 # Test for building DLLs with ghc -shared, see #2745
 shared001:
 	$(RM) Shared001.hi Shared001.o HSdll.dll.a HSdll.dll Shared001_stub.*
-	"$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) -v0 -shared Shared001.hs
+	"$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP_NO_RTSOPTS) -v0 -shared Shared001.hs
 
 # -----------------------------------------------------------------------------
 
-- 
GitLab


From fdd8f9d73f4c4e93e0ae3f53ac2b61000b9d3e0e Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 3 Feb 2013 18:41:55 +0000
Subject: [PATCH 086/223] Use a proper executable (rather than a shell script)
 in T6106

Fixes the test on Windows
---
 tests/ghci/scripts/Makefile         |  5 +++++
 tests/ghci/scripts/T6106.script     |  2 +-
 tests/ghci/scripts/T6106_preproc.hs | 17 +++++++++++++++++
 tests/ghci/scripts/T6106_preproc.sh |  7 -------
 tests/ghci/scripts/all.T            |  8 +++++++-
 5 files changed, 30 insertions(+), 9 deletions(-)
 create mode 100644 tests/ghci/scripts/T6106_preproc.hs
 delete mode 100755 tests/ghci/scripts/T6106_preproc.sh

diff --git a/tests/ghci/scripts/Makefile b/tests/ghci/scripts/Makefile
index 1fe702567..73f62036d 100644
--- a/tests/ghci/scripts/Makefile
+++ b/tests/ghci/scripts/Makefile
@@ -34,3 +34,8 @@ ghci037:
 
 ghci056_setup:
 	'$(TEST_HC)' $(TEST_HC_OPTS) -c ghci056_c.c
+
+.PHONY: T6106_prep
+T6106_prep:
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 --make T6106_preproc
+
diff --git a/tests/ghci/scripts/T6106.script b/tests/ghci/scripts/T6106.script
index 1b071ec60..be6de4636 100644
--- a/tests/ghci/scripts/T6106.script
+++ b/tests/ghci/scripts/T6106.script
@@ -3,7 +3,7 @@
 :l
 
 :shell rm -f T6106.hs
-:shell echo "{-# OPTIONS_GHC -F -pgmF ./T6106_preproc.sh #-}" >T6106.hs
+:shell echo "{-# OPTIONS_GHC -F -pgmF ./T6106_preproc #-}" >T6106.hs
 :shell echo "module T6106 where" >>T6106.hs
 :load T6106.hs
 -- second one should fail:
diff --git a/tests/ghci/scripts/T6106_preproc.hs b/tests/ghci/scripts/T6106_preproc.hs
new file mode 100644
index 000000000..fd2a55a64
--- /dev/null
+++ b/tests/ghci/scripts/T6106_preproc.hs
@@ -0,0 +1,17 @@
+
+import Control.Concurrent
+import Data.ByteString as BS
+import System.Environment
+
+main :: IO ()
+main = do args <- getArgs
+          case args of
+              [x, y, z] -> f x y z
+              _ -> error ("Bad args: " ++ show args)
+
+f :: String -> String -> String -> IO ()
+f x y z = do bs <- BS.readFile y
+             BS.writeFile z bs
+             threadDelay 1000000
+             Prelude.writeFile x "FAIL"
+
diff --git a/tests/ghci/scripts/T6106_preproc.sh b/tests/ghci/scripts/T6106_preproc.sh
deleted file mode 100755
index 56ca6082f..000000000
--- a/tests/ghci/scripts/T6106_preproc.sh
+++ /dev/null
@@ -1,7 +0,0 @@
-#!/bin/sh
-#
-# file T6106_preproc.sh
-#
-cat $2 > $3
-sleep 1
-echo "FAIL" >$1
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index 659a27566..b4dd4481c 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -128,7 +128,13 @@ test('T6027ghci', normal, ghci_script, ['T6027ghci.script'])
 
 test('T6007', normal, ghci_script, ['T6007.script'])
 test('T6091', normal, ghci_script, ['T6091.script'])
-test('T6106', extra_clean(['T6106.hs']), ghci_script, ['T6106.script'])
+test('T6106',
+     [extra_clean(['T6106.hs',
+                   'T6106_preproc.hi', 'T6106_preproc.o',
+                   'T6106_preproc', 'T6106_preproc.exe']),
+      pre_cmd('$MAKE -s --no-print-directory T6106_prep')],
+     ghci_script,
+     ['T6106.script'])
 test('T6105', normal, ghci_script, ['T6105.script'])
 test('T7117', normal, ghci_script, ['T7117.script'])
 test('ghci058',
-- 
GitLab


From e56d57b75d050583b05b63863fcb791939a90349 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 3 Feb 2013 19:25:54 +0000
Subject: [PATCH 087/223] Tidy up some tests

We now use pre_cmd rather than cmd_prefix wherever possible.
Also, pass "-s --no-print-directory" whenever we use pre_cmd.
---
 tests/annotations/should_run/all.T |  2 +-
 tests/concurrent/should_run/all.T  |  2 +-
 tests/ffi/should_run/all.T         | 12 ++++++------
 tests/ghci/scripts/all.T           |  2 +-
 tests/rts/all.T                    | 13 +++++++------
 5 files changed, 16 insertions(+), 15 deletions(-)

diff --git a/tests/annotations/should_run/all.T b/tests/annotations/should_run/all.T
index 22256b2f8..871b40916 100644
--- a/tests/annotations/should_run/all.T
+++ b/tests/annotations/should_run/all.T
@@ -10,7 +10,7 @@ test('annrun01',
      [extra_clean(['Annrun01_Help.hi', 'Annrun01_Help.o',
                     'annrun01.hi', 'annrun01.o',
                     'Config.hs', 'Config.hi', 'Config.o']),
-      pre_cmd('$MAKE -s config'),
+      pre_cmd('$MAKE -s --no-print-directory config'),
       omit_ways(['profasm','profthreaded', 'dyn'])],
       multimod_compile_and_run,
       ['annrun01', '-package ghc']
diff --git a/tests/concurrent/should_run/all.T b/tests/concurrent/should_run/all.T
index 356cdbc6b..ec867ed4d 100644
--- a/tests/concurrent/should_run/all.T
+++ b/tests/concurrent/should_run/all.T
@@ -204,7 +204,7 @@ test('conc058', only_compiler_types(['ghc']), compile_and_run, [''])
 test('conc059',
      [only_compiler_types(['ghc']),
       only_ways(['threaded1','threaded2']),
-      compile_cmd_prefix('$MAKE conc059_setup && '),
+      pre_cmd('$MAKE -s --no-print-directory conc059_setup'),
       extra_clean(['conc059_c.o'])],
      compile_and_run,
      ['conc059_c.c -no-hs-main'])
diff --git a/tests/ffi/should_run/all.T b/tests/ffi/should_run/all.T
index 772749265..1811f42af 100644
--- a/tests/ffi/should_run/all.T
+++ b/tests/ffi/should_run/all.T
@@ -13,7 +13,7 @@ test('fed001', compose(only_compiler_types(['ghc']),
 test('ffi001', omit_ways(['ghci']), compile_and_run, [''])
 test('ffi002', [ omit_ways(['ghci']),
                  extra_clean(['ffi002_c.o']),
-                 compile_cmd_prefix('$MAKE ffi002_setup && ') ],
+                 pre_cmd('$MAKE -s --no-print-directory ffi002_setup') ],
                  # The ffi002_setup hack is to ensure that we generate
                  # ffi002_stub.h before compiling ffi002_c.c, which
                  # needs it.
@@ -109,7 +109,7 @@ test('ffi018', [ omit_ways(['ghci']), extra_clean(['ffi018_c.o']) ],
                compile_and_run, ['ffi018_c.c'])
 
 test('ffi018_ghci', [ only_ways(['ghci']),
-                      cmd_prefix('$MAKE ffi018_ghci_setup && '),
+                      pre_cmd('$MAKE -s --no-print-directory ffi018_ghci_setup'),
                       extra_clean(['ffi018_ghci_c.o']) ],
                     compile_and_run, ['ffi018_ghci_c.o'])
 
@@ -122,7 +122,7 @@ test('T1288', [ omit_ways(['ghci']),
                 extra_clean(['T1288_c.o']) ],
               compile_and_run, ['T1288_c.c'])
 test('T1288_ghci', [ only_ways(['ghci']),
-                     cmd_prefix('$MAKE --no-print-directory T1288_ghci_setup && '),
+                     pre_cmd('$MAKE -s --no-print-directory T1288_ghci_setup'),
                      extra_clean(['T1288_ghci_c.o']) ],
                    compile_and_run, ['T1288_ghci_c.o'])
 
@@ -130,7 +130,7 @@ test('T2276', [ omit_ways(['ghci']),
                 extra_clean(['T2276_c.o']) ],
               compile_and_run, ['T2276_c.c'])
 test('T2276_ghci', [ only_ways(['ghci']),
-                     cmd_prefix('$MAKE --no-print-directory T2276_ghci_setup && '),
+                     pre_cmd('$MAKE -s --no-print-directory T2276_ghci_setup'),
                      extra_clean(['T2276_ghci_c.o']) ],
                    compile_and_run, ['-fobject-code T2276_ghci_c.o'])
 
@@ -177,12 +177,12 @@ test('T5402', [ omit_ways(['ghci']),
                   # The T5402_setup hack is to ensure that we generate
                   # T5402_stub.h before compiling T5402_main.c, which
                   # needs it.
-                compile_cmd_prefix('$MAKE --no-print-directory T5402_setup && ') ],
+                pre_cmd('$MAKE -s --no-print-directory T5402_setup') ],
               compile_and_run, ["-no-hs-main T5402_main.c"])
 
 test('T5594', [ omit_ways(['ghci']),
                 extra_clean(['T5594_c.o']),
-                compile_cmd_prefix('$MAKE --no-print-directory T5594_setup && ') ],
+                pre_cmd('$MAKE -s --no-print-directory T5594_setup') ],
                 # The T5594_setup hack is to ensure that we generate
                 # T5594_stub.h before compiling T5594_c.c, which
                 # needs it.
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index b4dd4481c..f204af76d 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -76,7 +76,7 @@ test('ghci055', combined_output, ghci_script, ['ghci055.script'])
 
 test('ghci056',
      [
-       cmd_prefix('$MAKE --no-print-directory ghci056_setup && '),
+       pre_cmd('$MAKE -s --no-print-directory ghci056_setup'),
        extra_run_opts('ghci056_c.o'),
        extra_clean('ghci056_c.o')
      ],
diff --git a/tests/rts/all.T b/tests/rts/all.T
index 50c6b3b00..00f9475f2 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -85,9 +85,9 @@ test('T2615',
        if_os('darwin', skip),
        # Solaris' linker does not support GNUish linker scripts
        if_os('solaris2', skip),
-       cmd_prefix('$MAKE T2615-prep && ' +
-                  # Add current directory to dlopen search path
-                  'LD_LIBRARY_PATH=$LD_LIBRARY_PATH:. '),
+       pre_cmd('$MAKE -s --no-print-directory T2615-prep'),
+       # Add current directory to dlopen search path
+       cmd_prefix('LD_LIBRARY_PATH=$LD_LIBRARY_PATH:. '),
        extra_clean(['libfoo_T2615.so', 'libfoo_T2615.o'])],
      compile_and_run,
      ['-package ghc'])
@@ -106,7 +106,8 @@ test('T4059',
 # Test for #4274
 test('exec_signals', [
      if_os('mingw32', skip),
-     cmd_prefix('$MAKE exec_signals-prep && ./exec_signals_prepare'),
+     pre_cmd('$MAKE -s --no-print-directory exec_signals-prep'),
+     cmd_prefix('./exec_signals_prepare'),
      extra_clean(['exec_signals_child', 'exec_signals_prepare'])
     ], compile_and_run, [''])
 
@@ -136,7 +137,7 @@ test('T5993', extra_run_opts('+RTS -k8 -RTS'), compile_and_run, [''])
 
 test('T6006', [ omit_ways(prof_ways + ['ghci']),
                  extra_clean(['T6006_c.o']),
-                 compile_cmd_prefix('$MAKE T6006_setup && ') ],
+                 pre_cmd('$MAKE -s --no-print-directory T6006_setup') ],
                  # The T6006_setup hack is to ensure that we generate
                  # T6006_stub.h before compiling T6006_c.c, which
                  # needs it.
@@ -154,7 +155,7 @@ test('T7040', [ extra_clean(['T7040_c.o']), omit_ways(['ghci']) ],
      compile_and_run, ['T7040_c.c'])
 
 test('T7040_ghci', [ only_ways(['ghci']),
-                      cmd_prefix('$MAKE T7040_ghci_setup && '),
+                      pre_cmd('$MAKE -s --no-print-directory T7040_ghci_setup'),
                       extra_clean(['T7040_ghci_c.o']) ],
                     compile_and_run, ['T7040_ghci_c.o'])
 
-- 
GitLab


From 649fe1d6825e4424ff529f516f900204c723a16a Mon Sep 17 00:00:00 2001
From: Austin Seipp <mad.one@gmail.com>
Date: Sun, 3 Feb 2013 21:22:51 -0600
Subject: [PATCH 088/223] Skip ghci/linking tests if we don't have ghci.

Otherwise, you get annoying failures if you run 'make fast stage=1'.

Signed-off-by: Austin Seipp <mad.one@gmail.com>
---
 tests/ghci/linking/all.T | 8 ++++++--
 1 file changed, 6 insertions(+), 2 deletions(-)

diff --git a/tests/ghci/linking/all.T b/tests/ghci/linking/all.T
index 39be389b5..bd87173c8 100644
--- a/tests/ghci/linking/all.T
+++ b/tests/ghci/linking/all.T
@@ -1,11 +1,12 @@
 test('ghcilink001',
      [if_ghci_dynamic(expect_fail), # dynamic ghci can't load '.a's
+      skip_if_no_ghci,
       extra_clean(['dir001/*','dir001'])],
      run_command,
      ['$MAKE -s --no-print-directory ghcilink001'])
 
 test('ghcilink002',
-     extra_clean(['dir002/*','dir002']),
+     [skip_if_no_ghci, extra_clean(['dir002/*','dir002'])],
      run_command,
      ['$MAKE -s --no-print-directory ghcilink002'])
 
@@ -13,6 +14,7 @@ test('ghcilink003',
      [
        if_os('mingw32', expect_broken(5289)), # still cannot load libstdc++
                                               # on Windows.  See also #4468.
+       skip_if_no_ghci,
        extra_clean(['dir003/*','dir003'])
      ],
      run_command,
@@ -20,12 +22,13 @@ test('ghcilink003',
 
 test('ghcilink004',
      [if_ghci_dynamic(expect_fail), # dynamic ghci can't load '.a's
+      skip_if_no_ghci,
       extra_clean(['dir004/*','dir004'])],
      run_command,
      ['$MAKE -s --no-print-directory ghcilink004'])
 
 test('ghcilink005',
-     extra_clean(['dir005/*','dir005']),
+     [skip_if_no_ghci, extra_clean(['dir005/*','dir005'])],
      run_command,
      ['$MAKE -s --no-print-directory ghcilink005'])
 
@@ -33,6 +36,7 @@ test('ghcilink006',
      [
        if_os('mingw32', expect_broken(5289)), # still cannot load libstdc++
                                               # on Windows.  See also #4468.
+       skip_if_no_ghci,
        extra_clean(['dir006/*','dir006'])
      ],
      run_command,
-- 
GitLab


From cb2592b63423d170ef6dadadf55ddf2baa486e1c Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Tue, 5 Feb 2013 19:53:20 +0000
Subject: [PATCH 089/223] Fix cabal01 on Windows

We were getting a
    Creating library file: dist\build\libHStest-1.0-ghc7.7.20130205.dll.a
message on stderr. We can't turn it off, so now the test just normalises
it away.
---
 driver/testlib.py         | 2 +-
 tests/cabal/cabal01/all.T | 5 ++++-
 2 files changed, 5 insertions(+), 2 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 54bae8369..476495d80 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -1625,7 +1625,7 @@ def check_stderr_ok( name ):
          return normalise_errmsg(str)
 
    return compare_outputs('stderr', \
-                          two_normalisers(norm, getTestOpts().extra_normaliser), \
+                          two_normalisers(norm, getTestOpts().extra_errmsg_normaliser), \
                           expected_stderr_file, actual_stderr_file)
 
 def dump_stderr( name ):
diff --git a/tests/cabal/cabal01/all.T b/tests/cabal/cabal01/all.T
index 2c64449c9..f8873230b 100644
--- a/tests/cabal/cabal01/all.T
+++ b/tests/cabal/cabal01/all.T
@@ -20,7 +20,10 @@ if default_testopts.cleanup != '':
 else:
    cleanup = ''
 
+def ignoreLdOutput(str):
+    return re.sub('Creating library file: dist.build.libHStest-1.0-ghc[0-9.]*.dll.a\n', '', str)
+
 test('cabal01',
-     normal,
+     normalise_errmsg_fun(ignoreLdOutput),
      run_command, 
      ['$MAKE -s --no-print-directory cabal01 VANILLA=' + vanilla + ' PROF=' + prof + ' DYN=' + dyn + ' ' + cleanup])
-- 
GitLab


From 1ebd16ee671792a741216b51c8f523e995b6269b Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Tue, 5 Feb 2013 20:08:05 +0000
Subject: [PATCH 090/223] dynamicToo001 is broken on Windows (#7665)

---
 tests/driver/dynamicToo/all.T | 1 +
 1 file changed, 1 insertion(+)

diff --git a/tests/driver/dynamicToo/all.T b/tests/driver/dynamicToo/all.T
index a03c314d9..b85ff318e 100644
--- a/tests/driver/dynamicToo/all.T
+++ b/tests/driver/dynamicToo/all.T
@@ -6,6 +6,7 @@ test('dynamicToo001',
                    'A001.dyn_o',  'B001.dyn_o',  'C001.dyn_o',
                    'A001.dyn_hi', 'B001.dyn_hi', 'C001.dyn_hi',
                    's001', 'd001']),
+      if_os('mingw32', expect_broken(7665)),
       unless_have_vanilla(skip),
       unless_have_dynamic(skip)],
      run_command,
-- 
GitLab


From fbe4e33539a8f13b3b4019971f5963fc70c66a6f Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Tue, 5 Feb 2013 20:17:58 +0000
Subject: [PATCH 091/223] Use normalise_errmsg_fun rather than normalise_fun
 where appropriate

---
 tests/cabal/all.T            | 6 +++---
 tests/safeHaskell/ghci/all.T | 6 +++---
 2 files changed, 6 insertions(+), 6 deletions(-)

diff --git a/tests/cabal/all.T b/tests/cabal/all.T
index 04e918d23..d05d05fe1 100644
--- a/tests/cabal/all.T
+++ b/tests/cabal/all.T
@@ -16,7 +16,7 @@ test('ghcpkg02',
 test('ghcpkg03',
      [extra_clean(['local03.package.conf',
                    'local03.package.conf.old']),
-      normalise_fun(normaliseDynlibNames)],
+      normalise_errmsg_fun(normaliseDynlibNames)],
      run_command,
      ['$MAKE -s --no-print-directory ghcpkg03'])
 test('ghcpkg04',
@@ -36,8 +36,8 @@ test('ghcpkg05',
                     'local05a.package.conf.old',
                     'local05b.package.conf',
                     'local05b.package.conf.old']),
-       normalise_fun(two_normalisers(normalise_haddock_junk,
-                                     normaliseDynlibNames))
+       normalise_errmsg_fun(two_normalisers(normalise_haddock_junk,
+                                            normaliseDynlibNames))
        ],
      run_command,
      ['$MAKE -s --no-print-directory ghcpkg05'])
diff --git a/tests/safeHaskell/ghci/all.T b/tests/safeHaskell/ghci/all.T
index 2a91b3310..2dca62efd 100644
--- a/tests/safeHaskell/ghci/all.T
+++ b/tests/safeHaskell/ghci/all.T
@@ -5,7 +5,7 @@ def normaliseBytestringPackage(str):
 
 test('p1', normal, ghci_script, ['p1.script'])
 test('p2', normal, ghci_script, ['p2.script'])
-test('p3', normalise_fun(normaliseBytestringPackage),
+test('p3', normalise_errmsg_fun(normaliseBytestringPackage),
            ghci_script, ['p3.script'])
 test('p4', normal, ghci_script, ['p4.script'])
 test('p5', normal, ghci_script, ['p5.script'])
@@ -15,13 +15,13 @@ test('p8', normal, ghci_script, ['p8.script'])
 test('p9', normal, ghci_script, ['p9.script'])
 test('p10', normal, ghci_script, ['p10.script'])
 test('p11', normal, ghci_script, ['p11.script'])
-test('p12', normalise_fun(normaliseBytestringPackage),
+test('p12', normalise_errmsg_fun(normaliseBytestringPackage),
             ghci_script, ['p12.script'])
 test('p13', normal, ghci_script, ['p13.script'])
 test('p14', normal, ghci_script, ['p14.script'])
 test('p15', normal, ghci_script, ['p15.script'])
 test('p16', normal, ghci_script, ['p16.script'])
-test('p17', normalise_fun(normaliseBytestringPackage),
+test('p17', normalise_errmsg_fun(normaliseBytestringPackage),
             ghci_script, ['p17.script'])
 # 7172
 test('p18', normalise_fun(normaliseBytestringPackage),
-- 
GitLab


From dde7816cde5112c685c11e563d40234a7ee07cda Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Tue, 5 Feb 2013 21:34:59 +0000
Subject: [PATCH 092/223] Fix T7037 on Win64

---
 tests/rts/Makefile     | 7 ++++++-
 tests/rts/T7037_main.c | 5 +----
 2 files changed, 7 insertions(+), 5 deletions(-)

diff --git a/tests/rts/Makefile b/tests/rts/Makefile
index 2eb952df2..5d663d126 100644
--- a/tests/rts/Makefile
+++ b/tests/rts/Makefile
@@ -48,11 +48,16 @@ T5423:
 T6006_setup :
 	'$(TEST_HC)' $(TEST_HC_OPTS) -c T6006.hs
 
+ifeq "$(TARGETPLATFORM)" "i386-unknown-mingw32"
+T7037_CONST = const
+else
+T7037_CONST =
+endif
 .PHONY: T7037
 T7037:
 	$(RM) 7037.o 7037.hi 7037$(exeext)
 	"$(TEST_HC)" $(TEST_HC_OPTS) T7037.hs -v0
-	"$(TEST_HC)" $(filter-out -rtsopts, $(TEST_HC_OPTS)) T7037_main.c -v0 -o T7037_main -no-hs-main
+	"$(TEST_HC)" -optc-DT7037_CONST=$(T7037_CONST) $(filter-out -rtsopts, $(TEST_HC_OPTS)) T7037_main.c -v0 -o T7037_main -no-hs-main
 	./T7037_main
 
 T7040_ghci_setup :
diff --git a/tests/rts/T7037_main.c b/tests/rts/T7037_main.c
index c19583465..ce7fa65b0 100644
--- a/tests/rts/T7037_main.c
+++ b/tests/rts/T7037_main.c
@@ -2,9 +2,6 @@
 #include <unistd.h>
 
 int main(int argc, char *argv[]) {
-#ifdef __MINGW32__
-    const
-#endif
-    char * args[2] = {"T7037", NULL};
+    T7037_CONST char * args[2] = {"T7037", NULL};
     execv("./T7037", args);
 }
-- 
GitLab


From 057f6541ee47069b04d8fb2198956256c30cea35 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Tue, 5 Feb 2013 21:56:27 +0000
Subject: [PATCH 093/223] Fix safePkg01 on Windows

---
 tests/safeHaskell/check/pkg01/all.T | 4 ++++
 1 file changed, 4 insertions(+)

diff --git a/tests/safeHaskell/check/pkg01/all.T b/tests/safeHaskell/check/pkg01/all.T
index 0f5f2024e..16f6ba6f7 100644
--- a/tests/safeHaskell/check/pkg01/all.T
+++ b/tests/safeHaskell/check/pkg01/all.T
@@ -8,6 +8,9 @@ def normaliseArrayPackage(str):
 def normaliseBytestringPackage(str):
     return re.sub('bytestring-[0-9]+(\.[0-9]+)*', 'bytestring-<VERSION>', str)
 
+def ignoreLdOutput(str):
+    return re.sub('Creating library file: pdb.safePkg01/dist.build.libHSsafePkg01-1.0-ghc[0-9.]*.dll.a\n', '', str)
+
 setTestOpts(f)
 
 if config.have_vanilla:
@@ -31,6 +34,7 @@ make_args = 'VANILLA=' + vanilla + ' PROF=' + prof + ' DYN=' + dyn
 # and can be changed correctly
 test('safePkg01',
      [clean_cmd('$MAKE -s --no-print-directory cleanPackageDatabase.safePkg01'),
+      normalise_errmsg_fun(ignoreLdOutput),
       normalise_fun(two_normalisers(normaliseArrayPackage,
                                     normaliseBytestringPackage))],
      run_command, 
-- 
GitLab


From 50b144a529f7c9a0f35fe343d4c99fa489917d13 Mon Sep 17 00:00:00 2001
From: Manuel M T Chakravarty <chak@cse.unsw.edu.au>
Date: Tue, 5 Feb 2013 10:32:10 +1100
Subject: [PATCH 094/223] dph/words: don't inline the vectorised exported
 functions

---
 tests/dph/words/WordsVect.hs | 2 ++
 1 file changed, 2 insertions(+)

diff --git a/tests/dph/words/WordsVect.hs b/tests/dph/words/WordsVect.hs
index ba4abc5d3..344442f3f 100644
--- a/tests/dph/words/WordsVect.hs
+++ b/tests/dph/words/WordsVect.hs
@@ -107,6 +107,7 @@ flattenState ss
 
 -- | Break up an array of chars into words then flatten it back.
 wordsOfPArray :: PArray Word8 -> PArray Word8
+{-# NOINLINE wordsOfPArray #-}
 wordsOfPArray arr
  = let	str	= fromPArrayP arr
 	state	= stateOfString str
@@ -116,6 +117,7 @@ wordsOfPArray arr
 
 -- | Count the number of words in an array
 wordCountOfPArray :: PArray Word8 -> Int
+{-# NOINLINE wordCountOfPArray #-}
 wordCountOfPArray arr
  = let	str	= fromPArrayP arr
 	state	= stateOfString str
-- 
GitLab


From be64fac97e278945c1cdd9a16761c21916d0ac2b Mon Sep 17 00:00:00 2001
From: Manuel M T Chakravarty <chak@cse.unsw.edu.au>
Date: Tue, 5 Feb 2013 17:55:47 +1100
Subject: [PATCH 095/223] dph: tests with dph-lifted-copy need to use
 '-fno-vectorisation-avoidance if scalar closures get too big

---
 tests/dph/nbody/dph-nbody.T         | 4 ++--
 tests/dph/quickhull/dph-quickhull.T | 4 ++--
 2 files changed, 4 insertions(+), 4 deletions(-)

diff --git a/tests/dph/nbody/dph-nbody.T b/tests/dph/nbody/dph-nbody.T
index 6d201606b..429ef8fa3 100644
--- a/tests/dph/nbody/dph-nbody.T
+++ b/tests/dph/nbody/dph-nbody.T
@@ -20,7 +20,7 @@ test    ('dph-nbody-copy-opt'
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
         , multimod_compile_and_run 
         , [ 'Main'
-          , '-Odph -fno-liberate-case -package dph-lifted-copy -package dph-prim-par'])
+          , '-Odph -fno-vectorisation-avoidance -fno-liberate-case -package dph-lifted-copy -package dph-prim-par'])
 
 
 test    ('dph-nbody-vseg-fast' 
@@ -40,4 +40,4 @@ test    ('dph-nbody-copy-fast'
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
         , multimod_compile_and_run 
         , [ 'Main'
-          , '-O0 -package dph-lifted-copy -package dph-prim-par'])
+          , '-O0 -fno-vectorisation-avoidance -package dph-lifted-copy -package dph-prim-par'])
diff --git a/tests/dph/quickhull/dph-quickhull.T b/tests/dph/quickhull/dph-quickhull.T
index bd1056535..14922821f 100644
--- a/tests/dph/quickhull/dph-quickhull.T
+++ b/tests/dph/quickhull/dph-quickhull.T
@@ -8,7 +8,7 @@ test    ('dph-quickhull-copy-opt'
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
         , multimod_compile_and_run 
         , [ 'Main'
-          , '-Odph -funfolding-use-threshold30 -package dph-lifted-copy -package dph-prim-par'])
+          , '-Odph -fno-vectorisation-avoidance -funfolding-use-threshold30 -package dph-lifted-copy -package dph-prim-par'])
 
 
 test    ('dph-quickhull-vseg-opt' 
@@ -30,7 +30,7 @@ test    ('dph-quickhull-copy-fast'
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
         , multimod_compile_and_run 
         , [ 'Main'
-          , '-O0 -package dph-lifted-copy -package dph-prim-par'])
+          , '-O0 -fno-vectorisation-avoidance -package dph-lifted-copy -package dph-prim-par'])
 
 
 test    ('dph-quickhull-vseg-fast' 
-- 
GitLab


From c9cb64544517dca88209093f2a197206c819a696 Mon Sep 17 00:00:00 2001
From: Manuel M T Chakravarty <chak@cse.unsw.edu.au>
Date: Tue, 5 Feb 2013 18:10:38 +1100
Subject: [PATCH 096/223] dph/classes: fails for the moment, but earlier
 success was spurious

---
 tests/dph/classes/dph-classes.T | 4 +++-
 1 file changed, 3 insertions(+), 1 deletion(-)

diff --git a/tests/dph/classes/dph-classes.T b/tests/dph/classes/dph-classes.T
index 29c520b9a..37c1dc480 100644
--- a/tests/dph/classes/dph-classes.T
+++ b/tests/dph/classes/dph-classes.T
@@ -1,8 +1,10 @@
 test    ('dph-classes-vseg-fast' 
+        , [ expect_fail
+        # , [ alone
         , [ extra_clean(['Main.o', 'Main.hi', 'DefsVect.hi', 'DefsVect.o'])
           , reqlib('dph-lifted-vseg')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
-        , multimod_compile_and_run 
+       , multimod_compile_and_run 
         , [ 'Main'
           , '-O -fno-enable-rewrite-rules -package dph-lifted-vseg'])
-- 
GitLab


From 6ed53a24b07ef68b82f7dbd96073da0eec6fc28f Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Wed, 6 Feb 2013 14:33:37 +0000
Subject: [PATCH 097/223] Fix framework failure

---
 tests/dph/classes/dph-classes.T | 5 ++---
 1 file changed, 2 insertions(+), 3 deletions(-)

diff --git a/tests/dph/classes/dph-classes.T b/tests/dph/classes/dph-classes.T
index 37c1dc480..aa10c831d 100644
--- a/tests/dph/classes/dph-classes.T
+++ b/tests/dph/classes/dph-classes.T
@@ -1,10 +1,9 @@
 test    ('dph-classes-vseg-fast' 
         , [ expect_fail
-        # , [ alone
-        , [ extra_clean(['Main.o', 'Main.hi', 'DefsVect.hi', 'DefsVect.o'])
+          , extra_clean(['Main.o', 'Main.hi', 'DefsVect.hi', 'DefsVect.o'])
           , reqlib('dph-lifted-vseg')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
-       , multimod_compile_and_run 
+        , multimod_compile_and_run 
         , [ 'Main'
           , '-O -fno-enable-rewrite-rules -package dph-lifted-vseg'])
-- 
GitLab


From 6f2f6794ecaf6961d589f88f4c428f76ad7f1c9a Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Wed, 6 Feb 2013 15:59:09 +0000
Subject: [PATCH 098/223] Eliminate *_num_field

We now use *_range_field everywhere instead
---
 driver/testlib.py            | 60 +++++-------------------
 tests/perf/compiler/all.T    | 45 +++++++-----------
 tests/perf/haddock/all.T     |  9 ++--
 tests/perf/should_run/all.T  | 89 ++++++++++++------------------------
 tests/perf/space_leaks/all.T | 12 ++---
 5 files changed, 66 insertions(+), 149 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 476495d80..0254b12fc 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -15,7 +15,7 @@ import traceback
 import copy
 import glob
 import types
-import math
+from math import ceil, trunc
 
 have_subprocess = False
 try:
@@ -260,24 +260,6 @@ def _extra_clean( opts, v ):
 
 # -----
 
-def stats_num_field( field, min, max ):
-    return lambda opts, f=field, x=min, y=max: _stats_num_field(opts, f, x, y);
-
-def _stats_num_field( opts, f, x, y ):
-    # copy the dictionary, as the config gets shared between all tests
-    opts.stats_num_fields = opts.stats_num_fields.copy()
-    opts.stats_num_fields[f] = (x, y)
-
-def compiler_stats_num_field( field, min, max ):
-    return lambda opts, f=field, x=min, y=max: _compiler_stats_num_field(opts, f, x, y);
-
-def _compiler_stats_num_field( opts, f, x, y ):
-    # copy the dictionary, as the config gets shared between all tests
-    opts.compiler_stats_num_fields = opts.compiler_stats_num_fields.copy()
-    opts.compiler_stats_num_fields[f] = (x, y)
-
-# -----
-
 def stats_range_field( field, min, max ):
     return lambda opts, f=field, x=min, y=max: _stats_range_field(opts, f, x, y);
 
@@ -1121,15 +1103,14 @@ def multi_compile_and_run( name, way, top_mod, extra_mods, extra_hc_opts ):
 
 def stats( name, way, stats_file ):
     opts = getTestOpts()
-    return checkStats(stats_file, opts.stats_range_fields
-                                , opts.stats_num_fields)
+    return checkStats(stats_file, opts.stats_range_fields)
 
 # -----------------------------------------------------------------------------
 # Check -t stats info
 
-def checkStats(stats_file, range_fields, num_fields):
+def checkStats(stats_file, range_fields):
     result = passed()
-    if len(num_fields) + len(range_fields) > 0:
+    if len(range_fields) > 0:
         f = open(in_testdir(stats_file))
         contents = f.read()
         f.close()
@@ -1141,8 +1122,8 @@ def checkStats(stats_file, range_fields, num_fields):
                 result = failBecause('no such stats field')
             val = int(m.group(1))
 
-            min = expected * ((100 - float(dev))/100);
-            max = expected * ((100 + float(dev))/100);
+            min = trunc(           expected * ((100 - float(dev))/100));
+            max = trunc(0.5 + ceil(expected * ((100 + float(dev))/100)));
 
             if val < min:
                 print field, val, 'is more than ' + repr(dev) + '%'
@@ -1154,23 +1135,6 @@ def checkStats(stats_file, range_fields, num_fields):
                 print field, val, 'is more than ' + repr(dev) + '% greater than the expected value,', expected, max
                 result = failBecause('stat not good enough')
 
-        # ToDo: remove all uses of this, and delete it
-        for (field, (min, max)) in num_fields.items():
-            m = re.search('\("' + field + '", "([0-9]+)"\)', contents)
-            if m == None:
-                print 'Failed to find field: ', field
-                result = failBecause('no such stats field')
-            val = int(m.group(1))
-
-            if val < min:
-                print field, val, 'is less than minimum allowed', min
-                print 'If this is because you have improved GHC, please'
-                print 'update the test so that GHC doesn\'t regress again'
-                result = failBecause('stat too good')
-            if val > max:
-                print field, val, 'is more than maximum allowed', max
-                result = failBecause('stat not good enough')
-
     return result
 
 # -----------------------------------------------------------------------------
@@ -1221,7 +1185,7 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf,
         to_do = '-c' # just compile
 
     stats_file = name + '.comp.stats'
-    if len(opts.compiler_stats_num_fields) + len(opts.compiler_stats_range_fields) > 0:
+    if len(opts.compiler_stats_range_fields) > 0:
         extra_hc_opts += ' +RTS -V0 -t' + stats_file + ' --machine-readable -RTS'
 
     # Required by GHC 7.3+, harmless for earlier versions:
@@ -1260,8 +1224,7 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf,
 
     # ToDo: if the sub-shell was killed by ^C, then exit
 
-    statsResult = checkStats(stats_file, opts.compiler_stats_range_fields
-                                       , opts.compiler_stats_num_fields)
+    statsResult = checkStats(stats_file, opts.compiler_stats_range_fields)
 
     if badResult(statsResult):
         return statsResult
@@ -1307,7 +1270,7 @@ def simple_run( name, way, prog, args ):
     my_rts_flags = rts_flags(way)
 
     stats_file = name + '.stats'
-    if len(opts.stats_num_fields) + len(opts.stats_range_fields) > 0:
+    if len(opts.stats_range_fields) > 0:
         args += ' +RTS -V0 -t' + stats_file + ' --machine-readable -RTS'
 
     if opts.no_stdin:
@@ -1361,8 +1324,7 @@ def simple_run( name, way, prog, args ):
         if check_prof and not check_prof_ok(name):
             return failBecause('bad profile')
 
-    return checkStats(stats_file, opts.stats_range_fields
-                                , opts.stats_num_fields)
+    return checkStats(stats_file, opts.stats_range_fields)
 
 def rts_flags(way):
     if (way == ''):
@@ -1910,7 +1872,7 @@ def runCmdFor( name, cmd, timeout_multiplier=1.0 ):
     if config.os == 'mingw32':
         # On MinGW, we will always have timeout
         assert config.timeout_prog!=''
-    timeout = int(math.ceil(config.timeout * timeout_multiplier))
+    timeout = int(ceil(config.timeout * timeout_multiplier))
 
     if config.timeout_prog != '':
         if config.check_files_written:
diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 09cdb0111..9242f8311 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -7,21 +7,18 @@ setTestOpts(no_lint)
 
 test('T1969',
      [if_wordsize(32,
-          compiler_stats_num_field('peak_megabytes_allocated', 13,
-                                                               19)),
+          compiler_stats_range_field('peak_megabytes_allocated', 18, 1)),
                              # expected value: 14 (x86/Windows 17/05/10)
                              #                 15 (x86/OS X)
                              #                 19 (x86/OS X)
       if_wordsize(64,
-          compiler_stats_num_field('peak_megabytes_allocated', 22,
-                                                               28)),
+          compiler_stats_range_field('peak_megabytes_allocated', 25, 1)),
                                              # expected value: 28 (amd64/Linux)
                                              # expected value: 34 (amd64/Linux)
                                              # 2012-09-20      23 (amd64/Linux)
                                              # 2012-10-03      25 (amd64/Linux if .hi exists)
       if_wordsize(32,
-          compiler_stats_num_field('max_bytes_used', 4000000,
-                                                     7000000)),
+          compiler_stats_range_field('max_bytes_used', 6149572, 5)),
                              # expected value: 6707308 (x86/OS X)
                              #                 5717704 (x86/Windows 17/05/10)
                              #                 6149572 (x86/Linux, 31/12/09)
@@ -81,10 +78,9 @@ else:
 
 test('T3294',
      [if_wordsize(32,
-          compiler_stats_num_field('max_bytes_used', 12000000,
-                                                     20000000)),
+          compiler_stats_range_field('max_bytes_used', 17725476, 5)),
                                    # expected value: 17725476 (x86/OS X)
-				   #                 14593500 (Windows)
+                                   #                 14593500 (Windows)
       if_wordsize(64,
           compiler_stats_range_field('max_bytes_used', 44894544, 15)),
                                    # prev:           25753192 (amd64/Linux)
@@ -122,7 +118,7 @@ test('T4801',
 
       # expected value: 58 (amd64/OS X):
       if_platform('x86_64-apple-darwin',
-          compiler_stats_num_field('peak_megabytes_allocated', 56, 60)),
+          compiler_stats_range_field('peak_megabytes_allocated', 58, 1)),
       # expected value: 228286660 (x86/OS X)
       if_wordsize(32,
           compiler_stats_range_field('bytes allocated', 185669232, 10)),
@@ -135,14 +131,12 @@ test('T4801',
 
       # expected value: 510938976 (amd64/OS X):
       if_platform('x86_64-apple-darwin',
-          compiler_stats_num_field('bytes allocated', 490000000,
-                                                      530000000)),
+          compiler_stats_range_field('bytes allocated', 510938976, 5)),
 
       if_wordsize(32,
+          compiler_stats_range_field('max_bytes_used', 9651948, 5)),
       #                    expected value: x86/OS X:  9651948
-          compiler_stats_num_field('max_bytes_used',  8000000,
-                                                     12000000)),
-      # expected value: 10290952 (windows)
+      #                    expected value:           10290952 (windows)
       if_wordsize(64,
           compiler_stats_range_field('max_bytes_used', 21657520, 15)),
                 # prev:       20486256 (amd64/OS X)
@@ -151,8 +145,7 @@ test('T4801',
                 # 19/10/2012: 18619912 (-fPIC turned off)
                 # 24/12/2012: 21657520 (perhaps gc sampling time wibbles?)
       if_platform('x86_64-apple-darwin',
-          compiler_stats_num_field('max_bytes_used', 20000000,
-                                                     23000000)),
+          compiler_stats_range_field('max_bytes_used', 21657520, 5)),
        only_ways(['normal']),
        extra_hc_opts('-static')
       ],
@@ -163,11 +156,11 @@ test('T3064',
      [# expect_broken( 3064 ),
       # expected value: 14 (x86/Linux 28-06-2012):
       if_wordsize(32,
-          compiler_stats_range_field('peak_megabytes_allocated', 14, 30)),
+          compiler_stats_range_field('peak_megabytes_allocated', 14, 1)),
 
-      # expected value: 18 (amd64/Linux):
       if_wordsize(64,
-          compiler_stats_num_field('peak_megabytes_allocated', 20, 28)),
+          compiler_stats_range_field('peak_megabytes_allocated', 24, 1)),
+                                    # expected value: 18 (amd64/Linux):
 
       # expected value: 56380288 (x86/Linux) (28/6/2011)
       #                 111189536 (x86/Windows) (30/10/12)
@@ -177,8 +170,7 @@ test('T3064',
 
       # expected value: 73259544 (amd64/Linux) (28/6/2011):
       if_wordsize(64,
-          compiler_stats_num_field('bytes allocated', 200000000,
-                                                      280000000)),
+          compiler_stats_range_field('bytes allocated', 240000000, 5)),
 
       # expected value: 2247016 (x86/Linux) (28/6/2011):
       if_wordsize(32,
@@ -186,8 +178,7 @@ test('T3064',
 
       # expected value: 4032024 (amd64/Linux, intree) (28/6/2011):
       if_wordsize(64,
-          compiler_stats_num_field('max_bytes_used', 8000000,
-                                                     14000000)),
+          compiler_stats_range_field('max_bytes_used', 11000000, 5)),
        only_ways(['normal'])
       ],
      compile,
@@ -221,8 +212,7 @@ test('T5631',
           compiler_stats_range_field('bytes allocated', 392904228, 10)),
       # expected value: 774,595,008 (amd64/Linux):
       if_wordsize(64,
-          compiler_stats_num_field('bytes allocated', 600000000,
-                                                      900000000)),
+          compiler_stats_range_field('bytes allocated', 774595008, 5)),
        only_ways(['normal'])
       ],
      compile,
@@ -234,8 +224,7 @@ test('parsing001',
           compiler_stats_range_field('bytes allocated', 274000576, 10)),
       # expected value: 587079016 (amd64/Linux):
       if_wordsize(64,
-          compiler_stats_num_field('bytes allocated', 540000000,
-                                                      620000000)),
+          compiler_stats_range_field('bytes allocated', 587079016, 5)),
        only_ways(['normal']),
       ],
      compile_fail, [''])
diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T
index 07942bd66..0a864a2b0 100644
--- a/tests/perf/haddock/all.T
+++ b/tests/perf/haddock/all.T
@@ -8,8 +8,7 @@ test('haddock.base',
                                         # 2012-11-12: 249 (amd64/Linux)
                                         # 2013-01-29: 274 (amd64/Linux)
      ,if_wordsize(32,
-          stats_num_field('peak_megabytes_allocated', 110,
-                                                      115))
+          stats_range_field('peak_megabytes_allocated', 113, 1))
                                         # 2012-08-14: 144 (x86/OSX)
                                         # 2012-10-30: 113 (x86/Windows)
      ,if_wordsize(64,
@@ -45,8 +44,7 @@ test('haddock.Cabal',
                              # 2012-09-20: 227 (amd64/Linux)
                              # 2012-10-08: 217 (amd64/Linux)
      ,if_wordsize(32,
-          stats_num_field('peak_megabytes_allocated', 80,
-                                                      85))
+          stats_range_field('peak_megabytes_allocated', 83, 1))
                                         # 2012-08-14: 116 (x86/OSX)
                                         # 2012-10-30: 83 (x86/Windows)
      ,if_wordsize(64,
@@ -81,8 +79,7 @@ test('haddock.compiler',
                                         # 2012-09-20: 1228 (amd64/Linux)
                                         # 2012-10-08: 1240 (amd64/Linux)
      ,if_wordsize(32,
-          stats_num_field('peak_megabytes_allocated', 600,
-                                                      610))
+          stats_range_field('peak_megabytes_allocated', 606, 1))
                                         # 2012-08-14: 631 (x86/OSX)
                                         # 2012-10-30: 606 (x86/Windows)
      ,if_wordsize(64,
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 9d1c0adcd..9e1da9c2c 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -4,11 +4,9 @@
 # because the test allocates an unboxed array of doubles.
 
 test('T3586',
-     [stats_num_field('peak_megabytes_allocated', 17,
-                                                  18),
+     [stats_range_field('peak_megabytes_allocated', 17, 1),
                                      # expected value: 17 (amd64/Linux)
-      stats_num_field('bytes allocated', 16000000,
-                                         17000000),
+      stats_range_field('bytes allocated', 16835544, 5),
                                      # expected value: 16835544 (amd64/Linux)
       only_ways(['normal'])
       ],
@@ -16,8 +14,7 @@ test('T3586',
      ['-O'])
 
 test('T4830',
-     [stats_num_field('bytes allocated', 60000,
-                                         200000),
+     [stats_range_field('bytes allocated', 127000, 5),
                                      # expected value: 127,000 (amd64/Linux)
       only_ways(['normal'])
       ],
@@ -30,11 +27,9 @@ test('T3245', normal, compile_and_run, ['-O'])
 # a bug in hGetBufNonBlocking in 6.13 that triggered this.
 #
 test('lazy-bs-alloc',
-     [stats_num_field('peak_megabytes_allocated', 1,
-                                                  3),
+     [stats_range_field('peak_megabytes_allocated', 2, 1),
                                      # expected value: 2 (amd64/Linux)
-      stats_num_field('bytes allocated', 400000,
-                                         600000),
+      stats_range_field('bytes allocated', 489776, 5),
                                      # expected value: 489776 (amd64/Linux)
       only_ways(['normal']),
       extra_run_opts('../../numeric/should_run/arith011.stdout'),
@@ -60,16 +55,13 @@ test('T3736',
      ['$MAKE -s --no-print-directory T3736'])
 test('T3738',
      [extra_clean(['T3738a.hi', 'T3738a.o']),
-      stats_num_field('peak_megabytes_allocated', 1,
-                                                  1),
+      stats_range_field('peak_megabytes_allocated', 1, 0),
                                      # expected value: 1 (amd64/Linux)
-      # expected value: 45648 (x86/Linux):
       if_wordsize(32,
-          stats_num_field('bytes allocated', 40000,
-                                             50000)),
+          stats_range_field('bytes allocated', 45648, 5)),
+                                     # expected value: 45648 (x86/Linux):
       if_wordsize(64,
-          stats_num_field('bytes allocated', 40000,
-                                             60000)),
+          stats_range_field('bytes allocated', 49400, 5)),
                                      # expected value: 49400 (amd64/Linux)
       only_ways(['normal'])
       ],
@@ -77,17 +69,14 @@ test('T3738',
      ['-O'])
 
 test('MethSharing',
-     [stats_num_field('peak_megabytes_allocated', 1,
-                                                  1),
+     [stats_range_field('peak_megabytes_allocated', 1, 0),
                                      # expected value: 1 (amd64/Linux)
       # expected value: 2685858140 (x86/OS X):
       if_wordsize(32,
-          stats_num_field('bytes allocated', 300000000,
-                                             400000000)),
+          stats_range_field('bytes allocated', 360940756, 5)),
                                   # expected: 360940756 (x86/Linux)
       if_wordsize(64,
-          stats_num_field('bytes allocated', 600000000,
-                                             700000000)),
+          stats_range_field('bytes allocated', 640067672, 5)),
                                   # expected: 640067672 (amd64/Linux)
       only_ways(['normal'])
       ],
@@ -114,11 +103,9 @@ test('T149',
 test('T5113',
      [
       if_wordsize(32,
-          stats_num_field('bytes allocated', 3000000,
-                                             5000000)),
+          stats_range_field('bytes allocated', 4000000, 5)),
       if_wordsize(64,
-          stats_num_field('bytes allocated', 8000000,
-                                             9000000)),
+          stats_range_field('bytes allocated', 8000000, 5)),
       only_ways(['normal']),
       expect_broken(7046)
       ],
@@ -128,11 +115,9 @@ test('T5113',
 
 test('T4978',
      [if_wordsize(32,
-          stats_num_field('bytes allocated',  9000000,
-                                             11000000)),
+          stats_range_field('bytes allocated', 10000000, 5)),
       if_wordsize(64,
-          stats_num_field('bytes allocated',  9000000,
-                                             11000000)),
+          stats_range_field('bytes allocated', 10137680, 5)),
                                      # expected value: 10137680 (amd64/Linux)
       only_ways(['normal'])
       ],
@@ -141,12 +126,10 @@ test('T4978',
 
 test('T5205',
      [if_wordsize(32,
-          stats_num_field('bytes allocated', 40000,
-                                             50000)),
+          stats_range_field('bytes allocated', 47088, 5)),
                            # expected value: 47088 (x86/Darwin)
       if_wordsize(64,
-          stats_num_field('bytes allocated', 40000,
-                                             60000)),
+          stats_range_field('bytes allocated', 51320, 5)),
                            # expected value: 51320 (amd64/Linux)
       only_ways(['normal', 'optasm'])
       ],
@@ -155,12 +138,10 @@ test('T5205',
 
 test('T5549',
      [if_wordsize(32,
-          stats_num_field('bytes allocated', 3000000000,
-                                             8000000000)),
+          stats_range_field('bytes allocated', 3362958676, 5)),
                            # expected value: 3362958676 (Windows)
       if_wordsize(64,
-          stats_num_field('bytes allocated', 5000000000,
-                                             8000000000)),
+          stats_range_field('bytes allocated', 6725846120, 5)),
                            # expected value: 6,725,846,120 (amd64/Linux)
       only_ways(['normal'])
       ],
@@ -169,12 +150,10 @@ test('T5549',
 
 test('T4474a',
      [if_wordsize(32,
-          stats_num_field('bytes allocated', 1600000000,
-                                             2000000000)),
+          stats_range_field('bytes allocated', 1879095912, 5)),
                            # expected value: 1879095912 (i386/OSX)
       if_wordsize(64,
-          stats_num_field('bytes allocated', 3500000000,
-                                             3900000000)),
+          stats_range_field('bytes allocated', 3766493912, 5)),
                            # expected value: 3766493912 (amd64/Linux)
       only_ways(['normal'])
       ],
@@ -182,12 +161,10 @@ test('T4474a',
      ['-O'])
 test('T4474b',
      [if_wordsize(32,
-          stats_num_field('bytes allocated', 1600000000,
-                                             2000000000)),
+          stats_range_field('bytes allocated', 1879095912, 5)),
                            # expected value: 1879095912 (i386/OSX)
       if_wordsize(64,
-          stats_num_field('bytes allocated', 3500000000,
-                                             3900000000)),
+          stats_range_field('bytes allocated', 3766493912, 5)),
                            # expected value: 3766493912 (amd64/Linux)
       only_ways(['normal'])
       ],
@@ -195,12 +172,10 @@ test('T4474b',
      ['-O'])
 test('T4474c',
      [if_wordsize(32,
-          stats_num_field('bytes allocated', 1600000000,
-                                             2000000000)),
+          stats_range_field('bytes allocated', 1879095912, 5)),
                            # expected value: 1879095912 (i386/OSX)
       if_wordsize(64,
-          stats_num_field('bytes allocated', 3500000000,
-                                             3900000000)),
+          stats_range_field('bytes allocated', 3766493912, 5)),
                            # expected value: 3766493912 (amd64/Linux)
       only_ways(['normal'])
       ],
@@ -209,12 +184,10 @@ test('T4474c',
 
 test('T5237',
      [if_wordsize(32,
-          stats_num_field('bytes allocated',  70000,
-                                              90000)),
+          stats_range_field('bytes allocated',  78328, 5)),
                            # expected value: 78328 (i386/Linux)
       if_wordsize(64,
-          stats_num_field('bytes allocated',  90000,
-                                             130000)),
+          stats_range_field('bytes allocated',  110888, 5)),
                            # expected value: 110888 (amd64/Linux)
      only_ways(['normal'])
      ],
@@ -223,8 +196,7 @@ test('T5237',
 
 test('T5536',
      [if_wordsize(32,
-          stats_num_field('bytes allocated', 1150000000,
-                                             1250000000)),
+          stats_range_field('bytes allocated', 1246287228, 5)),
                            # expected value: 1246287228 (i386/Linux)
       if_wordsize(64,
           stats_range_field('bytes allocated', 892399040, 5)),
@@ -272,8 +244,7 @@ test('T7507', omit_ways(['ghci']), compile_and_run, ['-O'])
 # For 7507, stack overflow is the bad case
 
 test('T7436',
-     [stats_num_field('max_bytes_used', 50000,
-                                         100000),
+     [stats_range_field('max_bytes_used', 70000, 5),
                                      # expected value: 127,000 (amd64/Linux)
       only_ways(['normal'])
       ],
diff --git a/tests/perf/space_leaks/all.T b/tests/perf/space_leaks/all.T
index 6dec9f099..23afe42d8 100644
--- a/tests/perf/space_leaks/all.T
+++ b/tests/perf/space_leaks/all.T
@@ -4,15 +4,13 @@ test('space_leak_001',
      # Now it's: 3 (amd64/Linux)
      #           4 (x86/OS X)
      #           5 (x86/Linux)
-     [stats_num_field('peak_megabytes_allocated', 3, 5),
-      stats_num_field('max_bytes_used', 400000,
-                                        500000),
+     [stats_range_field('peak_megabytes_allocated', 4, 1),
+      stats_range_field('max_bytes_used', 481456, 1),
                       # expected value: 440224 (amd64/Linux)
                       #                 417016 (x86/OS X)
                       #                 415672 (x86/Windows)
                       #                 481456 (unreg amd64/Linux)
-      stats_num_field('bytes allocated', 9050000000,
-                                         9100000000),
+      stats_range_field('bytes allocated', 9079316016, 1),
                            # expected value: 9079316016 (amd64/Linux)
                            #                 9331570416 (x86/Linux)
                            #                 9329073952 (x86/OS X)
@@ -25,7 +23,7 @@ test('space_leak_001',
 test('T4334',
      # Test for a space leak in Data.List.lines (fixed with #4334)
      [extra_run_opts('1000000 2 t'),
-      stats_num_field('peak_megabytes_allocated', 1, 3),
+      stats_range_field('peak_megabytes_allocated', 2, 0),
       # prof ways don't work well with +RTS -V0
       omit_ways(['profasm','profthreaded'])
       ],
@@ -34,7 +32,7 @@ test('T4334',
 test('T2762',
      [# peak_megabytes_allocated is 2 with 7.0.2.
       # Was 57 with 6.12.3.
-      stats_num_field('peak_megabytes_allocated', 1, 3),
+      stats_range_field('peak_megabytes_allocated', 2, 0),
       only_ways(['normal']),
       extra_clean(['T2762A.hi', 'T2762A.o'])],
      compile_and_run, ['-O'])
-- 
GitLab


From d83875fb76639dd704599fa4867e7ffbcdf5211e Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Wed, 6 Feb 2013 17:30:23 +0000
Subject: [PATCH 099/223] Make failing perf test output easier to read

---
 driver/testlib.py | 33 +++++++++++++++++++++++----------
 1 file changed, 23 insertions(+), 10 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 0254b12fc..846c401ea 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -1122,19 +1122,32 @@ def checkStats(stats_file, range_fields):
                 result = failBecause('no such stats field')
             val = int(m.group(1))
 
-            min = trunc(           expected * ((100 - float(dev))/100));
-            max = trunc(0.5 + ceil(expected * ((100 + float(dev))/100)));
-
-            if val < min:
-                print field, val, 'is more than ' + repr(dev) + '%'
-                print 'less than the exepected value', expected
-                print 'If this is because you have improved GHC, please'
-                print 'update the test so that GHC doesn\'t regress again'
+            lowerBound = trunc(           expected * ((100 - float(dev))/100));
+            upperBound = trunc(0.5 + ceil(expected * ((100 + float(dev))/100)));
+
+            if val < lowerBound:
+                print field, 'value is too low:'
+                print '(If this is because you have improved GHC, please'
+                print 'update the test so that GHC doesn\'t regress again)'
                 result = failBecause('stat too good')
-            if val > max:
-                print field, val, 'is more than ' + repr(dev) + '% greater than the expected value,', expected, max
+            if val > upperBound:
+                print field, 'value is too high:'
                 result = failBecause('stat not good enough')
 
+            if val < lowerBound or val > upperBound:
+                valStr = str(val)
+                valLen = len(valStr)
+                expectedStr = str(expected)
+                expectedLen = len(expectedStr)
+                length = max(map (lambda x : len(str(x)), [expected, lowerBound, upperBound, val]))
+                def display(descr, val, extra):
+                    valStr = str(val)
+                    print descr, (' ' * (length - len(valStr))) + valStr, extra
+                display('    Expected    ' + field + ':', expected, '+/-' + str(dev) + '%')
+                display('    Lower bound ' + field + ':', lowerBound, '')
+                display('    Upper bound ' + field + ':', upperBound, '')
+                display('    Actual      ' + field + ':', val, '')
+                
     return result
 
 # -----------------------------------------------------------------------------
-- 
GitLab


From c3e9cbb909a83db94421ce3efde3d5a231c7a9ae Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 02:02:53 +0000
Subject: [PATCH 100/223] Fix perf bounds on amd64/Linux following the change
 to *_range_field

---
 tests/perf/compiler/all.T    | 15 +++++++++------
 tests/perf/should_run/all.T  | 15 +++++++++------
 tests/perf/space_leaks/all.T | 10 +++++-----
 3 files changed, 23 insertions(+), 17 deletions(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 9242f8311..29e6ea9ef 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -159,8 +159,9 @@ test('T3064',
           compiler_stats_range_field('peak_megabytes_allocated', 14, 1)),
 
       if_wordsize(64,
-          compiler_stats_range_field('peak_megabytes_allocated', 24, 1)),
-                                    # expected value: 18 (amd64/Linux):
+          compiler_stats_range_field('peak_megabytes_allocated', 26, 1)),
+                                     # (amd64/Linux):            18
+                                     # (amd64/Linux) 2012-02-07: 26
 
       # expected value: 56380288 (x86/Linux) (28/6/2011)
       #                 111189536 (x86/Windows) (30/10/12)
@@ -168,17 +169,19 @@ test('T3064',
           compiler_stats_range_field('bytes allocated', 111189536, 10)),
 
 
-      # expected value: 73259544 (amd64/Linux) (28/6/2011):
       if_wordsize(64,
-          compiler_stats_range_field('bytes allocated', 240000000, 5)),
+          compiler_stats_range_field('bytes allocated', 224798696, 5)),
+                          # (amd64/Linux) (28/06/2011):  73259544
+                          # (amd64/Linux) (07/02/2013): 224798696
 
       # expected value: 2247016 (x86/Linux) (28/6/2011):
       if_wordsize(32,
           compiler_stats_range_field('max_bytes_used', 5511604, 20)),
 
-      # expected value: 4032024 (amd64/Linux, intree) (28/6/2011):
       if_wordsize(64,
-          compiler_stats_range_field('max_bytes_used', 11000000, 5)),
+          compiler_stats_range_field('max_bytes_used',  9819288, 5)),
+                 # (amd64/Linux, intree) (28/06/2011):  4032024
+                 # (amd64/Linux, intree) (07/02/2013):  9819288
        only_ways(['normal'])
       ],
      compile,
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 9e1da9c2c..ed7800300 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -14,8 +14,9 @@ test('T3586',
      ['-O'])
 
 test('T4830',
-     [stats_range_field('bytes allocated', 127000, 5),
-                                     # expected value: 127,000 (amd64/Linux)
+     [stats_range_field('bytes allocated',  99264, 1),
+               # (amd64/Linux):            127000
+               # (amd64/Linux) 2013-02-07:  99264
       only_ways(['normal'])
       ],
      compile_and_run,
@@ -29,8 +30,9 @@ test('T3245', normal, compile_and_run, ['-O'])
 test('lazy-bs-alloc',
      [stats_range_field('peak_megabytes_allocated', 2, 1),
                                      # expected value: 2 (amd64/Linux)
-      stats_range_field('bytes allocated', 489776, 5),
-                                     # expected value: 489776 (amd64/Linux)
+      stats_range_field('bytes allocated', 429744, 1),
+              # (amd64/Linux):             489776
+              # (amd64/Linux) 2013-02-07:  429744
       only_ways(['normal']),
       extra_run_opts('../../numeric/should_run/arith011.stdout'),
       ignore_output
@@ -244,8 +246,9 @@ test('T7507', omit_ways(['ghci']), compile_and_run, ['-O'])
 # For 7507, stack overflow is the bad case
 
 test('T7436',
-     [stats_range_field('max_bytes_used', 70000, 5),
-                                     # expected value: 127,000 (amd64/Linux)
+     [stats_range_field('max_bytes_used', 60360, 1),
+           # (amd64/Linux):              127000
+           # (amd64/Linux) 2013-02-07:    60360
       only_ways(['normal'])
       ],
      compile_and_run,
diff --git a/tests/perf/space_leaks/all.T b/tests/perf/space_leaks/all.T
index 23afe42d8..dcc1f0865 100644
--- a/tests/perf/space_leaks/all.T
+++ b/tests/perf/space_leaks/all.T
@@ -5,11 +5,11 @@ test('space_leak_001',
      #           4 (x86/OS X)
      #           5 (x86/Linux)
      [stats_range_field('peak_megabytes_allocated', 4, 1),
-      stats_range_field('max_bytes_used', 481456, 1),
-                      # expected value: 440224 (amd64/Linux)
-                      #                 417016 (x86/OS X)
-                      #                 415672 (x86/Windows)
-                      #                 481456 (unreg amd64/Linux)
+      stats_range_field('max_bytes_used', 440000, 10),
+                        # expected value: 440224 (amd64/Linux)
+                        #                 417016 (x86/OS X)
+                        #                 415672 (x86/Windows)
+                        #                 481456 (unreg amd64/Linux)
       stats_range_field('bytes allocated', 9079316016, 1),
                            # expected value: 9079316016 (amd64/Linux)
                            #                 9331570416 (x86/Linux)
-- 
GitLab


From bd6ded8586edc6aded611a4fc083b1af7cd2f729 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Thu, 7 Feb 2013 09:52:20 +0000
Subject: [PATCH 101/223] add test for #7636

---
 tests/rts/T7636.hs     | 13 +++++++++++++
 tests/rts/T7636.stderr |  1 +
 tests/rts/all.T        |  2 ++
 3 files changed, 16 insertions(+)
 create mode 100644 tests/rts/T7636.hs
 create mode 100644 tests/rts/T7636.stderr

diff --git a/tests/rts/T7636.hs b/tests/rts/T7636.hs
new file mode 100644
index 000000000..9e3dbd69d
--- /dev/null
+++ b/tests/rts/T7636.hs
@@ -0,0 +1,13 @@
+import GHC.Conc.Sync
+import System.Environment
+
+test n = atomically $ f [1..n]
+ where
+  f [] = retry
+  f (x:xs) = do
+    ys <- f xs
+    return (x:ys)
+
+main = do
+  [n] <- getArgs
+  test (read n)
diff --git a/tests/rts/T7636.stderr b/tests/rts/T7636.stderr
new file mode 100644
index 000000000..76984e3b7
--- /dev/null
+++ b/tests/rts/T7636.stderr
@@ -0,0 +1 @@
+T7636: thread blocked indefinitely in an STM transaction
diff --git a/tests/rts/all.T b/tests/rts/all.T
index 00f9475f2..2c0ae6180 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -162,3 +162,5 @@ test('T7040_ghci', [ only_ways(['ghci']),
 test('T7227', [ extra_run_opts('+RTS -tT7227.stat --machine-readable -RTS'),
                 extra_clean(['T7227.stat']) ]
             , compile_and_run, [''] )
+
+test('T7636', [ exit_code(1), extra_run_opts('100000') ], compile_and_run, [''] )
-- 
GitLab


From e13136461cc99fb02bfbc088a76c6a4acb7f3ba4 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 16:59:28 +0000
Subject: [PATCH 102/223] Add a TEST="..." line to testsuite output

This gives hte list of tests with unexpected results, so that you can
easily run them again.
---
 driver/testlib.py | 13 +++++++++++++
 1 file changed, 13 insertions(+)

diff --git a/driver/testlib.py b/driver/testlib.py
index 846c401ea..141b4320d 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -2211,6 +2211,7 @@ def findTFiles_(path):
 def summary(t, file):
 
     file.write('\n')
+    printUnexpectedTests(file, [t.unexpected_passes, t.unexpected_failures])
     file.write('OVERALL SUMMARY for test run started at ' \
                + t.start_time + '\n'\
                + string.rjust(`t.total_tests`, 8) \
@@ -2247,6 +2248,18 @@ def summary(t, file):
     if stopping():
         file.write('WARNING: Testsuite run was terminated early\n')
 
+def printUnexpectedTests(file, testInfoss):
+    unexpected = []
+    for testInfos in testInfoss:
+        directories = testInfos.keys()
+        for directory in directories:
+            tests = testInfos[directory].keys()
+            unexpected += tests
+    if unexpected != []:
+        file.write('Unexpected results from:\n')
+        file.write('TEST="' + ' '.join(unexpected) + '"\n')
+        file.write('\n')
+
 def printPassingTestInfosSummary(file, testInfos):
     directories = testInfos.keys()
     directories.sort()
-- 
GitLab


From cd178d3b61e8fa7a4cc79aaba391accdd46b8f14 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 17:01:46 +0000
Subject: [PATCH 103/223] Simplify driver code slightly

---
 driver/testlib.py | 3 +--
 1 file changed, 1 insertion(+), 2 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 141b4320d..88ff472ae 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -1141,8 +1141,7 @@ def checkStats(stats_file, range_fields):
                 expectedLen = len(expectedStr)
                 length = max(map (lambda x : len(str(x)), [expected, lowerBound, upperBound, val]))
                 def display(descr, val, extra):
-                    valStr = str(val)
-                    print descr, (' ' * (length - len(valStr))) + valStr, extra
+                    print descr, string.rjust(str(val), length), extra
                 display('    Expected    ' + field + ':', expected, '+/-' + str(dev) + '%')
                 display('    Lower bound ' + field + ':', lowerBound, '')
                 display('    Upper bound ' + field + ':', upperBound, '')
-- 
GitLab


From 9a907eda72fc6f0c61351fcf3ead663680e60015 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 18:12:41 +0000
Subject: [PATCH 104/223] Define 'when' and 'unless' helpers

This will reduce the number of helper functions that we need
---
 driver/testlib.py               | 22 ++++-----
 tests/codeGen/should_run/all.T  |  4 +-
 tests/llvm/should_compile/all.T |  2 +-
 tests/perf/compiler/all.T       | 80 ++++++++++++++++-----------------
 tests/perf/haddock/all.T        | 36 +++++++--------
 tests/perf/should_run/all.T     | 56 +++++++++++------------
 6 files changed, 100 insertions(+), 100 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 88ff472ae..4ce737279 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -290,6 +290,15 @@ def skip_if_fast(opts):
 
 # -----
 
+def when(b, f):
+    if b:
+        return f
+    else:
+        return normal
+
+def unless(b, f):
+    return when(not b, f)
+
 def if_platform( plat, f ):
     if config.platform == plat:
         return f
@@ -326,17 +335,8 @@ def unless_arch( arch, f ):
     else:
         return f
 
-def if_wordsize( ws, f ):
-    if config.wordsize == str(ws):
-        return f
-    else:
-        return normal
-
-def unless_wordsize( ws, f ):
-    if config.wordsize == str(ws):
-        return normal
-    else:
-        return f
+def wordsize( ws ):
+    return config.wordsize == str(ws)
 
 def if_unregisterised( f ):
     if config.unregisterised:
diff --git a/tests/codeGen/should_run/all.T b/tests/codeGen/should_run/all.T
index b12c30b8f..77224a2e1 100644
--- a/tests/codeGen/should_run/all.T
+++ b/tests/codeGen/should_run/all.T
@@ -100,8 +100,8 @@ test('T7319', [ extra_ways(['prof']), only_ways(['prof']), exit_code(1),
                 req_profiling,
                 extra_hc_opts('-fprof-auto'),
                 extra_run_opts('+RTS -xc') ], compile_and_run, [''])
-test('Word2Float32', unless_wordsize(32, skip), compile_and_run, [''])
-test('Word2Float64', unless_wordsize(64, skip), compile_and_run, [''])
+test('Word2Float32', unless(wordsize(32), skip), compile_and_run, [''])
+test('Word2Float64', unless(wordsize(64), skip), compile_and_run, [''])
 
 test('T7361', normal, compile_and_run, [''])
 test('T7600', normal, compile_and_run, [''])
diff --git a/tests/llvm/should_compile/all.T b/tests/llvm/should_compile/all.T
index 61d0f3f61..16a91e0ac 100644
--- a/tests/llvm/should_compile/all.T
+++ b/tests/llvm/should_compile/all.T
@@ -11,4 +11,4 @@ test('T5486', normal, compile, [''])
 test('T5681', normal, compile, [''])
 test('T6158', [reqlib('vector'), reqlib('primitive')], compile, ['-package vector -package primitive'])
 test('T7571', cmm_src, compile, [''])
-test('T7575', unless_wordsize(32, skip), compile, [''])
+test('T7575', unless(wordsize(32), skip), compile, [''])
diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 29e6ea9ef..24fb98c25 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -6,36 +6,36 @@ setTestOpts(no_lint)
 
 
 test('T1969',
-     [if_wordsize(32,
+     [when(wordsize(32),
           compiler_stats_range_field('peak_megabytes_allocated', 18, 1)),
                              # expected value: 14 (x86/Windows 17/05/10)
                              #                 15 (x86/OS X)
                              #                 19 (x86/OS X)
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('peak_megabytes_allocated', 25, 1)),
                                              # expected value: 28 (amd64/Linux)
                                              # expected value: 34 (amd64/Linux)
                                              # 2012-09-20      23 (amd64/Linux)
                                              # 2012-10-03      25 (amd64/Linux if .hi exists)
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('max_bytes_used', 6149572, 5)),
                              # expected value: 6707308 (x86/OS X)
                              #                 5717704 (x86/Windows 17/05/10)
                              #                 6149572 (x86/Linux, 31/12/09)
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('max_bytes_used', 9000000, 20)),
                                   # looks like the peak is around 10M, but we're
                                   # unlikely to GC exactly on the peak.
                                   # varies quite a lot with CLEANUP and BINDIST,
                                   # hence 10% range.
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('bytes allocated', 303930948, 5)),
                         # expected value: 215582916 (x86/Windows)
                         #                 221667908 (x86/OS X)
                         #                 274932264 (x86/Linux)
                         # 2012-10-08:     303930948 (x86/Linux, new codegen)
                         # 2012-10-29:     298921816 (x86/Windows; increased range to 5%
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 658786936, 5)),
                         # 17/11/2009:     434,845,560 (amd64/Linux)
                         # 08/12/2009:     459,776,680 (amd64/Linux)
@@ -77,23 +77,23 @@ else:
    conf_3294 = skip
 
 test('T3294',
-     [if_wordsize(32,
+     [when(wordsize(32),
           compiler_stats_range_field('max_bytes_used', 17725476, 5)),
                                    # expected value: 17725476 (x86/OS X)
                                    #                 14593500 (Windows)
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('max_bytes_used', 44894544, 15)),
                                    # prev:           25753192 (amd64/Linux)
                                    # 29/08/2012:     37724352 (amd64/Linux)
                                    #  (increase due to new codegen, see #7198)
                                    # 13/13/2012:     44894544 (amd64/Linux)
                                    #  (reason for increase unknown)
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('bytes allocated', 1373514844, 5)),
                                    # previous:     815479800  (x86/Linux)
                                    # (^ increase due to new codegen, see #7198)
                                    # 2012-10-08:   1373514844 (x86/Linux)
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 2717327208, 5)),
                                    # old:        1,357,587,088 (amd64/Linux)
                                    # 29/08/2012: 2,961,778,696 (amd64/Linux)
@@ -107,10 +107,10 @@ test('T3294',
 test('T4801',
      [ # expect_broken(5224),
        # temporarily unbroken (#5227)
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('peak_megabytes_allocated', 30, 20)),
 
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('peak_megabytes_allocated', 49, 20)),
                    # prev:       50 (amd64/Linux)
                    # 19/10/2012: 64 (amd64/Linux) (REASON UNKNOWN!)
@@ -120,10 +120,10 @@ test('T4801',
       if_platform('x86_64-apple-darwin',
           compiler_stats_range_field('peak_megabytes_allocated', 58, 1)),
       # expected value: 228286660 (x86/OS X)
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('bytes allocated', 185669232, 10)),
 
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 392409984, 10)),
                    # prev:       360243576 (amd64/Linux)
                    # 19/10/2012: 447190832 (amd64/Linux) (-fPIC turned on)
@@ -133,11 +133,11 @@ test('T4801',
       if_platform('x86_64-apple-darwin',
           compiler_stats_range_field('bytes allocated', 510938976, 5)),
 
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('max_bytes_used', 9651948, 5)),
       #                    expected value: x86/OS X:  9651948
       #                    expected value:           10290952 (windows)
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('max_bytes_used', 21657520, 15)),
                 # prev:       20486256 (amd64/OS X)
                 # 30/08/2012: 17305600--20391920 (varies a lot)
@@ -155,30 +155,30 @@ test('T4801',
 test('T3064',
      [# expect_broken( 3064 ),
       # expected value: 14 (x86/Linux 28-06-2012):
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('peak_megabytes_allocated', 14, 1)),
 
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('peak_megabytes_allocated', 26, 1)),
                                      # (amd64/Linux):            18
                                      # (amd64/Linux) 2012-02-07: 26
 
       # expected value: 56380288 (x86/Linux) (28/6/2011)
       #                 111189536 (x86/Windows) (30/10/12)
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('bytes allocated', 111189536, 10)),
 
 
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 224798696, 5)),
                           # (amd64/Linux) (28/06/2011):  73259544
                           # (amd64/Linux) (07/02/2013): 224798696
 
       # expected value: 2247016 (x86/Linux) (28/6/2011):
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('max_bytes_used', 5511604, 20)),
 
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('max_bytes_used',  9819288, 5)),
                  # (amd64/Linux, intree) (28/06/2011):  4032024
                  # (amd64/Linux, intree) (07/02/2013):  9819288
@@ -194,12 +194,12 @@ test('T4007',
 
 test('T5030',
      [
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('bytes allocated', 259547660, 10)),
                      # previous:    196457520
                      # 2012-10-08:  259547660 (x86/Linux, new codegen)
 
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 602993184, 10)),
             # Previously 530000000 (+/- 10%)
             # 17/1/13:       602,993,184  (x86_64/Linux)
@@ -211,10 +211,10 @@ test('T5030',
      ['-fcontext-stack=300'])
 
 test('T5631',
-     [if_wordsize(32, # sample from x86/Linux
+     [when(wordsize(32), # sample from x86/Linux
           compiler_stats_range_field('bytes allocated', 392904228, 10)),
       # expected value: 774,595,008 (amd64/Linux):
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 774595008, 5)),
        only_ways(['normal'])
       ],
@@ -223,10 +223,10 @@ test('T5631',
 
 test('parsing001',
      [# expected value: ?
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('bytes allocated', 274000576, 10)),
       # expected value: 587079016 (amd64/Linux):
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 587079016, 5)),
        only_ways(['normal']),
       ],
@@ -236,10 +236,10 @@ test('parsing001',
 test('T783',
      [ only_ways(['normal']),  # no optimisation for this one
       # expected value: 175,569,928 (x86/Linux)
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('bytes allocated', 226907420, 10)),
                            # 2012-10-08: 226907420 (x86/Linux)
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 640324528, 10)),
                            # prev:       349,263,216 (amd64/Linux)
                            # 07/08/2012: 384,479,856 (amd64/Linux)
@@ -254,12 +254,12 @@ test('T783',
 test('T5321Fun',
      [ only_ways(['normal']),  # no optimisation for this one
       # sample from x86/Linux
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('bytes allocated', 344416344, 10)),
                                          # prev:       300000000
                                          # 2012-10-08: 344416344
                                          #  (increase due to new codegen)
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 713385808, 10))
                                          # prev:       585,521,080
                                          # 29/08/2012: 713,385,808
@@ -269,12 +269,12 @@ test('T5321Fun',
 
 test('T5321FD',
      [ only_ways(['normal']),  # no optimisation for this one
-      if_wordsize(32,
+      when(wordsize(32),
           compiler_stats_range_field('bytes allocated', 240302920, 10)),
                                          # prev:       213380256
                                          # 2012-10-08: 240302920 (x86/Linux)
                                          #  (increase due to new codegen)
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 492905640, 10))
                                          # prev:       418,306,336
                                          # 29/08/2012: 492,905,640
@@ -284,20 +284,20 @@ test('T5321FD',
 
 test('T5642',
      [ only_ways(['normal']),
-      if_wordsize(32, # sample from x86/Linux
+      when(wordsize(32), # sample from x86/Linux
           compiler_stats_range_field('bytes allocated',  650000000, 10)),
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 1300000000, 10))
       ],
       compile,['-O'])
 
 test('T5837',
      [ only_ways(['normal']),
-      if_wordsize(32, # sample from x86/Linux
+      when(wordsize(32), # sample from x86/Linux
           compiler_stats_range_field('bytes allocated', 40000000, 10)),
 
       # sample: 3926235424 (amd64/Linux, 15/2/2012)
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 81879216, 10))
 	  				   # 2012-10-02 81879216
                                            # 2012-09-20 87254264 amd64/Linux
@@ -306,11 +306,11 @@ test('T5837',
 
 test('T6048',
      [ only_ways(['optasm']),
-      if_wordsize(32, # sample from x86/Linux
+      when(wordsize(32), # sample from x86/Linux
           compiler_stats_range_field('bytes allocated', 48887164, 10)),
                                            # prev:       38000000
                                            # 2012-10-08: 48887164 (x86/Linux)
-      if_wordsize(64,
+      when(wordsize(64),
           compiler_stats_range_field('bytes allocated', 97247032, 10))
                                            # 18/09/2012 97247032 amd64/Linux
       ],
diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T
index 0a864a2b0..14d972783 100644
--- a/tests/perf/haddock/all.T
+++ b/tests/perf/haddock/all.T
@@ -1,33 +1,33 @@
 
 test('haddock.base',
      [unless_in_tree_compiler(skip)
-     ,if_wordsize(64,
+     ,when(wordsize(64),
           stats_range_field('peak_megabytes_allocated', 274, 10))
                                         # 2012-08-14: 240 (amd64/Linux)
                                         # 2012-09-18: 237 (amd64/Linux)
                                         # 2012-11-12: 249 (amd64/Linux)
                                         # 2013-01-29: 274 (amd64/Linux)
-     ,if_wordsize(32,
+     ,when(wordsize(32),
           stats_range_field('peak_megabytes_allocated', 113, 1))
                                         # 2012-08-14: 144 (x86/OSX)
                                         # 2012-10-30: 113 (x86/Windows)
-     ,if_wordsize(64,
+     ,when(wordsize(64),
           stats_range_field('max_bytes_used', 96022312, 10))
                                 # 2012-08-14: 87374568 (amd64/Linux)
                                 # 2012-08-21: 86428216 (amd64/Linux)
                                 # 2012-09-20: 84794136 (amd64/Linux)
                                 # 2012-11-12: 87265136 (amd64/Linux)
                                 # 2013-01-29: 96022312 (amd64/Linux)
-     ,if_wordsize(32,
+     ,when(wordsize(32),
           stats_range_field('max_bytes_used', 45574928, 1))
                                 # 2012-08-14: 45574928 (x86/OSX)
-     ,if_wordsize(64,
+     ,when(wordsize(64),
           stats_range_field('bytes allocated', 6064874536, 2))
                                  # 2012-08-14: 5920822352 (amd64/Linux)
                                  # 2012-09-20: 5829972376 (amd64/Linux)
                                  # 2012-10-08: 5902601224 (amd64/Linux)
                                  # 2013-01-17: 6064874536 (x86_64/Linux)
-     ,if_wordsize(32,
+     ,when(wordsize(32),
           stats_range_field('bytes allocated', 2955470952, 1))
                                  # 2012-08-14: 3046487920 (x86/OSX)
                                  # 2012-10-30: 2955470952 (x86/Windows)
@@ -37,32 +37,32 @@ test('haddock.base',
 
 test('haddock.Cabal',
      [unless_in_tree_compiler(skip)
-     ,if_wordsize(64,
+     ,when(wordsize(64),
           stats_range_field('peak_megabytes_allocated', 217, 10))
                              # 2012-08-14: 202 (amd64/Linux)
                              # 2012-08-29: 211 (amd64/Linux, new codegen)
                              # 2012-09-20: 227 (amd64/Linux)
                              # 2012-10-08: 217 (amd64/Linux)
-     ,if_wordsize(32,
+     ,when(wordsize(32),
           stats_range_field('peak_megabytes_allocated', 83, 1))
                                         # 2012-08-14: 116 (x86/OSX)
                                         # 2012-10-30: 83 (x86/Windows)
-     ,if_wordsize(64,
+     ,when(wordsize(64),
           stats_range_field('max_bytes_used', 80590280, 15))
                              # 2012-08-14: 74119424 (amd64/Linux)
                              # 2012-08-29: 77992512 (amd64/Linux, new codegen)
                              # 2012-10-02: 91341568 (amd64/Linux)
                              # 2012-10-08: 80590280 (amd64/Linux)
-     ,if_wordsize(32,
+     ,when(wordsize(32),
           stats_range_field('max_bytes_used', 44224896, 5))
                              # 2012-08-14: 47461532 (x86/OSX)
                              # 2012-10-30: 44224896 (x86/Windows insreased range to 5%)
-     ,if_wordsize(64,
+     ,when(wordsize(64),
           stats_range_field('bytes allocated', 3373401360, 2))
                              # 2012-08-14: 3255435248 (amd64/Linux)
                              # 2012-08-29: 3324606664 (amd64/Linux, new codegen)
                              # 2012-10-08: 3373401360 (amd64/Linux)
-     ,if_wordsize(32,
+     ,when(wordsize(32),
           stats_range_field('bytes allocated', 1733638168, 1))
                              # 2012-08-14: 1648610180 (x86/OSX)
                              # 2012-10-30: 1733638168 (x86/Windows)
@@ -72,33 +72,33 @@ test('haddock.Cabal',
 
 test('haddock.compiler',
      [unless_in_tree_compiler(skip)
-     ,if_wordsize(64,
+     ,when(wordsize(64),
           stats_range_field('peak_megabytes_allocated', 1240, 10))
                                         # 2012-08-14: 1203 (amd64/Linux)
                                         # 2012-08-21: 1199 (amd64/Linux)
                                         # 2012-09-20: 1228 (amd64/Linux)
                                         # 2012-10-08: 1240 (amd64/Linux)
-     ,if_wordsize(32,
+     ,when(wordsize(32),
           stats_range_field('peak_megabytes_allocated', 606, 1))
                                         # 2012-08-14: 631 (x86/OSX)
                                         # 2012-10-30: 606 (x86/Windows)
-     ,if_wordsize(64,
+     ,when(wordsize(64),
           stats_range_field('max_bytes_used', 420105120, 10))
                                 # 2012-08-14: 428775544 (amd64/Linux)
                                 # 2012-09-20: 437618008 (amd64/Linux)
                                 # 2012-10-08: 442768280 (amd64/Linux)
                                 # 2012-11-12: 420105120 (amd64/Linux)
-     ,if_wordsize(32,
+     ,when(wordsize(32),
           stats_range_field('max_bytes_used', 220847924, 1))
                                 # 2012-08-14: 231064920 (x86/OSX)
                                 # 2012-10-30: 220847924 (x86/Windows)
-     ,if_wordsize(64,
+     ,when(wordsize(64),
           stats_range_field('bytes allocated', 25990254632, 10))
                               # 2012-08-14: 26,070,600,504 (amd64/Linux)
                               # 2012-08-29: 26,353,100,288 (amd64/Linux, new CG)
                               # 2012-09-18: 26,882,813,032 (amd64/Linux)
                               # 2012-11-12: 25,990,254,632 (amd64/Linux)
-     ,if_wordsize(32,
+     ,when(wordsize(32),
           stats_range_field('bytes allocated', 13773051312, 1))
                                  # 2012-08-14: 13471797488 (x86/OSX)
                                  # 2012-10-30: 13773051312 (x86/Windows)
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index ed7800300..d484c96b2 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -59,10 +59,10 @@ test('T3738',
      [extra_clean(['T3738a.hi', 'T3738a.o']),
       stats_range_field('peak_megabytes_allocated', 1, 0),
                                      # expected value: 1 (amd64/Linux)
-      if_wordsize(32,
+      when(wordsize(32),
           stats_range_field('bytes allocated', 45648, 5)),
                                      # expected value: 45648 (x86/Linux):
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 49400, 5)),
                                      # expected value: 49400 (amd64/Linux)
       only_ways(['normal'])
@@ -74,10 +74,10 @@ test('MethSharing',
      [stats_range_field('peak_megabytes_allocated', 1, 0),
                                      # expected value: 1 (amd64/Linux)
       # expected value: 2685858140 (x86/OS X):
-      if_wordsize(32,
+      when(wordsize(32),
           stats_range_field('bytes allocated', 360940756, 5)),
                                   # expected: 360940756 (x86/Linux)
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 640067672, 5)),
                                   # expected: 640067672 (amd64/Linux)
       only_ways(['normal'])
@@ -104,9 +104,9 @@ test('T149',
 
 test('T5113',
      [
-      if_wordsize(32,
+      when(wordsize(32),
           stats_range_field('bytes allocated', 4000000, 5)),
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 8000000, 5)),
       only_ways(['normal']),
       expect_broken(7046)
@@ -116,9 +116,9 @@ test('T5113',
 
 
 test('T4978',
-     [if_wordsize(32,
+     [when(wordsize(32),
           stats_range_field('bytes allocated', 10000000, 5)),
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 10137680, 5)),
                                      # expected value: 10137680 (amd64/Linux)
       only_ways(['normal'])
@@ -127,10 +127,10 @@ test('T4978',
      ['-O2'])
 
 test('T5205',
-     [if_wordsize(32,
+     [when(wordsize(32),
           stats_range_field('bytes allocated', 47088, 5)),
                            # expected value: 47088 (x86/Darwin)
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 51320, 5)),
                            # expected value: 51320 (amd64/Linux)
       only_ways(['normal', 'optasm'])
@@ -139,10 +139,10 @@ test('T5205',
      [''])
 
 test('T5549',
-     [if_wordsize(32,
+     [when(wordsize(32),
           stats_range_field('bytes allocated', 3362958676, 5)),
                            # expected value: 3362958676 (Windows)
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 6725846120, 5)),
                            # expected value: 6,725,846,120 (amd64/Linux)
       only_ways(['normal'])
@@ -151,10 +151,10 @@ test('T5549',
      ['-O'])
 
 test('T4474a',
-     [if_wordsize(32,
+     [when(wordsize(32),
           stats_range_field('bytes allocated', 1879095912, 5)),
                            # expected value: 1879095912 (i386/OSX)
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 3766493912, 5)),
                            # expected value: 3766493912 (amd64/Linux)
       only_ways(['normal'])
@@ -162,10 +162,10 @@ test('T4474a',
      compile_and_run,
      ['-O'])
 test('T4474b',
-     [if_wordsize(32,
+     [when(wordsize(32),
           stats_range_field('bytes allocated', 1879095912, 5)),
                            # expected value: 1879095912 (i386/OSX)
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 3766493912, 5)),
                            # expected value: 3766493912 (amd64/Linux)
       only_ways(['normal'])
@@ -173,10 +173,10 @@ test('T4474b',
      compile_and_run,
      ['-O'])
 test('T4474c',
-     [if_wordsize(32,
+     [when(wordsize(32),
           stats_range_field('bytes allocated', 1879095912, 5)),
                            # expected value: 1879095912 (i386/OSX)
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 3766493912, 5)),
                            # expected value: 3766493912 (amd64/Linux)
       only_ways(['normal'])
@@ -185,10 +185,10 @@ test('T4474c',
      ['-O'])
 
 test('T5237',
-     [if_wordsize(32,
+     [when(wordsize(32),
           stats_range_field('bytes allocated',  78328, 5)),
                            # expected value: 78328 (i386/Linux)
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated',  110888, 5)),
                            # expected value: 110888 (amd64/Linux)
      only_ways(['normal'])
@@ -197,10 +197,10 @@ test('T5237',
     ['-O ' + sse2_opts])
 
 test('T5536',
-     [if_wordsize(32,
+     [when(wordsize(32),
           stats_range_field('bytes allocated', 1246287228, 5)),
                            # expected value: 1246287228 (i386/Linux)
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 892399040, 5)),
                            # expected value: 2,492,589,480 (amd64/Linux)
                            # 17/1/13:          892,399,040 (x86_64/Linux)
@@ -213,16 +213,16 @@ test('T5536',
     ['-O'])
 
 test('T7257',
-     [if_wordsize(32,
+     [when(wordsize(32),
           stats_range_field('bytes allocated', 1150000000, 10)),
                            # expected value: 1246287228 (i386/Linux)
-      if_wordsize(32,
+      when(wordsize(32),
           stats_range_field('peak_megabytes_allocated', 217, 5)),
                            # 2012-10-08: 217 (x86/Linux)
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 1774893760, 5)),
                            # 2012-09-21: 1774893760 (amd64/Linux)
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('peak_megabytes_allocated', 227, 5)),
                            # 2012-09-21: 227 (amd64/Linux)
 
@@ -231,10 +231,10 @@ test('T7257',
     compile_and_run, ['-O'])
 
 test('Conversions',
-     [if_wordsize(32,
+     [when(wordsize(32),
           stats_range_field('bytes allocated', 55316, 5)),
                            # 2012-12-18: Guessed 64-bit value / 2
-      if_wordsize(64,
+      when(wordsize(64),
           stats_range_field('bytes allocated', 110632, 5)),
                            # 2012-12-18: 109608 (amd64/OS X)
 
-- 
GitLab


From e567f77a894b4630745e9b2693509939ae9c0c15 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 18:19:26 +0000
Subject: [PATCH 105/223] Rename some arguments

---
 driver/testlib.py | 8 ++++----
 1 file changed, 4 insertions(+), 4 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 4ce737279..c262b5371 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -260,16 +260,16 @@ def _extra_clean( opts, v ):
 
 # -----
 
-def stats_range_field( field, min, max ):
-    return lambda opts, f=field, x=min, y=max: _stats_range_field(opts, f, x, y);
+def stats_range_field( field, expected, dev ):
+    return lambda opts, f=field, x=expected, y=dev: _stats_range_field(opts, f, x, y);
 
 def _stats_range_field( opts, f, x, y ):
     # copy the dictionary, as the config gets shared between all tests
     opts.stats_range_fields = opts.stats_range_fields.copy()
     opts.stats_range_fields[f] = (x, y)
 
-def compiler_stats_range_field( field, min, max ):
-    return lambda opts, f=field, x=min, y=max: _compiler_stats_range_field(opts, f, x, y);
+def compiler_stats_range_field( field, expected, dev ):
+    return lambda opts, f=field, x=expected, y=dev: _compiler_stats_range_field(opts, f, x, y);
 
 def _compiler_stats_range_field( opts, f, x, y ):
     # copy the dictionary, as the config gets shared between all tests
-- 
GitLab


From 2246f3fd5fda083179c71363cbf01a04491a52fd Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 19:00:51 +0000
Subject: [PATCH 106/223] Change how the testsuite driver handles copying the
 test options

We now deepcopy the options for each test, which means that the test
helpers don't need to worry about sharing.
---
 driver/testlib.py | 8 +++-----
 1 file changed, 3 insertions(+), 5 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index c262b5371..13373922e 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -264,16 +264,12 @@ def stats_range_field( field, expected, dev ):
     return lambda opts, f=field, x=expected, y=dev: _stats_range_field(opts, f, x, y);
 
 def _stats_range_field( opts, f, x, y ):
-    # copy the dictionary, as the config gets shared between all tests
-    opts.stats_range_fields = opts.stats_range_fields.copy()
     opts.stats_range_fields[f] = (x, y)
 
 def compiler_stats_range_field( field, expected, dev ):
     return lambda opts, f=field, x=expected, y=dev: _compiler_stats_range_field(opts, f, x, y);
 
 def _compiler_stats_range_field( opts, f, x, y ):
-    # copy the dictionary, as the config gets shared between all tests
-    opts.compiler_stats_range_fields = opts.compiler_stats_range_fields.copy()
     opts.compiler_stats_range_fields[f] = (x, y)
 
 # -----
@@ -637,7 +633,9 @@ def test (name, setup, func, args):
         framework_fail(name, 'duplicate', 'There are multiple tests with this name')
     if not re.match('^[0-9]*[a-zA-Z][a-zA-Z0-9._-]*$', name):
         framework_fail(name, 'bad_name', 'This test has an invalid name')
-    myTestOpts = copy.copy(thisdir_testopts)
+    # We need a deepcopy so that dictionarys, such as the stats_range_fields
+    # dictionary, get copied too.
+    myTestOpts = copy.deepcopy(thisdir_testopts)
 
     if type(setup) is types.ListType:
        setup = composes(setup)
-- 
GitLab


From 88fe8315284410fb5819ecb351f092faba0d975d Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 21:37:15 +0000
Subject: [PATCH 107/223] Pass the test name to the test options

This allows them to give framework failures.

I also had to change how setTestOpts works. Now, rather than applying
the options to the directory's "default options", it just stores the
options to be applied for each test (i.e. once we know the test name).
---
 driver/runtests.py                   |   3 -
 driver/testlib.py                    | 183 +++++++++++++--------------
 tests/concurrent/should_run/all.T    |   2 +-
 tests/cpranal/should_compile/all.T   |   2 +-
 tests/deSugar/should_compile/all.T   |   2 +-
 tests/ffi/should_compile/all.T       |   2 +-
 tests/ghci/prog004/prog004.T         |   2 +-
 tests/ghci/should_run/all.T          |   2 +-
 tests/llvm/should_compile/all.T      |   2 +-
 tests/perf/compiler/all.T            |   2 +-
 tests/plugins/all.T                  |   2 +-
 tests/programs/okeefe_neural/test.T  |   2 +-
 tests/rts/all.T                      |   2 +-
 tests/safeHaskell/check/all.T        |   2 +-
 tests/safeHaskell/check/pkg01/all.T  |   2 +-
 tests/safeHaskell/flags/all.T        |   2 +-
 tests/safeHaskell/safeInfered/all.T  |   2 +-
 tests/safeHaskell/safeLanguage/all.T |   2 +-
 tests/safeHaskell/unsafeLibs/all.T   |   2 +-
 tests/simplCore/should_run/all.T     |   2 +-
 tests/th/TH_spliceViewPat/test.T     |   2 +-
 tests/th/all.T                       |   2 +-
 tests/typecheck/should_compile/all.T |   2 +-
 tests/typecheck/should_run/all.T     |   2 +-
 24 files changed, 112 insertions(+), 118 deletions(-)

diff --git a/driver/runtests.py b/driver/runtests.py
index f6581db8b..04d69b734 100644
--- a/driver/runtests.py
+++ b/driver/runtests.py
@@ -207,9 +207,6 @@ if windows or darwin:
 global testopts_local
 testopts_local.x = TestOptions()
 
-global thisdir_testopts
-thisdir_testopts = getThisDirTestOpts()
-
 if config.use_threads:
     t.lock = threading.Lock()
     t.thread_pool = threading.Condition(t.lock)
diff --git a/driver/testlib.py b/driver/testlib.py
index 13373922e..7d744bb5f 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -40,16 +40,6 @@ def stopNow():
 def stopping():
     return wantToStop
 
-# Options valid for all the tests in the current "directory".  After
-# each test, we reset the options to these.  To change the options for
-# multiple tests, the function setTestOpts() below can be used to alter
-# these options.
-global thisdir_testopts
-thisdir_testopts = TestOptions()
-
-def getThisDirTestOpts():
-    return thisdir_testopts
-
 # Options valid for the current test only (these get reset to
 # testdir_testopts after each test).
 
@@ -71,7 +61,8 @@ def setLocalTestOpts(opts):
 # This can be called at the top of a file of tests, to set default test options
 # for the following tests.
 def setTestOpts( f ):
-    f( thisdir_testopts );
+    global thisdir_settings
+    thisdir_settings = compose(thisdir_settings, f)
 
 # -----------------------------------------------------------------------------
 # Canned setup functions for common cases.  eg. for a test you might say
@@ -84,23 +75,23 @@ def setTestOpts( f ):
 #
 # to expect failure for this test.
 
-def normal( opts ):
+def normal( name, opts ):
     return;
 
-def skip( opts ):
+def skip( name, opts ):
     opts.skip = 1
 
-def expect_fail( opts ):
+def expect_fail( name, opts ):
     opts.expect = 'fail';
 
 def reqlib( lib ):
-    return lambda opts, l=lib: _reqlib (opts, l )
+    return lambda name, opts, l=lib: _reqlib (name, opts, l )
 
 # Cache the results of looking to see if we have a library or not.
 # This makes quite a difference, especially on Windows.
 have_lib = {}
 
-def _reqlib( opts, lib ):
+def _reqlib( name, opts, lib ):
     if have_lib.has_key(lib):
         got_it = have_lib[lib]
     else:
@@ -123,164 +114,164 @@ def _reqlib( opts, lib ):
     if not got_it:
         opts.expect = 'missing-lib'
 
-def req_profiling( opts ):
+def req_profiling( name, opts ):
     if not config.have_profiling:
         opts.expect = 'fail'
 
-def req_shared_libs( opts ):
+def req_shared_libs( name, opts ):
     if not config.have_shared_libs:
         opts.expect = 'fail'
 
-def req_interp( opts ):
+def req_interp( name, opts ):
     if not config.have_interp:
         opts.expect = 'fail'
 
-def req_smp( opts ):
+def req_smp( name, opts ):
     if not config.have_smp:
         opts.expect = 'fail'
 
 def expect_broken( bug ):
-    return lambda opts, b=bug: _expect_broken (opts, b )
+    return lambda name, opts, b=bug: _expect_broken (name, opts, b )
 
-def _expect_broken( opts, bug ):
+def _expect_broken( name, opts, bug ):
     opts.expect = 'fail';
 
-def ignore_output( opts ):
+def ignore_output( name, opts ):
     opts.ignore_output = 1
 
-def no_stdin( opts ):
+def no_stdin( name, opts ):
     opts.no_stdin = 1
 
-def combined_output( opts ):
+def combined_output( name, opts ):
     opts.combined_output = True
 
 # -----
 
 def expect_fail_for( ways ):
-    return lambda opts, w=ways: _expect_fail_for( opts, w )
+    return lambda name, opts, w=ways: _expect_fail_for( name, opts, w )
 
-def _expect_fail_for( opts, ways ):
+def _expect_fail_for( name, opts, ways ):
     opts.expect_fail_for = ways
 
 def expect_broken_for( bug, ways ):
-    return lambda opts, b=bug, w=ways: _expect_broken_for( opts, b, w )
+    return lambda name, opts, b=bug, w=ways: _expect_broken_for( name, opts, b, w )
 
-def _expect_broken_for( opts, bug, ways ):
+def _expect_broken_for( name, opts, bug, ways ):
     opts.expect_fail_for = ways
 
 # -----
 
 def omit_ways( ways ):
-    return lambda opts, w=ways: _omit_ways( opts, w )
+    return lambda name, opts, w=ways: _omit_ways( name, opts, w )
 
-def _omit_ways( opts, ways ):
+def _omit_ways( name, opts, ways ):
     opts.omit_ways = ways
 
 # -----
 
 def only_ways( ways ):
-    return lambda opts, w=ways: _only_ways( opts, w )
+    return lambda name, opts, w=ways: _only_ways( name, opts, w )
 
-def _only_ways( opts, ways ):
+def _only_ways( name, opts, ways ):
     opts.only_ways = ways
 
 # -----
 
 def extra_ways( ways ):
-    return lambda opts, w=ways: _extra_ways( opts, w )
+    return lambda name, opts, w=ways: _extra_ways( name, opts, w )
 
-def _extra_ways( opts, ways ):
+def _extra_ways( name, opts, ways ):
     opts.extra_ways = ways
 
 # -----
 
 def omit_compiler_types( compiler_types ):
-   return lambda opts, c=compiler_types: _omit_compiler_types(opts, c)
+   return lambda name, opts, c=compiler_types: _omit_compiler_types(name, opts, c)
 
-def _omit_compiler_types( opts, compiler_types ):
+def _omit_compiler_types( name, opts, compiler_types ):
     if config.compiler_type in compiler_types:
         opts.skip = 1
 
 # -----
 
 def only_compiler_types( compiler_types ):
-   return lambda opts, c=compiler_types: _only_compiler_types(opts, c)
+   return lambda name, opts, c=compiler_types: _only_compiler_types(name, opts, c)
 
-def _only_compiler_types( opts, compiler_types ):
+def _only_compiler_types( name, opts, compiler_types ):
     if config.compiler_type not in compiler_types:
         opts.skip = 1
 
 # -----
 
 def set_stdin( file ):
-   return lambda opts, f=file: _set_stdin(opts, f);
+   return lambda name, opts, f=file: _set_stdin(name, opts, f);
 
-def _set_stdin( opts, f ):
+def _set_stdin( name, opts, f ):
    opts.stdin = f
 
 # -----
 
 def exit_code( val ):
-    return lambda opts, v=val: _exit_code(opts, v);
+    return lambda name, opts, v=val: _exit_code(name, opts, v);
 
-def _exit_code( opts, v ):
+def _exit_code( name, opts, v ):
     opts.exit_code = v
 
 # -----
 
 def timeout_multiplier( val ):
-    return lambda opts, v=val: _timeout_multiplier(opts, v)
+    return lambda name, opts, v=val: _timeout_multiplier(name, opts, v)
 
-def _timeout_multiplier( opts, v ):
+def _timeout_multiplier( name, opts, v ):
     opts.timeout_multiplier = v
 
 # -----
 
 def extra_run_opts( val ):
-    return lambda opts, v=val: _extra_run_opts(opts, v);
+    return lambda name, opts, v=val: _extra_run_opts(name, opts, v);
 
-def _extra_run_opts( opts, v ):
+def _extra_run_opts( name, opts, v ):
     opts.extra_run_opts = v
 
 # -----
 
 def extra_hc_opts( val ):
-    return lambda opts, v=val: _extra_hc_opts(opts, v);
+    return lambda name, opts, v=val: _extra_hc_opts(name, opts, v);
 
-def _extra_hc_opts( opts, v ):
+def _extra_hc_opts( name, opts, v ):
     opts.extra_hc_opts = v
 
 # -----
 
 def extra_clean( files ):
-    return lambda opts, v=files: _extra_clean(opts, v);
+    return lambda name, opts, v=files: _extra_clean(name, opts, v);
 
-def _extra_clean( opts, v ):
+def _extra_clean( name, opts, v ):
     opts.clean_files = v
 
 # -----
 
 def stats_range_field( field, expected, dev ):
-    return lambda opts, f=field, x=expected, y=dev: _stats_range_field(opts, f, x, y);
+    return lambda name, opts, f=field, x=expected, y=dev: _stats_range_field(name, opts, f, x, y);
 
-def _stats_range_field( opts, f, x, y ):
+def _stats_range_field( name, opts, f, x, y ):
     opts.stats_range_fields[f] = (x, y)
 
 def compiler_stats_range_field( field, expected, dev ):
-    return lambda opts, f=field, x=expected, y=dev: _compiler_stats_range_field(opts, f, x, y);
+    return lambda name, opts, f=field, x=expected, y=dev: _compiler_stats_range_field(name, opts, f, x, y);
 
-def _compiler_stats_range_field( opts, f, x, y ):
+def _compiler_stats_range_field( name, opts, f, x, y ):
     opts.compiler_stats_range_fields[f] = (x, y)
 
 # -----
 
-def skip_if_no_ghci(opts):
+def skip_if_no_ghci(name, opts):
     if not ('ghci' in config.run_ways):
         opts.skip = 1
 
 # ----
 
-def skip_if_fast(opts):
+def skip_if_fast(name, opts):
     if config.fast:
         opts.skip = 1
 
@@ -487,89 +478,89 @@ def unless_tag( tag, f ):
         return normal
 
 # ---
-def high_memory_usage(opts):
+def high_memory_usage(name, opts):
     opts.alone = True
 
 # ---
-def literate( opts ):
+def literate( name, opts ):
     opts.literate = 1;
 
-def c_src( opts ):
+def c_src( name, opts ):
     opts.c_src = 1;
 
-def objc_src( opts ):
+def objc_src( name, opts ):
     opts.objc_src = 1;
 
-def objcpp_src( opts ):
+def objcpp_src( name, opts ):
     opts.objcpp_src = 1;
 
-def cmm_src( opts ):
+def cmm_src( name, opts ):
     opts.cmm_src = 1;
 
 def outputdir( odir ):
-    return lambda opts, d=odir: _outputdir(opts, d)
+    return lambda name, opts, d=odir: _outputdir(name, opts, d)
 
-def _outputdir( opts, odir ):
+def _outputdir( name, opts, odir ):
     opts.outputdir = odir;
 
 # ----
 
 def pre_cmd( cmd ):
-    return lambda opts, c=cmd: _pre_cmd(opts, cmd)
+    return lambda name, opts, c=cmd: _pre_cmd(name, opts, cmd)
 
-def _pre_cmd( opts, cmd ):
+def _pre_cmd( name, opts, cmd ):
     opts.pre_cmd = cmd
 
 # ----
 
 def clean_cmd( cmd ):
-    return lambda opts, c=cmd: _clean_cmd(opts, cmd)
+    return lambda name, opts, c=cmd: _clean_cmd(name, opts, cmd)
 
-def _clean_cmd( opts, cmd ):
+def _clean_cmd( name, opts, cmd ):
     opts.clean_cmd = cmd
 
 # ----
 
 def cmd_prefix( prefix ):
-    return lambda opts, p=prefix: _cmd_prefix(opts, prefix)
+    return lambda name, opts, p=prefix: _cmd_prefix(name, opts, prefix)
 
-def _cmd_prefix( opts, prefix ):
+def _cmd_prefix( name, opts, prefix ):
     opts.cmd_wrapper = lambda cmd, p=prefix: p + ' ' + cmd;
 
 # ----
 
 def cmd_wrapper( fun ):
-    return lambda opts, f=fun: _cmd_wrapper(opts, fun)
+    return lambda name, opts, f=fun: _cmd_wrapper(name, opts, fun)
 
-def _cmd_wrapper( opts, fun ):
+def _cmd_wrapper( name, opts, fun ):
     opts.cmd_wrapper = fun
 
 # ----
 
 def compile_cmd_prefix( prefix ):
-    return lambda opts, p=prefix: _compile_cmd_prefix(opts, prefix)
+    return lambda name, opts, p=prefix: _compile_cmd_prefix(name, opts, prefix)
 
-def _compile_cmd_prefix( opts, prefix ):
+def _compile_cmd_prefix( name, opts, prefix ):
     opts.compile_cmd_prefix = prefix
 
 # ----
 
-def normalise_slashes( opts ):
+def normalise_slashes( name, opts ):
     opts.extra_normaliser = normalise_slashes_
 
-def normalise_exe( opts ):
+def normalise_exe( name, opts ):
     opts.extra_normaliser = normalise_exe_
 
 def normalise_fun( fun ):
-    return lambda opts, f=fun: _normalise_fun(opts, f)
+    return lambda name, opts, f=fun: _normalise_fun(name, opts, f)
 
-def _normalise_fun( opts, f ):
+def _normalise_fun( name, opts, f ):
     opts.extra_normaliser = f
 
 def normalise_errmsg_fun( fun ):
-    return lambda opts, f=fun: _normalise_errmsg_fun(opts, f)
+    return lambda name, opts, f=fun: _normalise_errmsg_fun(name, opts, f)
 
-def _normalise_errmsg_fun( opts, f ):
+def _normalise_errmsg_fun( name, opts, f ):
     opts.extra_errmsg_normaliser = f
 
 def two_normalisers(f, g):
@@ -582,21 +573,23 @@ def composes( fs ):
     return reduce(lambda f, g: compose(f, g), fs)
 
 def compose( f, g ):
-    return lambda opts, f=f, g=g: _compose(opts,f,g)
+    return lambda name, opts, f=f, g=g: _compose(name, opts, f, g)
 
-def _compose( opts, f, g ):
-    f(opts)
-    g(opts)
+def _compose( name, opts, f, g ):
+    f(name, opts)
+    g(name, opts)
 
 # -----------------------------------------------------------------------------
 # The current directory of tests
 
 def newTestDir( dir ):
-    global thisdir_testopts
+    global thisdir_settings
     # reset the options for this test directory
-    thisdir_testopts = copy.copy(default_testopts)
-    thisdir_testopts.testdir = dir
-    thisdir_testopts.compiler_always_flags = config.compiler_always_flags
+    thisdir_settings = lambda name, opts, dir=dir: _newTestDir( name, opts, dir )
+
+def _newTestDir( name, opts, dir ):
+    opts.testdir = dir
+    opts.compiler_always_flags = config.compiler_always_flags
 
 # -----------------------------------------------------------------------------
 # Actually doing tests
@@ -629,18 +622,22 @@ def test (name, setup, func, args):
     global aloneTests
     global parallelTests
     global allTestNames
+    global thisdir_settings
     if name in allTestNames:
         framework_fail(name, 'duplicate', 'There are multiple tests with this name')
     if not re.match('^[0-9]*[a-zA-Z][a-zA-Z0-9._-]*$', name):
         framework_fail(name, 'bad_name', 'This test has an invalid name')
-    # We need a deepcopy so that dictionarys, such as the stats_range_fields
-    # dictionary, get copied too.
-    myTestOpts = copy.deepcopy(thisdir_testopts)
+
+    # Make a deep copy of the default_testopts, as we need our own copy
+    # of any dictionaries etc inside it. Otherwise, if one test modifies
+    # them, all tests will see the modified version!
+    myTestOpts = copy.deepcopy(default_testopts)
 
     if type(setup) is types.ListType:
        setup = composes(setup)
 
-    setup(myTestOpts)
+    setup = compose(thisdir_settings, setup)
+    setup(name, myTestOpts)
 
     thisTest = lambda : runTest(myTestOpts, name, func, args)
     if myTestOpts.alone:
diff --git a/tests/concurrent/should_run/all.T b/tests/concurrent/should_run/all.T
index ec867ed4d..97dc4b13a 100644
--- a/tests/concurrent/should_run/all.T
+++ b/tests/concurrent/should_run/all.T
@@ -77,7 +77,7 @@ test('T5866', exit_code(1), compile_and_run, [''])
 # -----------------------------------------------------------------------------
 # These tests we only do for a full run
 
-def f( opts ):
+def f( name, opts ):
   if config.fast:
   	opts.skip = 1
 
diff --git a/tests/cpranal/should_compile/all.T b/tests/cpranal/should_compile/all.T
index 99ffed997..2ec0a84e9 100644
--- a/tests/cpranal/should_compile/all.T
+++ b/tests/cpranal/should_compile/all.T
@@ -1,5 +1,5 @@
 # Just do the opt way...
-def f( opts ):
+def f( name, opts ):
   opts.only_ways = ['optasm']
 
 setTestOpts(f)
diff --git a/tests/deSugar/should_compile/all.T b/tests/deSugar/should_compile/all.T
index b932a49a0..979b1e764 100644
--- a/tests/deSugar/should_compile/all.T
+++ b/tests/deSugar/should_compile/all.T
@@ -1,5 +1,5 @@
 # Just do the normal way...
-def f( opts ):
+def f( name, opts ):
   opts.only_ways = ['normal']
 
 setTestOpts(f)
diff --git a/tests/ffi/should_compile/all.T b/tests/ffi/should_compile/all.T
index 99c5eef8f..a192a7b0c 100644
--- a/tests/ffi/should_compile/all.T
+++ b/tests/ffi/should_compile/all.T
@@ -1,5 +1,5 @@
 
-def ffi( opts ):
+def ffi( name, opts ):
   opts.extra_hc_opts = '-XForeignFunctionInterface -optc-Wno-implicit'
 
 setTestOpts(ffi)
diff --git a/tests/ghci/prog004/prog004.T b/tests/ghci/prog004/prog004.T
index a67ebf35c..ed17afd08 100644
--- a/tests/ghci/prog004/prog004.T
+++ b/tests/ghci/prog004/prog004.T
@@ -1,6 +1,6 @@
 setTestOpts(only_compiler_types(['ghc']))
 
-def f(opts):
+def f(name, opts):
   if not ('ghci' in config.run_ways):
 	opts.skip = 1
 setTestOpts(f)
diff --git a/tests/ghci/should_run/all.T b/tests/ghci/should_run/all.T
index d34eade39..a2552f6f9 100644
--- a/tests/ghci/should_run/all.T
+++ b/tests/ghci/should_run/all.T
@@ -2,7 +2,7 @@
 setTestOpts(if_compiler_profiled(skip))
 
 # We only want to run these tests with GHCi
-def just_ghci( opts ):
+def just_ghci( name, opts ):
   opts.only_ways = ['ghci']
 
 test('ghcirun001', just_ghci, compile_and_run, [''])
diff --git a/tests/llvm/should_compile/all.T b/tests/llvm/should_compile/all.T
index 16a91e0ac..448e8e009 100644
--- a/tests/llvm/should_compile/all.T
+++ b/tests/llvm/should_compile/all.T
@@ -1,6 +1,6 @@
 # Tests for LLVM code generator
 
-def f( opts ):
+def f( name, opts ):
   opts.only_ways = ['optllvm', 'llvm', 'debugllvm']
 
 setTestOpts(f)
diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 24fb98c25..09a02975a 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -1,4 +1,4 @@
-def no_lint(opts):
+def no_lint(name, opts):
    opts.compiler_always_flags = \
        filter(lambda opt: opt != '-dcore-lint' and opt != '-dcmm-lint', opts.compiler_always_flags)
 
diff --git a/tests/plugins/all.T b/tests/plugins/all.T
index 68225aed7..2f0fc44c9 100644
--- a/tests/plugins/all.T
+++ b/tests/plugins/all.T
@@ -1,4 +1,4 @@
-def f(opts):
+def f(name, opts):
   if (ghc_with_interpreter == 0):
 	opts.skip = 1
 
diff --git a/tests/programs/okeefe_neural/test.T b/tests/programs/okeefe_neural/test.T
index cf329cf71..326dd6b0f 100644
--- a/tests/programs/okeefe_neural/test.T
+++ b/tests/programs/okeefe_neural/test.T
@@ -1,7 +1,7 @@
 
 # this one causes the compiler to run out of heap in the simplifier
 
-def set_opts( opts ):
+def set_opts( name, opts ):
   opts.expect = 'fail'
 
 test('okeefe_neural',
diff --git a/tests/rts/all.T b/tests/rts/all.T
index 2c0ae6180..05510e9ad 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -115,7 +115,7 @@ test('return_mem_to_os', normal, compile_and_run, [''])
 
 test('T4850', normal, run_command, ['$MAKE -s --no-print-directory T4850'])
 
-def config_T5250(opts):
+def config_T5250(name, opts):
     if not (config.arch in ['i386','x86_64']):
         opts.skip = 1;
 
diff --git a/tests/safeHaskell/check/all.T b/tests/safeHaskell/check/all.T
index ca6ba0f37..59ab4fdb9 100644
--- a/tests/safeHaskell/check/all.T
+++ b/tests/safeHaskell/check/all.T
@@ -2,7 +2,7 @@
 # check of safe haskell is working properly.
 
 # Just do the normal way, SafeHaskell is all in the frontend
-def f( opts ):
+def f( name, opts ):
   opts.only_ways = ['normal']
 
 setTestOpts(f)
diff --git a/tests/safeHaskell/check/pkg01/all.T b/tests/safeHaskell/check/pkg01/all.T
index 16f6ba6f7..08f0b6182 100644
--- a/tests/safeHaskell/check/pkg01/all.T
+++ b/tests/safeHaskell/check/pkg01/all.T
@@ -1,5 +1,5 @@
 # Just do the normal way, SafeHaskell is all in the frontend
-def f( opts ):
+def f( name, opts ):
   opts.only_ways = ['normal']
 
 def normaliseArrayPackage(str):
diff --git a/tests/safeHaskell/flags/all.T b/tests/safeHaskell/flags/all.T
index 713439567..fff884179 100644
--- a/tests/safeHaskell/flags/all.T
+++ b/tests/safeHaskell/flags/all.T
@@ -4,7 +4,7 @@
 # has been dropped.
 
 # Just do the normal way, SafeHaskell is all in the frontend
-def f( opts ):
+def f( name, opts ):
   opts.only_ways = ['normal']
 
 setTestOpts(f)
diff --git a/tests/safeHaskell/safeInfered/all.T b/tests/safeHaskell/safeInfered/all.T
index dee056a61..47e965627 100644
--- a/tests/safeHaskell/safeInfered/all.T
+++ b/tests/safeHaskell/safeInfered/all.T
@@ -2,7 +2,7 @@
 # mode safe inference works correctly.
 
 # Just do the normal way, SafeHaskell is all in the frontend
-def f( opts ):
+def f( name, opts ):
   opts.only_ways = ['normal']
 
 setTestOpts(f)
diff --git a/tests/safeHaskell/safeLanguage/all.T b/tests/safeHaskell/safeLanguage/all.T
index 506b45d43..f8479b12c 100644
--- a/tests/safeHaskell/safeLanguage/all.T
+++ b/tests/safeHaskell/safeLanguage/all.T
@@ -4,7 +4,7 @@
 # works correctly (incluidng testing safe imports a little).
 
 # Just do the normal way, SafeHaskell is all in the frontend
-def f( opts ):
+def f( name, opts ):
   opts.only_ways = ['normal']
 
 setTestOpts(f)
diff --git a/tests/safeHaskell/unsafeLibs/all.T b/tests/safeHaskell/unsafeLibs/all.T
index eddf9566c..69d1804b0 100644
--- a/tests/safeHaskell/unsafeLibs/all.T
+++ b/tests/safeHaskell/unsafeLibs/all.T
@@ -4,7 +4,7 @@
 # Checking base package is properly safe basically
 
 # Just do the normal way, SafeHaskell is all in the frontend
-def f( opts ):
+def f( name, opts ):
   opts.only_ways = ['normal']
 
 setTestOpts(f)
diff --git a/tests/simplCore/should_run/all.T b/tests/simplCore/should_run/all.T
index 40c553fe8..545dadbf6 100644
--- a/tests/simplCore/should_run/all.T
+++ b/tests/simplCore/should_run/all.T
@@ -4,7 +4,7 @@
 #	expected process return value, if not zero
 
 # Only compile with optimisation
-def f( opts ):
+def f( name, opts ):
   opts.only_ways = ['optasm']
 
 setTestOpts(f)
diff --git a/tests/th/TH_spliceViewPat/test.T b/tests/th/TH_spliceViewPat/test.T
index c93e1cb3a..b177c075b 100644
--- a/tests/th/TH_spliceViewPat/test.T
+++ b/tests/th/TH_spliceViewPat/test.T
@@ -1,4 +1,4 @@
-def f(opts):
+def f(name, opts):
   opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell'
   if (ghc_with_interpreter == 0):
 	opts.skip = 1
diff --git a/tests/th/all.T b/tests/th/all.T
index 2d190dd5c..e9c6c08cd 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -3,7 +3,7 @@
 # to run it !if_compiler_profiled
 test('T4255', unless_compiler_profiled(skip), compile_fail, ['-v0'])
 
-def f(opts):
+def f(name, opts):
   opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell'
   if (ghc_with_interpreter == 0):
 	opts.skip = 1
diff --git a/tests/typecheck/should_compile/all.T b/tests/typecheck/should_compile/all.T
index 94ebf41fd..da9123369 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -1,6 +1,6 @@
 # Args to vtc are: extra compile flags
 
-def f( opts ):
+def f( name, opts ):
   opts.extra_hc_opts = '-fno-warn-incomplete-patterns'
 
 setTestOpts(f)
diff --git a/tests/typecheck/should_run/all.T b/tests/typecheck/should_run/all.T
index 4c9d7abff..083088c3e 100755
--- a/tests/typecheck/should_run/all.T
+++ b/tests/typecheck/should_run/all.T
@@ -16,7 +16,7 @@ test('Defer01', normal, compile_and_run, [''])
 # -----------------------------------------------------------------------------
 # Skip everything else if fast is on
 
-def f(opts):
+def f(name, opts):
   if config.fast:
 	opts.skip = 1
 setTestOpts(f)
-- 
GitLab


From 76c3b2e95063a0aa131848605659f099c24f7a27 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 21:39:54 +0000
Subject: [PATCH 108/223] Remove unused *_num_fields bindings

---
 driver/testglobals.py | 11 -----------
 1 file changed, 11 deletions(-)

diff --git a/driver/testglobals.py b/driver/testglobals.py
index 500e7f401..db99ef1b2 100644
--- a/driver/testglobals.py
+++ b/driver/testglobals.py
@@ -214,17 +214,6 @@ class TestOptions:
        self.compiler_stats_range_fields = {}
        self.stats_range_fields = {}
 
-       # TODO: deprecate this in favour of compiler_stats_range_fields
-       #
-       # which -t numeric fields do we want to look at, and what bounds must
-       # they fall within?
-       # Elements of these lists should be things like
-       # ('bytes allocated',
-       #   9300000000,
-       #   9400000000)
-       self.compiler_stats_num_fields = {}
-       self.stats_num_fields = {}
-
        # should we run this test alone, i.e. not run it in parallel with
        # any other threads
        self.alone = False
-- 
GitLab


From 3967a5e4aca1b17c47beaa72da7e633854413cb8 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 22:47:30 +0000
Subject: [PATCH 109/223] Add a different sort of stats_num_field helper
 function

Uses look like
    stats_num_field('bytes allocated',
                    [(wordsize(32), 45648, 5),
                     (wordsize(64), 49400, 5)])
where the first matching triple will be used. e.g. we could override
the Win32 expected values with:
                    [(platform('i386-unknown-mingw32'), 41000, 5),
                     (wordsize(32),                     45648, 5),
                     (wordsize(64),                     49400, 5)])
with other 32-bit platforms falling through to the wordsize(32) case.

This makes it easier to give different values for different platforms,
while being sure that all platforms are covered.
---
 driver/testlib.py           | 36 +++++++++++++++++++++++++++++-------
 tests/perf/should_run/all.T | 11 +++++------
 2 files changed, 34 insertions(+), 13 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 7d744bb5f..c9884347c 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -251,17 +251,39 @@ def _extra_clean( name, opts, v ):
 
 # -----
 
+def stats_num_field( field, expecteds ):
+    return lambda name, opts, f=field, e=expecteds: _stats_num_field(name, opts, f, e);
+
+def _stats_num_field( name, opts, field, expecteds ):
+    if field in opts.stats_range_fields:
+        framework_fail(name, 'duplicate-numfield', 'Duplicate ' + field + ' num_field check')
+
+    for (b, expected, dev) in expecteds:
+        if b:
+            opts.stats_range_fields[field] = (expected, dev)
+            return
+
+    framework_fail(name, 'numfield-no-expected', 'No expected value found for ' + field + ' in num_field check')
+
 def stats_range_field( field, expected, dev ):
-    return lambda name, opts, f=field, x=expected, y=dev: _stats_range_field(name, opts, f, x, y);
+    return stats_num_field( field, [(True, expected, dev)] )
 
-def _stats_range_field( name, opts, f, x, y ):
-    opts.stats_range_fields[f] = (x, y)
+def compiler_stats_num_field( field, expecteds ):
+    return lambda name, opts, f=field, e=expecteds: _compiler_stats_num_field(name, opts, f, e);
 
-def compiler_stats_range_field( field, expected, dev ):
-    return lambda name, opts, f=field, x=expected, y=dev: _compiler_stats_range_field(name, opts, f, x, y);
+def _compiler_stats_num_field( name, opts, field, expecteds ):
+    if field in opts.compiler_stats_range_fields:
+        framework_fail(name, 'duplicate-numfield', 'Duplicate ' + field + ' num_field check')
+
+    for (b, expected, dev) in expecteds:
+        if b:
+            opts.compiler_stats_range_fields[field] = (expected, dev)
+            return
 
-def _compiler_stats_range_field( name, opts, f, x, y ):
-    opts.compiler_stats_range_fields[f] = (x, y)
+    framework_fail(name, 'numfield-no-expected', 'No expected value found for ' + field + ' in num_field check')
+
+def compiler_stats_range_field( field, expected, dev ):
+    return compiler_stats_num_field( field, [(True, expected, dev)] )
 
 # -----
 
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index d484c96b2..6ec85234f 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -59,12 +59,11 @@ test('T3738',
      [extra_clean(['T3738a.hi', 'T3738a.o']),
       stats_range_field('peak_megabytes_allocated', 1, 0),
                                      # expected value: 1 (amd64/Linux)
-      when(wordsize(32),
-          stats_range_field('bytes allocated', 45648, 5)),
-                                     # expected value: 45648 (x86/Linux):
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 49400, 5)),
-                                     # expected value: 49400 (amd64/Linux)
+      stats_num_field('bytes allocated',
+                      [(wordsize(32), 45648, 5),
+                    # expected value: 45648 (x86/Linux)
+                       (wordsize(64), 49400, 5)]),
+                    # expected value: 49400 (amd64/Linux)
       only_ways(['normal'])
       ],
      compile_and_run,
-- 
GitLab


From 6259d78582773a8fabae0f6edccc475e6921b013 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 23:36:55 +0000
Subject: [PATCH 110/223] Allow a simpler form of stats_num_field where all
 platforms use the same value

---
 driver/testlib.py           | 14 +++++++++-----
 tests/perf/should_run/all.T |  4 ++--
 2 files changed, 11 insertions(+), 7 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index c9884347c..4c9b2c269 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -258,12 +258,16 @@ def _stats_num_field( name, opts, field, expecteds ):
     if field in opts.stats_range_fields:
         framework_fail(name, 'duplicate-numfield', 'Duplicate ' + field + ' num_field check')
 
-    for (b, expected, dev) in expecteds:
-        if b:
-            opts.stats_range_fields[field] = (expected, dev)
-            return
+    if type(expecteds) is types.ListType:
+        for (b, expected, dev) in expecteds:
+            if b:
+                opts.stats_range_fields[field] = (expected, dev)
+                return
+        framework_fail(name, 'numfield-no-expected', 'No expected value found for ' + field + ' in num_field check')
 
-    framework_fail(name, 'numfield-no-expected', 'No expected value found for ' + field + ' in num_field check')
+    else:
+        (expected, dev) = expecteds
+        opts.stats_range_fields[field] = (expected, dev)
 
 def stats_range_field( field, expected, dev ):
     return stats_num_field( field, [(True, expected, dev)] )
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 6ec85234f..4f45a7089 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -57,8 +57,8 @@ test('T3736',
      ['$MAKE -s --no-print-directory T3736'])
 test('T3738',
      [extra_clean(['T3738a.hi', 'T3738a.o']),
-      stats_range_field('peak_megabytes_allocated', 1, 0),
-                                     # expected value: 1 (amd64/Linux)
+      stats_num_field('peak_megabytes_allocated', (1, 0)),
+                                 # expected value: 1 (amd64/Linux)
       stats_num_field('bytes allocated',
                       [(wordsize(32), 45648, 5),
                     # expected value: 45648 (x86/Linux)
-- 
GitLab


From 9cbf1939fbb5718d48f29b0af6301fd048f4f556 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 7 Feb 2013 23:58:38 +0000
Subject: [PATCH 111/223] Convert to stats_num_field in perf/should_run

---
 tests/perf/should_run/all.T | 178 +++++++++++++++++-------------------
 1 file changed, 82 insertions(+), 96 deletions(-)

diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 4f45a7089..5b17e452c 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -4,19 +4,19 @@
 # because the test allocates an unboxed array of doubles.
 
 test('T3586',
-     [stats_range_field('peak_megabytes_allocated', 17, 1),
-                                     # expected value: 17 (amd64/Linux)
-      stats_range_field('bytes allocated', 16835544, 5),
-                                     # expected value: 16835544 (amd64/Linux)
+     [stats_num_field('peak_megabytes_allocated', (17, 1)),
+                                 # expected value: 17 (amd64/Linux)
+      stats_num_field('bytes allocated', (16835544, 5)),
+                        # expected value: 16835544 (amd64/Linux)
       only_ways(['normal'])
       ],
      compile_and_run,
      ['-O'])
 
 test('T4830',
-     [stats_range_field('bytes allocated',  99264, 1),
-               # (amd64/Linux):            127000
-               # (amd64/Linux) 2013-02-07:  99264
+     [stats_num_field('bytes allocated', (99264, 1)),
+             # (amd64/Linux):            127000
+             # (amd64/Linux) 2013-02-07:  99264
       only_ways(['normal'])
       ],
      compile_and_run,
@@ -28,11 +28,11 @@ test('T3245', normal, compile_and_run, ['-O'])
 # a bug in hGetBufNonBlocking in 6.13 that triggered this.
 #
 test('lazy-bs-alloc',
-     [stats_range_field('peak_megabytes_allocated', 2, 1),
-                                     # expected value: 2 (amd64/Linux)
-      stats_range_field('bytes allocated', 429744, 1),
-              # (amd64/Linux):             489776
-              # (amd64/Linux) 2013-02-07:  429744
+     [stats_num_field('peak_megabytes_allocated', (2, 1)),
+                                 # expected value: 2 (amd64/Linux)
+      stats_num_field('bytes allocated', (429744, 1)),
+             # (amd64/Linux):             489776
+             # (amd64/Linux) 2013-02-07:  429744
       only_ways(['normal']),
       extra_run_opts('../../numeric/should_run/arith011.stdout'),
       ignore_output
@@ -70,15 +70,14 @@ test('T3738',
      ['-O'])
 
 test('MethSharing',
-     [stats_range_field('peak_megabytes_allocated', 1, 0),
-                                     # expected value: 1 (amd64/Linux)
-      # expected value: 2685858140 (x86/OS X):
-      when(wordsize(32),
-          stats_range_field('bytes allocated', 360940756, 5)),
-                                  # expected: 360940756 (x86/Linux)
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 640067672, 5)),
-                                  # expected: 640067672 (amd64/Linux)
+     [stats_num_field('peak_megabytes_allocated', (1, 0)),
+                                 # expected value: 1 (amd64/Linux)
+      stats_num_field('bytes allocated', 
+                      [(wordsize(32), 360940756, 5),
+                    # expected value: 2685858140 (x86/OS X)
+                          # expected: 360940756 (x86/Linux)
+                       (wordsize(64), 640067672, 5)]),
+                          # expected: 640067672 (amd64/Linux)
       only_ways(['normal'])
       ],
      compile_and_run,
@@ -102,11 +101,9 @@ test('T149',
      ['$MAKE -s --no-print-directory T149'])
 
 test('T5113',
-     [
-      when(wordsize(32),
-          stats_range_field('bytes allocated', 4000000, 5)),
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 8000000, 5)),
+     [stats_num_field('bytes allocated',
+                      [(wordsize(32), 4000000, 5),
+                       (wordsize(64), 8000000, 5)]),
       only_ways(['normal']),
       expect_broken(7046)
       ],
@@ -115,95 +112,87 @@ test('T5113',
 
 
 test('T4978',
-     [when(wordsize(32),
-          stats_range_field('bytes allocated', 10000000, 5)),
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 10137680, 5)),
-                                     # expected value: 10137680 (amd64/Linux)
+     [stats_num_field('bytes allocated',
+                      [(wordsize(32), 10000000, 5),
+                       (wordsize(64), 10137680, 5)]),
+                    # expected value: 10137680 (amd64/Linux)
       only_ways(['normal'])
       ],
      compile_and_run,
      ['-O2'])
 
 test('T5205',
-     [when(wordsize(32),
-          stats_range_field('bytes allocated', 47088, 5)),
-                           # expected value: 47088 (x86/Darwin)
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 51320, 5)),
-                           # expected value: 51320 (amd64/Linux)
+     [stats_num_field('bytes allocated',
+                      [(wordsize(32), 47088, 5),
+                    # expected value: 47088 (x86/Darwin)
+                       (wordsize(64), 51320, 5)]),
+                    # expected value: 51320 (amd64/Linux)
       only_ways(['normal', 'optasm'])
       ],
      compile_and_run,
      [''])
 
 test('T5549',
-     [when(wordsize(32),
-          stats_range_field('bytes allocated', 3362958676, 5)),
-                           # expected value: 3362958676 (Windows)
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 6725846120, 5)),
-                           # expected value: 6,725,846,120 (amd64/Linux)
+     [stats_num_field('bytes allocated',
+                      [(wordsize(32), 3362958676, 5),
+                    # expected value: 3362958676 (Windows)
+                       (wordsize(64), 6725846120, 5)]),
+                    # expected value: 6725846120 (amd64/Linux)
       only_ways(['normal'])
       ],
      compile_and_run,
      ['-O'])
 
 test('T4474a',
-     [when(wordsize(32),
-          stats_range_field('bytes allocated', 1879095912, 5)),
-                           # expected value: 1879095912 (i386/OSX)
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 3766493912, 5)),
-                           # expected value: 3766493912 (amd64/Linux)
+     [stats_num_field('bytes allocated',
+                      [(wordsize(32), 1879095912, 5),
+                    # expected value: 1879095912 (i386/OSX)
+                       (wordsize(64), 3766493912, 5)]),
+                    # expected value: 3766493912 (amd64/Linux)
       only_ways(['normal'])
       ],
      compile_and_run,
      ['-O'])
 test('T4474b',
-     [when(wordsize(32),
-          stats_range_field('bytes allocated', 1879095912, 5)),
-                           # expected value: 1879095912 (i386/OSX)
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 3766493912, 5)),
-                           # expected value: 3766493912 (amd64/Linux)
+     [stats_num_field('bytes allocated',
+                      [(wordsize(32), 1879095912, 5),
+                    # expected value: 1879095912 (i386/OSX)
+                       (wordsize(64), 3766493912, 5)]),
+                    # expected value: 3766493912 (amd64/Linux)
       only_ways(['normal'])
       ],
      compile_and_run,
      ['-O'])
 test('T4474c',
-     [when(wordsize(32),
-          stats_range_field('bytes allocated', 1879095912, 5)),
-                           # expected value: 1879095912 (i386/OSX)
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 3766493912, 5)),
-                           # expected value: 3766493912 (amd64/Linux)
+     [stats_num_field('bytes allocated',
+                      [(wordsize(32), 1879095912, 5),
+                    # expected value: 1879095912 (i386/OSX)
+                       (wordsize(64), 3766493912, 5)]),
+                    # expected value: 3766493912 (amd64/Linux)
       only_ways(['normal'])
       ],
      compile_and_run,
      ['-O'])
 
 test('T5237',
-     [when(wordsize(32),
-          stats_range_field('bytes allocated',  78328, 5)),
-                           # expected value: 78328 (i386/Linux)
-      when(wordsize(64),
-          stats_range_field('bytes allocated',  110888, 5)),
-                           # expected value: 110888 (amd64/Linux)
+     [stats_num_field('bytes allocated',
+                        [(wordsize(32), 78328, 5),
+                      # expected value: 78328 (i386/Linux)
+                         (wordsize(64), 110888, 5)]),
+                      # expected value: 110888 (amd64/Linux)
      only_ways(['normal'])
      ],
     compile_and_run,
     ['-O ' + sse2_opts])
 
 test('T5536',
-     [when(wordsize(32),
-          stats_range_field('bytes allocated', 1246287228, 5)),
-                           # expected value: 1246287228 (i386/Linux)
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 892399040, 5)),
-                           # expected value: 2,492,589,480 (amd64/Linux)
-                           # 17/1/13:          892,399,040 (x86_64/Linux)
-                           #                   (new demand analyser)
+     [stats_num_field('bytes allocated',
+                      [(wordsize(32), 1246287228, 5),
+                    # expected value: 1246287228 (i386/Linux)
+                       (wordsize(64), 892399040, 5)]),
+                   # expected value: 2492589480 (amd64/Linux)
+                   # 17/1/13:         892399040 (x86_64/Linux)
+                   #                  (new demand analyser)
      extra_clean(['T5536.data']),
      ignore_output,
      only_ways(['normal'])
@@ -212,30 +201,27 @@ test('T5536',
     ['-O'])
 
 test('T7257',
-     [when(wordsize(32),
-          stats_range_field('bytes allocated', 1150000000, 10)),
-                           # expected value: 1246287228 (i386/Linux)
-      when(wordsize(32),
-          stats_range_field('peak_megabytes_allocated', 217, 5)),
-                           # 2012-10-08: 217 (x86/Linux)
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 1774893760, 5)),
-                           # 2012-09-21: 1774893760 (amd64/Linux)
-      when(wordsize(64),
-          stats_range_field('peak_megabytes_allocated', 227, 5)),
-                           # 2012-09-21: 227 (amd64/Linux)
+     [stats_num_field('bytes allocated',
+                      [(wordsize(32), 1150000000, 10),
+                    # expected value: 1246287228 (i386/Linux)
+                       (wordsize(64), 1774893760, 5)]),
+                        # 2012-09-21: 1774893760 (amd64/Linux)
+      stats_num_field('peak_megabytes_allocated',
+                      [(wordsize(32), 217, 5),
+                        # 2012-10-08: 217 (x86/Linux)
+                       (wordsize(64), 227, 5)]),
+                        # 2012-09-21: 227 (amd64/Linux)
 
       only_ways(['normal'])
      ],
     compile_and_run, ['-O'])
 
 test('Conversions',
-     [when(wordsize(32),
-          stats_range_field('bytes allocated', 55316, 5)),
-                           # 2012-12-18: Guessed 64-bit value / 2
-      when(wordsize(64),
-          stats_range_field('bytes allocated', 110632, 5)),
-                           # 2012-12-18: 109608 (amd64/OS X)
+     [stats_num_field('bytes allocated',
+                      [(wordsize(32), 55316, 5),
+                        # 2012-12-18: Guessed 64-bit value / 2
+                       (wordsize(64), 110632, 5)]),
+                        # 2012-12-18: 109608 (amd64/OS X)
 
       only_ways(['normal'])
      ],
@@ -245,9 +231,9 @@ test('T7507', omit_ways(['ghci']), compile_and_run, ['-O'])
 # For 7507, stack overflow is the bad case
 
 test('T7436',
-     [stats_range_field('max_bytes_used', 60360, 1),
-           # (amd64/Linux):              127000
-           # (amd64/Linux) 2013-02-07:    60360
+     [stats_num_field('max_bytes_used', (60360, 1)),
+          # (amd64/Linux):              127000
+          # (amd64/Linux) 2013-02-07:    60360
       only_ways(['normal'])
       ],
      compile_and_run,
-- 
GitLab


From 22951cdab93ab21dab9fe5597954b922c9c89a48 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 8 Feb 2013 00:38:42 +0000
Subject: [PATCH 112/223] Replace 'if_platform' and 'unless_platform' with
 'platform'

---
 driver/testlib.py                  | 13 ++-----------
 tests/codeGen/should_gen_asm/all.T |  6 +++---
 tests/ffi/should_run/all.T         |  2 +-
 tests/ghci/scripts/all.T           |  2 +-
 tests/numeric/should_run/all.T     |  2 +-
 tests/perf/compiler/all.T          |  6 +++---
 tests/rts/all.T                    | 12 ++++++------
 7 files changed, 17 insertions(+), 26 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 4c9b2c269..aa601f786 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -312,17 +312,8 @@ def when(b, f):
 def unless(b, f):
     return when(not b, f)
 
-def if_platform( plat, f ):
-    if config.platform == plat:
-        return f
-    else:
-        return normal
-
-def unless_platform( plat, f ):
-    if config.platform != plat:
-        return f
-    else:
-        return normal
+def platform( plat ):
+    return config.platform == plat
 
 def if_os( os, f ):
     if config.os == os:
diff --git a/tests/codeGen/should_gen_asm/all.T b/tests/codeGen/should_gen_asm/all.T
index a24ae311b..be30d5fe1 100644
--- a/tests/codeGen/should_gen_asm/all.T
+++ b/tests/codeGen/should_gen_asm/all.T
@@ -1,6 +1,6 @@
 test('memcpy',
-     unless_platform('x86_64-unknown-linux',skip), compile_cmp_asm, [''])
+     unless(platform('x86_64-unknown-linux'),skip), compile_cmp_asm, [''])
 test('memcpy-unroll',
-     unless_platform('x86_64-unknown-linux',skip), compile_cmp_asm, [''])
+     unless(platform('x86_64-unknown-linux'),skip), compile_cmp_asm, [''])
 test('memcpy-unroll-conprop',
-     unless_platform('x86_64-unknown-linux',skip), compile_cmp_asm, [''])
+     unless(platform('x86_64-unknown-linux'),skip), compile_cmp_asm, [''])
diff --git a/tests/ffi/should_run/all.T b/tests/ffi/should_run/all.T
index 1811f42af..09e69447e 100644
--- a/tests/ffi/should_run/all.T
+++ b/tests/ffi/should_run/all.T
@@ -33,7 +33,7 @@ test('ffi004', skip, compile_and_run, [''])
 #
 test('ffi005', [ omit_ways(prof_ways), 
                  if_arch('i386', skip),
-                 if_platform('i386-apple-darwin', expect_broken(4105)),
+                 when(platform('i386-apple-darwin'), expect_broken(4105)),
                  exit_code(3) ],
                compile_and_run, [''])
 
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index f204af76d..0b8f62e99 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -38,7 +38,7 @@ test('ghci022', normal, ghci_script, ['ghci022.script'])
 test('ghci023', normal, ghci_script, ['ghci023.script'])
 test('ghci024',
      [skip_if_fast,
-      if_platform("powerpc-apple-darwin", expect_broken(1845))],
+      when(platform("powerpc-apple-darwin"), expect_broken(1845))],
      run_command,
      ['$MAKE -s --no-print-directory ghci024'])
 test('ghci025', normal, ghci_script, ['ghci025.script'])
diff --git a/tests/numeric/should_run/all.T b/tests/numeric/should_run/all.T
index b2109de9e..d2f017a1f 100644
--- a/tests/numeric/should_run/all.T
+++ b/tests/numeric/should_run/all.T
@@ -7,7 +7,7 @@ test('arith001', normal, compile_and_run, [''])
 test('arith002', normal, compile_and_run, [''])
 test('arith003', normal, compile_and_run, [''])
 test('arith004', normal, compile_and_run, [''])
-test('arith005', if_platform('i386-apple-darwin', expect_broken_for(7043, 'ghci')), compile_and_run, [''])
+test('arith005', when(platform('i386-apple-darwin'), expect_broken_for(7043, 'ghci')), compile_and_run, [''])
 test('arith006', normal, compile_and_run, [''])
 test('arith007', normal, compile_and_run, [''])
 
diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 09a02975a..1ba4c15cb 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -117,7 +117,7 @@ test('T4801',
                    # 12/11/2012: 49 (amd64/Linux) (REASON UNKNOWN!)
 
       # expected value: 58 (amd64/OS X):
-      if_platform('x86_64-apple-darwin',
+      when(platform('x86_64-apple-darwin'),
           compiler_stats_range_field('peak_megabytes_allocated', 58, 1)),
       # expected value: 228286660 (x86/OS X)
       when(wordsize(32),
@@ -130,7 +130,7 @@ test('T4801',
                    # 19/10/2012: 392409984 (amd64/Linux) (-fPIC turned off)
 
       # expected value: 510938976 (amd64/OS X):
-      if_platform('x86_64-apple-darwin',
+      when(platform('x86_64-apple-darwin'),
           compiler_stats_range_field('bytes allocated', 510938976, 5)),
 
       when(wordsize(32),
@@ -144,7 +144,7 @@ test('T4801',
                 # 19/10/2012: 26882576 (-fPIC turned on)
                 # 19/10/2012: 18619912 (-fPIC turned off)
                 # 24/12/2012: 21657520 (perhaps gc sampling time wibbles?)
-      if_platform('x86_64-apple-darwin',
+      when(platform('x86_64-apple-darwin'),
           compiler_stats_range_field('max_bytes_used', 21657520, 5)),
        only_ways(['normal']),
        extra_hc_opts('-static')
diff --git a/tests/rts/all.T b/tests/rts/all.T
index 05510e9ad..380ce85c9 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -9,7 +9,7 @@ test('testblockalloc', compose(c_src,
 test('bug1010', normal, compile_and_run, ['+RTS -c -RTS'])
 test('derefnull',
      composes([
-             if_platform('x86_64-unknown-mingw32', expect_broken(6079)),
+             when(platform('x86_64-unknown-mingw32'), expect_broken(6079)),
              # LLVM Optimiser considers dereference of a null pointer
              # undefined and marks the code as unreachable which means
              # that later optimisations remove it altogether.
@@ -21,13 +21,13 @@ test('derefnull',
              # the right exit code we're OK.
              if_os('linux', ignore_output),
              # SIGBUS on OX X (PPC and x86 only; amd64 gives SEGV)
-             if_platform('i386-apple-darwin', exit_code(138)),
-             if_platform('powerpc-apple-darwin', exit_code(138)),
+             when(platform('i386-apple-darwin'), exit_code(138)),
+             when(platform('powerpc-apple-darwin'), exit_code(138)),
              if_os('mingw32', exit_code(1))]),
      compile_and_run, [''])
 test('divbyzero',
      composes([
-             if_platform('x86_64-unknown-mingw32', expect_broken(6079)),
+             when(platform('x86_64-unknown-mingw32'), expect_broken(6079)),
              # SIGFPE on Linux
              exit_code(136),
              # Apparently the output can be different on different
@@ -121,8 +121,8 @@ def config_T5250(name, opts):
 
 test('T5250', [ config_T5250,
                 # stack ptr is not 16-byte aligned on 32-bit Windows
-                if_platform('i386-unknown-mingw32', expect_fail),
-                if_platform('i386-unknown-linux',
+                when(platform('i386-unknown-mingw32'), expect_fail),
+                when(platform('i386-unknown-linux'),
                             expect_broken_for(4211,['llvm'])),
                 extra_clean(['spalign.o']),
                 omit_ways(['ghci']) ],
-- 
GitLab


From 9f66dc1c6af1359c552194fd6a03bf21bb4bc3c2 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 8 Feb 2013 00:54:41 +0000
Subject: [PATCH 113/223] Switch some more tests to use the new helpers

---
 tests/perf/compiler/all.T | 59 ++++++++++++++++++---------------------
 1 file changed, 27 insertions(+), 32 deletions(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 1ba4c15cb..83b458d38 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -107,45 +107,40 @@ test('T3294',
 test('T4801',
      [ # expect_broken(5224),
        # temporarily unbroken (#5227)
-      when(wordsize(32),
-          compiler_stats_range_field('peak_megabytes_allocated', 30, 20)),
-
-      when(wordsize(64),
-          compiler_stats_range_field('peak_megabytes_allocated', 49, 20)),
-                   # prev:       50 (amd64/Linux)
-                   # 19/10/2012: 64 (amd64/Linux) (REASON UNKNOWN!)
-                   # 12/11/2012: 49 (amd64/Linux) (REASON UNKNOWN!)
-
-      # expected value: 58 (amd64/OS X):
-      when(platform('x86_64-apple-darwin'),
-          compiler_stats_range_field('peak_megabytes_allocated', 58, 1)),
-      # expected value: 228286660 (x86/OS X)
-      when(wordsize(32),
-          compiler_stats_range_field('bytes allocated', 185669232, 10)),
-
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 392409984, 10)),
-                   # prev:       360243576 (amd64/Linux)
-                   # 19/10/2012: 447190832 (amd64/Linux) (-fPIC turned on)
-                   # 19/10/2012: 392409984 (amd64/Linux) (-fPIC turned off)
-
-      # expected value: 510938976 (amd64/OS X):
-      when(platform('x86_64-apple-darwin'),
-          compiler_stats_range_field('bytes allocated', 510938976, 5)),
-
-      when(wordsize(32),
-          compiler_stats_range_field('max_bytes_used', 9651948, 5)),
+      compiler_stats_num_field('peak_megabytes_allocated',
+          [(platform('x86_64-apple-darwin'), 58, 1),
+                           # expected value: 58 (amd64/OS X)
+           (wordsize(32), 30, 20),
+           (wordsize(64), 49, 20)]),
+            # prev:       50 (amd64/Linux)
+            # 19/10/2012: 64 (amd64/Linux)
+            #                (REASON UNKNOWN!)
+            # 12/11/2012: 49 (amd64/Linux)
+            #                (REASON UNKNOWN!)
+
+      compiler_stats_num_field('bytes allocated',
+          [(platform('x86_64-apple-darwin'), 510938976, 5),
+                           # expected value: 510938976 (amd64/OS X):
+
+           (wordsize(32), 185669232, 10),
+        # expected value: 228286660 (x86/OS X)
+
+           (wordsize(64), 392409984, 10)]),
+            # prev:       360243576 (amd64/Linux)
+            # 19/10/2012: 447190832 (amd64/Linux) (-fPIC turned on)
+            # 19/10/2012: 392409984 (amd64/Linux) (-fPIC turned off)
+
+      compiler_stats_num_field('max_bytes_used',
+          [(platform('x86_64-apple-darwin'), 21657520, 5),
+           (wordsize(32), 9651948, 5),
       #                    expected value: x86/OS X:  9651948
       #                    expected value:           10290952 (windows)
-      when(wordsize(64),
-          compiler_stats_range_field('max_bytes_used', 21657520, 15)),
+           (wordsize(64), 21657520, 15)]),
                 # prev:       20486256 (amd64/OS X)
                 # 30/08/2012: 17305600--20391920 (varies a lot)
                 # 19/10/2012: 26882576 (-fPIC turned on)
                 # 19/10/2012: 18619912 (-fPIC turned off)
                 # 24/12/2012: 21657520 (perhaps gc sampling time wibbles?)
-      when(platform('x86_64-apple-darwin'),
-          compiler_stats_range_field('max_bytes_used', 21657520, 5)),
        only_ways(['normal']),
        extra_hc_opts('-static')
       ],
-- 
GitLab


From 478da8fea8c7aca287a0a6270e20254221c60c84 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 8 Feb 2013 13:35:34 +0000
Subject: [PATCH 114/223] Convert remaining *_range_field's to *_num_field

---
 tests/perf/compiler/all.T    | 318 ++++++++++++++++-------------------
 tests/perf/haddock/all.T     | 169 +++++++++----------
 tests/perf/space_leaks/all.T |  26 +--
 3 files changed, 241 insertions(+), 272 deletions(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 83b458d38..20b755bbe 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -6,55 +6,52 @@ setTestOpts(no_lint)
 
 
 test('T1969',
-     [when(wordsize(32),
-          compiler_stats_range_field('peak_megabytes_allocated', 18, 1)),
-                             # expected value: 14 (x86/Windows 17/05/10)
-                             #                 15 (x86/OS X)
-                             #                 19 (x86/OS X)
-      when(wordsize(64),
-          compiler_stats_range_field('peak_megabytes_allocated', 25, 1)),
-                                             # expected value: 28 (amd64/Linux)
-                                             # expected value: 34 (amd64/Linux)
-                                             # 2012-09-20      23 (amd64/Linux)
-                                             # 2012-10-03      25 (amd64/Linux if .hi exists)
-      when(wordsize(32),
-          compiler_stats_range_field('max_bytes_used', 6149572, 5)),
-                             # expected value: 6707308 (x86/OS X)
-                             #                 5717704 (x86/Windows 17/05/10)
-                             #                 6149572 (x86/Linux, 31/12/09)
-      when(wordsize(64),
-          compiler_stats_range_field('max_bytes_used', 9000000, 20)),
-                                  # looks like the peak is around 10M, but we're
-                                  # unlikely to GC exactly on the peak.
-                                  # varies quite a lot with CLEANUP and BINDIST,
-                                  # hence 10% range.
-      when(wordsize(32),
-          compiler_stats_range_field('bytes allocated', 303930948, 5)),
-                        # expected value: 215582916 (x86/Windows)
-                        #                 221667908 (x86/OS X)
-                        #                 274932264 (x86/Linux)
-                        # 2012-10-08:     303930948 (x86/Linux, new codegen)
-                        # 2012-10-29:     298921816 (x86/Windows; increased range to 5%
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 658786936, 5)),
-                        # 17/11/2009:     434,845,560 (amd64/Linux)
-                        # 08/12/2009:     459,776,680 (amd64/Linux)
-                        # 17/05/2010:     519,377,728 (amd64/Linux)
-                        # 05/08/2011:     561,382,568 (amd64/OS X)
-                        # 16/07/2012:     589,168,872 (amd64/Linux)
-                        # 20/07/2012:     595,936,240 (amd64/Linux)
-                        # 23/08/2012:     606,230,880 (amd64/Linux)
-                        # 29/08/2012:     633,334,184 (amd64/Linux)
-                        #                 (^ new codegen)
-                        # 18/09/2012:     641,959,976 (amd64/Linux)
-                        # 19/10/2012:     661,832,592 (amd64/Linux)
-                        #                 (^ -fPIC turned on)
-                        # 23/10/2012:     642,594,312 (amd64/Linux)
-                        #                 (^ -fPIC turned off again)
-                        # 12/11/2012:     658,786,936 (amd64/Linux)
-                        #                 ( UNKNOWN REASON )
-                        # 17/1/13:        667,160,192 (x86_64/Linux)
-                        #                 (new demand analyser)
+     [compiler_stats_num_field('peak_megabytes_allocated',
+          [(wordsize(32), 18, 1),
+        # expected value: 14 (x86/Windows 17/05/10)
+        #                 15 (x86/OS X)
+        #                 19 (x86/OS X)
+           (wordsize(64), 25, 1)]),
+        # expected value: 28 (amd64/Linux)
+        # expected value: 34 (amd64/Linux)
+        # 2012-09-20      23 (amd64/Linux)
+        # 2012-10-03      25 (amd64/Linux if .hi exists)
+      compiler_stats_num_field('max_bytes_used',
+          [(wordsize(32), 6149572, 5),
+        # expected value: 6707308 (x86/OS X)
+        #                 5717704 (x86/Windows 17/05/10)
+        #                 6149572 (x86/Linux, 31/12/09)
+           (wordsize(64), 9000000, 20)]),
+               # looks like the peak is around 10M, but we're
+               # unlikely to GC exactly on the peak.
+               # varies quite a lot with CLEANUP and BINDIST,
+               # hence 10% range.
+      compiler_stats_num_field('bytes allocated',
+          [(wordsize(32), 303930948, 5),
+        # expected value: 215582916 (x86/Windows)
+        #                 221667908 (x86/OS X)
+        #                 274932264 (x86/Linux)
+        # 2012-10-08:     303930948 (x86/Linux, new codegen)
+        # 2012-10-29:     298921816 (x86/Windows; increased range to 5%
+           (wordsize(64), 658786936, 5)]),
+        # 17/11/2009:     434845560 (amd64/Linux)
+        # 08/12/2009:     459776680 (amd64/Linux)
+        # 17/05/2010:     519377728 (amd64/Linux)
+        # 05/08/2011:     561382568 (amd64/OS X)
+        # 16/07/2012:     589168872 (amd64/Linux)
+        # 20/07/2012:     595936240 (amd64/Linux)
+        # 23/08/2012:     606230880 (amd64/Linux)
+        # 29/08/2012:     633334184 (amd64/Linux)
+        #                 (^ new codegen)
+        # 18/09/2012:     641959976 (amd64/Linux)
+        # 19/10/2012:     661832592 (amd64/Linux)
+        #                 (^ -fPIC turned on)
+        # 23/10/2012:     642594312 (amd64/Linux)
+        #                 (^ -fPIC turned off again)
+        # 12/11/2012:     658786936 (amd64/Linux)
+        #                 ( UNKNOWN REASON )
+        # 17/1/13:        667160192 (x86_64/Linux)
+        #                 (new demand analyser)
       only_ways(['normal']),
 
       extra_hc_opts('-dcore-lint -static')
@@ -77,28 +74,27 @@ else:
    conf_3294 = skip
 
 test('T3294',
-     [when(wordsize(32),
-          compiler_stats_range_field('max_bytes_used', 17725476, 5)),
-                                   # expected value: 17725476 (x86/OS X)
-                                   #                 14593500 (Windows)
-      when(wordsize(64),
-          compiler_stats_range_field('max_bytes_used', 44894544, 15)),
-                                   # prev:           25753192 (amd64/Linux)
-                                   # 29/08/2012:     37724352 (amd64/Linux)
-                                   #  (increase due to new codegen, see #7198)
-                                   # 13/13/2012:     44894544 (amd64/Linux)
-                                   #  (reason for increase unknown)
-      when(wordsize(32),
-          compiler_stats_range_field('bytes allocated', 1373514844, 5)),
-                                   # previous:     815479800  (x86/Linux)
-                                   # (^ increase due to new codegen, see #7198)
-                                   # 2012-10-08:   1373514844 (x86/Linux)
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 2717327208, 5)),
-                                   # old:        1,357,587,088 (amd64/Linux)
-                                   # 29/08/2012: 2,961,778,696 (amd64/Linux)
-                                   # (^ increase due to new codegen, see #7198)
-                                   # 18/09/2012: 2,717,327,208 (amd64/Linux)
+     [
+      compiler_stats_num_field('max_bytes_used',
+          [(wordsize(32), 17725476, 5),
+        # expected value: 17725476 (x86/OS X)
+        #                 14593500 (Windows)
+           (wordsize(64), 44894544, 15)]),
+        # prev:           25753192 (amd64/Linux)
+        # 29/08/2012:     37724352 (amd64/Linux)
+        #  (increase due to new codegen, see #7198)
+        # 13/13/2012:     44894544 (amd64/Linux)
+        #  (reason for increase unknown)
+      compiler_stats_num_field('bytes allocated',
+          [(wordsize(32), 1373514844, 5),
+           # previous:     815479800  (x86/Linux)
+           # (^ increase due to new codegen, see #7198)
+           # 2012-10-08:  1373514844 (x86/Linux)
+           (wordsize(64), 2717327208, 5)]),
+            # old:        1357587088 (amd64/Linux)
+            # 29/08/2012: 2961778696 (amd64/Linux)
+            # (^ increase due to new codegen, see #7198)
+            # 18/09/2012: 2717327208 (amd64/Linux)
       conf_3294
       ],
      compile,
@@ -149,34 +145,27 @@ test('T4801',
 
 test('T3064',
      [# expect_broken( 3064 ),
-      # expected value: 14 (x86/Linux 28-06-2012):
-      when(wordsize(32),
-          compiler_stats_range_field('peak_megabytes_allocated', 14, 1)),
-
-      when(wordsize(64),
-          compiler_stats_range_field('peak_megabytes_allocated', 26, 1)),
-                                     # (amd64/Linux):            18
-                                     # (amd64/Linux) 2012-02-07: 26
-
-      # expected value: 56380288 (x86/Linux) (28/6/2011)
-      #                 111189536 (x86/Windows) (30/10/12)
-      when(wordsize(32),
-          compiler_stats_range_field('bytes allocated', 111189536, 10)),
-
-
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 224798696, 5)),
-                          # (amd64/Linux) (28/06/2011):  73259544
-                          # (amd64/Linux) (07/02/2013): 224798696
+      compiler_stats_num_field('peak_megabytes_allocated',
+          [(wordsize(32), 14, 1),
+        # expected value: 14 (x86/Linux 28-06-2012):
+           (wordsize(64), 26, 1)]),
+            # (amd64/Linux):            18
+            # (amd64/Linux) 2012-02-07: 26
 
-      # expected value: 2247016 (x86/Linux) (28/6/2011):
-      when(wordsize(32),
-          compiler_stats_range_field('max_bytes_used', 5511604, 20)),
+      compiler_stats_num_field('bytes allocated',
+          [(wordsize(32), 111189536, 10),
+         # expected value: 56380288 (x86/Linux) (28/6/2011)
+         #                111189536 (x86/Windows) (30/10/12)
+           (wordsize(64), 224798696, 5)]),
+            # (amd64/Linux) (28/06/2011):  73259544
+            # (amd64/Linux) (07/02/2013): 224798696
 
-      when(wordsize(64),
-          compiler_stats_range_field('max_bytes_used',  9819288, 5)),
-                 # (amd64/Linux, intree) (28/06/2011):  4032024
-                 # (amd64/Linux, intree) (07/02/2013):  9819288
+      compiler_stats_num_field('max_bytes_used',
+          [(wordsize(32), 5511604, 20),
+        # expected value: 2247016 (x86/Linux) (28/6/2011):
+           (wordsize(64), 9819288, 5)]),
+            # (amd64/Linux, intree) (28/06/2011):  4032024
+            # (amd64/Linux, intree) (07/02/2013):  9819288
        only_ways(['normal'])
       ],
      compile,
@@ -188,17 +177,14 @@ test('T4007',
      ['$MAKE -s --no-print-directory T4007'])
 
 test('T5030',
-     [
-      when(wordsize(32),
-          compiler_stats_range_field('bytes allocated', 259547660, 10)),
-                     # previous:    196457520
-                     # 2012-10-08:  259547660 (x86/Linux, new codegen)
-
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 602993184, 10)),
-            # Previously 530000000 (+/- 10%)
-            # 17/1/13:       602,993,184  (x86_64/Linux)
-            #                (new demand analyser)
+     [compiler_stats_num_field('bytes allocated',
+          [(wordsize(32), 259547660, 10),
+           # previous:    196457520
+           # 2012-10-08:  259547660 (x86/Linux, new codegen)
+           (wordsize(64), 602993184, 10)]),
+             # Previously 530000000 (+/- 10%)
+             # 17/1/13:   602993184  (x86_64/Linux)
+             #            (new demand analyser)
    
        only_ways(['normal'])
       ],
@@ -206,23 +192,21 @@ test('T5030',
      ['-fcontext-stack=300'])
 
 test('T5631',
-     [when(wordsize(32), # sample from x86/Linux
-          compiler_stats_range_field('bytes allocated', 392904228, 10)),
-      # expected value: 774,595,008 (amd64/Linux):
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 774595008, 5)),
+     [compiler_stats_num_field('bytes allocated',
+          [(wordsize(32), 392904228, 10),
+        # expected value: 392904228 (x86/Linux)
+           (wordsize(64), 774595008, 5)]),
+        # expected value: 774595008 (amd64/Linux):
        only_ways(['normal'])
       ],
      compile,
      [''])
 
 test('parsing001',
-     [# expected value: ?
-      when(wordsize(32),
-          compiler_stats_range_field('bytes allocated', 274000576, 10)),
-      # expected value: 587079016 (amd64/Linux):
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 587079016, 5)),
+     [compiler_stats_num_field('bytes allocated',
+          [(wordsize(32), 274000576, 10),
+           (wordsize(64), 587079016, 5)]),
+        # expected value: 587079016 (amd64/Linux)
        only_ways(['normal']),
       ],
      compile_fail, [''])
@@ -231,82 +215,76 @@ test('parsing001',
 test('T783',
      [ only_ways(['normal']),  # no optimisation for this one
       # expected value: 175,569,928 (x86/Linux)
-      when(wordsize(32),
-          compiler_stats_range_field('bytes allocated', 226907420, 10)),
-                           # 2012-10-08: 226907420 (x86/Linux)
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 640324528, 10)),
-                           # prev:       349,263,216 (amd64/Linux)
-                           # 07/08/2012: 384,479,856 (amd64/Linux)
-                           # 29/08/2012: 436,927,840 (amd64/Linux)
-                           # 12/11/2012: 640,324,528 (amd64/Linux)
-                           #   (OldCmm removed: not sure why this got worse, the
-                           #    other perf tests remained about the same)
+      compiler_stats_num_field('bytes allocated',
+          [(wordsize(32), 226907420, 10),
+            # 2012-10-08: 226907420 (x86/Linux)
+           (wordsize(64), 640324528, 10)]),
+            # prev:       349263216 (amd64/Linux)
+            # 07/08/2012: 384479856 (amd64/Linux)
+            # 29/08/2012: 436927840 (amd64/Linux)
+            # 12/11/2012: 640324528 (amd64/Linux)
+            #   (OldCmm removed: not sure why this got worse, the
+            #    other perf tests remained about the same)
       extra_hc_opts('-static')
       ],
       compile,[''])
 
 test('T5321Fun',
      [ only_ways(['normal']),  # no optimisation for this one
-      # sample from x86/Linux
-      when(wordsize(32),
-          compiler_stats_range_field('bytes allocated', 344416344, 10)),
-                                         # prev:       300000000
-                                         # 2012-10-08: 344416344
-                                         #  (increase due to new codegen)
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 713385808, 10))
-                                         # prev:       585,521,080
-                                         # 29/08/2012: 713,385,808
-                                         #  (increase due to new codegen)
+       compiler_stats_num_field('bytes allocated',
+           [(wordsize(32), 344416344, 10),
+             # prev:       300000000
+             # 2012-10-08: 344416344 x86/Linux
+             #  (increase due to new codegen)
+            (wordsize(64), 713385808, 10)])
+             # prev:       585521080
+             # 29/08/2012: 713385808
+             #  (increase due to new codegen)
       ],
       compile,[''])
 
 test('T5321FD',
      [ only_ways(['normal']),  # no optimisation for this one
-      when(wordsize(32),
-          compiler_stats_range_field('bytes allocated', 240302920, 10)),
-                                         # prev:       213380256
-                                         # 2012-10-08: 240302920 (x86/Linux)
-                                         #  (increase due to new codegen)
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 492905640, 10))
-                                         # prev:       418,306,336
-                                         # 29/08/2012: 492,905,640
-                                         #  (increase due to new codegen)
+      compiler_stats_num_field('bytes allocated',
+          [(wordsize(32), 240302920, 10),
+            # prev:       213380256
+            # 2012-10-08: 240302920 (x86/Linux)
+            #  (increase due to new codegen)
+           (wordsize(64), 492905640, 10)])
+            # prev:       418306336
+            # 29/08/2012: 492905640
+            #  (increase due to new codegen)
       ],
       compile,[''])
 
 test('T5642',
      [ only_ways(['normal']),
-      when(wordsize(32), # sample from x86/Linux
-          compiler_stats_range_field('bytes allocated',  650000000, 10)),
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 1300000000, 10))
+       compiler_stats_num_field('bytes allocated',
+           [(wordsize(32), 650000000, 10),
+                     # sample from x86/Linux
+            (wordsize(64), 1300000000, 10)])
       ],
       compile,['-O'])
 
 test('T5837',
      [ only_ways(['normal']),
-      when(wordsize(32), # sample from x86/Linux
-          compiler_stats_range_field('bytes allocated', 40000000, 10)),
-
-      # sample: 3926235424 (amd64/Linux, 15/2/2012)
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 81879216, 10))
-	  				   # 2012-10-02 81879216
-                                           # 2012-09-20 87254264 amd64/Linux
+      compiler_stats_num_field('bytes allocated',
+          [(wordsize(32), 40000000, 10),
+          # sample from x86/Linux
+           (wordsize(64), 81879216, 10)])
+              # sample: 3926235424 (amd64/Linux, 15/2/2012)
+             # 2012-10-02 81879216
+             # 2012-09-20 87254264 amd64/Linux
       ],
       compile_fail,['-fcontext-stack=50'])
 
 test('T6048',
      [ only_ways(['optasm']),
-      when(wordsize(32), # sample from x86/Linux
-          compiler_stats_range_field('bytes allocated', 48887164, 10)),
-                                           # prev:       38000000
-                                           # 2012-10-08: 48887164 (x86/Linux)
-      when(wordsize(64),
-          compiler_stats_range_field('bytes allocated', 97247032, 10))
-                                           # 18/09/2012 97247032 amd64/Linux
+      compiler_stats_num_field('bytes allocated',
+          [(wordsize(32), 48887164, 10),
+            # prev:       38000000 (x86/Linux)
+            # 2012-10-08: 48887164 (x86/Linux)
+           (wordsize(64), 97247032, 10)])
+             # 18/09/2012 97247032 amd64/Linux
       ],
       compile,[''])
diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T
index 14d972783..a2ffd0be4 100644
--- a/tests/perf/haddock/all.T
+++ b/tests/perf/haddock/all.T
@@ -1,107 +1,98 @@
 
 test('haddock.base',
      [unless_in_tree_compiler(skip)
-     ,when(wordsize(64),
-          stats_range_field('peak_megabytes_allocated', 274, 10))
-                                        # 2012-08-14: 240 (amd64/Linux)
-                                        # 2012-09-18: 237 (amd64/Linux)
-                                        # 2012-11-12: 249 (amd64/Linux)
-                                        # 2013-01-29: 274 (amd64/Linux)
-     ,when(wordsize(32),
-          stats_range_field('peak_megabytes_allocated', 113, 1))
-                                        # 2012-08-14: 144 (x86/OSX)
-                                        # 2012-10-30: 113 (x86/Windows)
-     ,when(wordsize(64),
-          stats_range_field('max_bytes_used', 96022312, 10))
-                                # 2012-08-14: 87374568 (amd64/Linux)
-                                # 2012-08-21: 86428216 (amd64/Linux)
-                                # 2012-09-20: 84794136 (amd64/Linux)
-                                # 2012-11-12: 87265136 (amd64/Linux)
-                                # 2013-01-29: 96022312 (amd64/Linux)
-     ,when(wordsize(32),
-          stats_range_field('max_bytes_used', 45574928, 1))
-                                # 2012-08-14: 45574928 (x86/OSX)
-     ,when(wordsize(64),
-          stats_range_field('bytes allocated', 6064874536, 2))
-                                 # 2012-08-14: 5920822352 (amd64/Linux)
-                                 # 2012-09-20: 5829972376 (amd64/Linux)
-                                 # 2012-10-08: 5902601224 (amd64/Linux)
-                                 # 2013-01-17: 6064874536 (x86_64/Linux)
-     ,when(wordsize(32),
-          stats_range_field('bytes allocated', 2955470952, 1))
-                                 # 2012-08-14: 3046487920 (x86/OSX)
-                                 # 2012-10-30: 2955470952 (x86/Windows)
+     ,stats_num_field('peak_megabytes_allocated',
+          [(wordsize(64), 274, 10)
+            # 2012-08-14: 240 (amd64/Linux)
+            # 2012-09-18: 237 (amd64/Linux)
+            # 2012-11-12: 249 (amd64/Linux)
+            # 2013-01-29: 274 (amd64/Linux)
+          ,(wordsize(32), 113, 1)])
+            # 2012-08-14: 144 (x86/OSX)
+            # 2012-10-30: 113 (x86/Windows)
+     ,stats_num_field('max_bytes_used',
+          [(wordsize(64), 96022312, 10)
+            # 2012-08-14: 87374568 (amd64/Linux)
+            # 2012-08-21: 86428216 (amd64/Linux)
+            # 2012-09-20: 84794136 (amd64/Linux)
+            # 2012-11-12: 87265136 (amd64/Linux)
+            # 2013-01-29: 96022312 (amd64/Linux)
+          ,(wordsize(32), 45574928, 1)])
+            # 2012-08-14: 45574928 (x86/OSX)
+     ,stats_num_field('bytes allocated',
+          [(wordsize(64), 6064874536, 2)
+            # 2012-08-14: 5920822352 (amd64/Linux)
+            # 2012-09-20: 5829972376 (amd64/Linux)
+            # 2012-10-08: 5902601224 (amd64/Linux)
+            # 2013-01-17: 6064874536 (x86_64/Linux)
+          ,(wordsize(32), 2955470952, 1)])
+            # 2012-08-14: 3046487920 (x86/OSX)
+            # 2012-10-30: 2955470952 (x86/Windows)
       ],
      stats,
      ['../../../../libraries/base/dist-install/doc/html/base/base.haddock.t'])
 
 test('haddock.Cabal',
      [unless_in_tree_compiler(skip)
-     ,when(wordsize(64),
-          stats_range_field('peak_megabytes_allocated', 217, 10))
-                             # 2012-08-14: 202 (amd64/Linux)
-                             # 2012-08-29: 211 (amd64/Linux, new codegen)
-                             # 2012-09-20: 227 (amd64/Linux)
-                             # 2012-10-08: 217 (amd64/Linux)
-     ,when(wordsize(32),
-          stats_range_field('peak_megabytes_allocated', 83, 1))
-                                        # 2012-08-14: 116 (x86/OSX)
-                                        # 2012-10-30: 83 (x86/Windows)
-     ,when(wordsize(64),
-          stats_range_field('max_bytes_used', 80590280, 15))
-                             # 2012-08-14: 74119424 (amd64/Linux)
-                             # 2012-08-29: 77992512 (amd64/Linux, new codegen)
-                             # 2012-10-02: 91341568 (amd64/Linux)
-                             # 2012-10-08: 80590280 (amd64/Linux)
-     ,when(wordsize(32),
-          stats_range_field('max_bytes_used', 44224896, 5))
-                             # 2012-08-14: 47461532 (x86/OSX)
-                             # 2012-10-30: 44224896 (x86/Windows insreased range to 5%)
-     ,when(wordsize(64),
-          stats_range_field('bytes allocated', 3373401360, 2))
-                             # 2012-08-14: 3255435248 (amd64/Linux)
-                             # 2012-08-29: 3324606664 (amd64/Linux, new codegen)
-                             # 2012-10-08: 3373401360 (amd64/Linux)
-     ,when(wordsize(32),
-          stats_range_field('bytes allocated', 1733638168, 1))
-                             # 2012-08-14: 1648610180 (x86/OSX)
-                             # 2012-10-30: 1733638168 (x86/Windows)
+     ,stats_num_field('peak_megabytes_allocated',
+          [(wordsize(64), 217, 10)
+            # 2012-08-14: 202 (amd64/Linux)
+            # 2012-08-29: 211 (amd64/Linux, new codegen)
+            # 2012-09-20: 227 (amd64/Linux)
+            # 2012-10-08: 217 (amd64/Linux)
+          ,(wordsize(32), 83, 1)])
+           # 2012-08-14: 116 (x86/OSX)
+           # 2012-10-30:  83 (x86/Windows)
+     ,stats_num_field('max_bytes_used',
+          [(wordsize(64), 80590280, 15)
+            # 2012-08-14: 74119424 (amd64/Linux)
+            # 2012-08-29: 77992512 (amd64/Linux, new codegen)
+            # 2012-10-02: 91341568 (amd64/Linux)
+            # 2012-10-08: 80590280 (amd64/Linux)
+          ,(wordsize(32), 44224896, 5)])
+            # 2012-08-14: 47461532 (x86/OSX)
+            # 2012-10-30: 44224896 (x86/Windows insreased range to 5%)
+     ,stats_num_field('bytes allocated',
+          [(wordsize(64), 3373401360, 2)
+            # 2012-08-14: 3255435248 (amd64/Linux)
+            # 2012-08-29: 3324606664 (amd64/Linux, new codegen)
+            # 2012-10-08: 3373401360 (amd64/Linux)
+          ,(wordsize(32), 1733638168, 1)])
+            # 2012-08-14: 1648610180 (x86/OSX)
+            # 2012-10-30: 1733638168 (x86/Windows)
       ],
      stats,
      ['../../../../libraries/Cabal/Cabal/dist-install/doc/html/Cabal/Cabal.haddock.t'])
 
 test('haddock.compiler',
      [unless_in_tree_compiler(skip)
-     ,when(wordsize(64),
-          stats_range_field('peak_megabytes_allocated', 1240, 10))
-                                        # 2012-08-14: 1203 (amd64/Linux)
-                                        # 2012-08-21: 1199 (amd64/Linux)
-                                        # 2012-09-20: 1228 (amd64/Linux)
-                                        # 2012-10-08: 1240 (amd64/Linux)
-     ,when(wordsize(32),
-          stats_range_field('peak_megabytes_allocated', 606, 1))
-                                        # 2012-08-14: 631 (x86/OSX)
-                                        # 2012-10-30: 606 (x86/Windows)
-     ,when(wordsize(64),
-          stats_range_field('max_bytes_used', 420105120, 10))
-                                # 2012-08-14: 428775544 (amd64/Linux)
-                                # 2012-09-20: 437618008 (amd64/Linux)
-                                # 2012-10-08: 442768280 (amd64/Linux)
-                                # 2012-11-12: 420105120 (amd64/Linux)
-     ,when(wordsize(32),
-          stats_range_field('max_bytes_used', 220847924, 1))
-                                # 2012-08-14: 231064920 (x86/OSX)
-                                # 2012-10-30: 220847924 (x86/Windows)
-     ,when(wordsize(64),
-          stats_range_field('bytes allocated', 25990254632, 10))
-                              # 2012-08-14: 26,070,600,504 (amd64/Linux)
-                              # 2012-08-29: 26,353,100,288 (amd64/Linux, new CG)
-                              # 2012-09-18: 26,882,813,032 (amd64/Linux)
-                              # 2012-11-12: 25,990,254,632 (amd64/Linux)
-     ,when(wordsize(32),
-          stats_range_field('bytes allocated', 13773051312, 1))
-                                 # 2012-08-14: 13471797488 (x86/OSX)
-                                 # 2012-10-30: 13773051312 (x86/Windows)
+     ,stats_num_field('peak_megabytes_allocated',
+          [(wordsize(64), 1240, 10)
+            # 2012-08-14: 1203 (amd64/Linux)
+            # 2012-08-21: 1199 (amd64/Linux)
+            # 2012-09-20: 1228 (amd64/Linux)
+            # 2012-10-08: 1240 (amd64/Linux)
+          ,(wordsize(32), 606, 1)])
+            # 2012-08-14: 631 (x86/OSX)
+            # 2012-10-30: 606 (x86/Windows)
+     ,stats_num_field('max_bytes_used',
+          [(wordsize(64), 420105120, 10)
+            # 2012-08-14: 428775544 (amd64/Linux)
+            # 2012-09-20: 437618008 (amd64/Linux)
+            # 2012-10-08: 442768280 (amd64/Linux)
+            # 2012-11-12: 420105120 (amd64/Linux)
+          ,(wordsize(32), 220847924, 1)])
+            # 2012-08-14: 231064920 (x86/OSX)
+            # 2012-10-30: 220847924 (x86/Windows)
+     ,stats_num_field('bytes allocated',
+          [(wordsize(64), 25990254632, 10)
+            # 2012-08-14: 26070600504 (amd64/Linux)
+            # 2012-08-29: 26353100288 (amd64/Linux, new CG)
+            # 2012-09-18: 26882813032 (amd64/Linux)
+            # 2012-11-12: 25990254632 (amd64/Linux)
+          ,(wordsize(32), 13773051312, 1)])
+            # 2012-08-14: 13471797488 (x86/OSX)
+            # 2012-10-30: 13773051312 (x86/Windows)
       ],
      stats,
      ['../../../../compiler/stage2/doc/html/ghc/ghc.haddock.t'])
diff --git a/tests/perf/space_leaks/all.T b/tests/perf/space_leaks/all.T
index dcc1f0865..f3260c2eb 100644
--- a/tests/perf/space_leaks/all.T
+++ b/tests/perf/space_leaks/all.T
@@ -4,17 +4,17 @@ test('space_leak_001',
      # Now it's: 3 (amd64/Linux)
      #           4 (x86/OS X)
      #           5 (x86/Linux)
-     [stats_range_field('peak_megabytes_allocated', 4, 1),
-      stats_range_field('max_bytes_used', 440000, 10),
-                        # expected value: 440224 (amd64/Linux)
-                        #                 417016 (x86/OS X)
-                        #                 415672 (x86/Windows)
-                        #                 481456 (unreg amd64/Linux)
-      stats_range_field('bytes allocated', 9079316016, 1),
-                           # expected value: 9079316016 (amd64/Linux)
-                           #                 9331570416 (x86/Linux)
-                           #                 9329073952 (x86/OS X)
-                           #                 9327959840 (x86/Windows)
+     [stats_num_field('peak_megabytes_allocated', (4, 1)),
+      stats_num_field('max_bytes_used', (440000, 10)),
+                       # expected value: 440224 (amd64/Linux)
+                       #                 417016 (x86/OS X)
+                       #                 415672 (x86/Windows)
+                       #                 481456 (unreg amd64/Linux)
+      stats_num_field('bytes allocated', (9079316016, 1)),
+                        # expected value: 9079316016 (amd64/Linux)
+                        #                 9331570416 (x86/Linux)
+                        #                 9329073952 (x86/OS X)
+                        #                 9327959840 (x86/Windows)
       omit_ways(['profasm','profthreaded','threaded1','threaded2'])
       ],
      compile_and_run,
@@ -23,7 +23,7 @@ test('space_leak_001',
 test('T4334',
      # Test for a space leak in Data.List.lines (fixed with #4334)
      [extra_run_opts('1000000 2 t'),
-      stats_range_field('peak_megabytes_allocated', 2, 0),
+      stats_num_field('peak_megabytes_allocated', (2, 0)),
       # prof ways don't work well with +RTS -V0
       omit_ways(['profasm','profthreaded'])
       ],
@@ -32,7 +32,7 @@ test('T4334',
 test('T2762',
      [# peak_megabytes_allocated is 2 with 7.0.2.
       # Was 57 with 6.12.3.
-      stats_range_field('peak_megabytes_allocated', 2, 0),
+      stats_num_field('peak_megabytes_allocated', (2, 0)),
       only_ways(['normal']),
       extra_clean(['T2762A.hi', 'T2762A.o'])],
      compile_and_run, ['-O'])
-- 
GitLab


From 6fc5493f84f872b6a7c0ced9095ed821a3de58a7 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 8 Feb 2013 13:36:22 +0000
Subject: [PATCH 115/223] Remove unused helper functions

---
 driver/testlib.py | 6 ------
 1 file changed, 6 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index aa601f786..77b05ed99 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -269,9 +269,6 @@ def _stats_num_field( name, opts, field, expecteds ):
         (expected, dev) = expecteds
         opts.stats_range_fields[field] = (expected, dev)
 
-def stats_range_field( field, expected, dev ):
-    return stats_num_field( field, [(True, expected, dev)] )
-
 def compiler_stats_num_field( field, expecteds ):
     return lambda name, opts, f=field, e=expecteds: _compiler_stats_num_field(name, opts, f, e);
 
@@ -286,9 +283,6 @@ def _compiler_stats_num_field( name, opts, field, expecteds ):
 
     framework_fail(name, 'numfield-no-expected', 'No expected value found for ' + field + ' in num_field check')
 
-def compiler_stats_range_field( field, expected, dev ):
-    return compiler_stats_num_field( field, [(True, expected, dev)] )
-
 # -----
 
 def skip_if_no_ghci(name, opts):
-- 
GitLab


From 48d6d779022a594d5f433ba0500eae2182b32981 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Sat, 9 Feb 2013 12:34:51 +0000
Subject: [PATCH 116/223] Wibbles to test

---
 tests/typecheck/should_fail/AssocTyDef02.hs     |  3 ++-
 tests/typecheck/should_fail/AssocTyDef02.stderr | 12 ++++++------
 2 files changed, 8 insertions(+), 7 deletions(-)

diff --git a/tests/typecheck/should_fail/AssocTyDef02.hs b/tests/typecheck/should_fail/AssocTyDef02.hs
index 8f22d4ce1..5db82037b 100644
--- a/tests/typecheck/should_fail/AssocTyDef02.hs
+++ b/tests/typecheck/should_fail/AssocTyDef02.hs
@@ -3,5 +3,6 @@ module AssocTyDef02 where
 
 class Cls a where
     type Typ a
-    type Typ b = Int
+    type Typ [b] = Int
       -- Default is not parametric in type class params
+
diff --git a/tests/typecheck/should_fail/AssocTyDef02.stderr b/tests/typecheck/should_fail/AssocTyDef02.stderr
index 920ae0acd..2d1b43952 100644
--- a/tests/typecheck/should_fail/AssocTyDef02.stderr
+++ b/tests/typecheck/should_fail/AssocTyDef02.stderr
@@ -1,6 +1,6 @@
-
-AssocTyDef02.hs:6:10:
-    Type indexes must match class instance head
-    Found `b' but expected `a'
-    In the type synonym instance default declaration for `Typ'
-    In the class declaration for `Cls'
+
+AssocTyDef02.hs:6:10:
+    Type indexes must match class instance head
+    Found `[b]' but expected `a'
+    In the type synonym instance default declaration for `Typ'
+    In the class declaration for `Cls'
-- 
GitLab


From 67e626eae4b0820539b75c8cdabab9debe3b4059 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 10 Feb 2013 16:45:24 +0000
Subject: [PATCH 117/223] Update 32bit perf results for the haddock tests

---
 tests/perf/haddock/all.T | 51 +++++++++++++++++++++++++++++-----------
 1 file changed, 37 insertions(+), 14 deletions(-)

diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T
index a2ffd0be4..baeb1801a 100644
--- a/tests/perf/haddock/all.T
+++ b/tests/perf/haddock/all.T
@@ -7,9 +7,12 @@ test('haddock.base',
             # 2012-09-18: 237 (amd64/Linux)
             # 2012-11-12: 249 (amd64/Linux)
             # 2013-01-29: 274 (amd64/Linux)
-          ,(wordsize(32), 113, 1)])
+          ,(platform('i386-unknown-mingw32'), 133, 1)
+            # 2013-02-10:                     133 (x86/Windows)
+          ,(wordsize(32), 139, 1)])
             # 2012-08-14: 144 (x86/OSX)
             # 2012-10-30: 113 (x86/Windows)
+            # 2013-02-10: 139 (x86/OSX)
      ,stats_num_field('max_bytes_used',
           [(wordsize(64), 96022312, 10)
             # 2012-08-14: 87374568 (amd64/Linux)
@@ -17,17 +20,22 @@ test('haddock.base',
             # 2012-09-20: 84794136 (amd64/Linux)
             # 2012-11-12: 87265136 (amd64/Linux)
             # 2013-01-29: 96022312 (amd64/Linux)
-          ,(wordsize(32), 45574928, 1)])
-            # 2012-08-14: 45574928 (x86/OSX)
+          ,(platform('i386-unknown-mingw32'), 47988488, 1)
+            # 2013-02-10:                     47988488 (x86/Windows)
+          ,(wordsize(32), 52237984, 1)])
+            # 2013-02-10: 52237984 (x86/OSX)
      ,stats_num_field('bytes allocated',
           [(wordsize(64), 6064874536, 2)
             # 2012-08-14: 5920822352 (amd64/Linux)
             # 2012-09-20: 5829972376 (amd64/Linux)
             # 2012-10-08: 5902601224 (amd64/Linux)
             # 2013-01-17: 6064874536 (x86_64/Linux)
-          ,(wordsize(32), 2955470952, 1)])
+          ,(platform('i386-unknown-mingw32'), 3358693084, 1)
+            # 2013-02-10:                     3358693084 (x86/Windows)
+          ,(wordsize(32), 3146596848, 1)])
             # 2012-08-14: 3046487920 (x86/OSX)
             # 2012-10-30: 2955470952 (x86/Windows)
+            # 2013-02-10: 3146596848 (x86/OSX)
       ],
      stats,
      ['../../../../libraries/base/dist-install/doc/html/base/base.haddock.t'])
@@ -40,26 +48,33 @@ test('haddock.Cabal',
             # 2012-08-29: 211 (amd64/Linux, new codegen)
             # 2012-09-20: 227 (amd64/Linux)
             # 2012-10-08: 217 (amd64/Linux)
-          ,(wordsize(32), 83, 1)])
+          ,(platform('i386-unknown-mingw32'), 116, 1)
+            # 2012-10-30:                      83 (x86/Windows)
+            # 2013-02-10:                     116 (x86/Windows)
+          ,(wordsize(32), 89, 1)])
            # 2012-08-14: 116 (x86/OSX)
-           # 2012-10-30:  83 (x86/Windows)
+           # 2013-02-10:  89 (x86/Windows)
      ,stats_num_field('max_bytes_used',
           [(wordsize(64), 80590280, 15)
             # 2012-08-14: 74119424 (amd64/Linux)
             # 2012-08-29: 77992512 (amd64/Linux, new codegen)
             # 2012-10-02: 91341568 (amd64/Linux)
             # 2012-10-08: 80590280 (amd64/Linux)
-          ,(wordsize(32), 44224896, 5)])
+          ,(platform('i386-unknown-mingw32'), 44224896, 1)
+            # 2012-10-30:                     44224896 (x86/Windows)
+          ,(wordsize(32), 46563344, 1)])
             # 2012-08-14: 47461532 (x86/OSX)
-            # 2012-10-30: 44224896 (x86/Windows insreased range to 5%)
+            # 2013-02-10: 46563344 (x86/OSX)
      ,stats_num_field('bytes allocated',
           [(wordsize(64), 3373401360, 2)
             # 2012-08-14: 3255435248 (amd64/Linux)
             # 2012-08-29: 3324606664 (amd64/Linux, new codegen)
             # 2012-10-08: 3373401360 (amd64/Linux)
+          ,(platform('i386-unknown-mingw32'), 1906532680, 1)
+            # 2012-10-30:                     1733638168 (x86/Windows)
+            # 2013-02-10:                     1906532680 (x86/Windows)
           ,(wordsize(32), 1733638168, 1)])
             # 2012-08-14: 1648610180 (x86/OSX)
-            # 2012-10-30: 1733638168 (x86/Windows)
       ],
      stats,
      ['../../../../libraries/Cabal/Cabal/dist-install/doc/html/Cabal/Cabal.haddock.t'])
@@ -72,27 +87,35 @@ test('haddock.compiler',
             # 2012-08-21: 1199 (amd64/Linux)
             # 2012-09-20: 1228 (amd64/Linux)
             # 2012-10-08: 1240 (amd64/Linux)
-          ,(wordsize(32), 606, 1)])
+          ,(platform('i386-unknown-mingw32'), 653, 1)
+            # 2012-10-30:                     606 (x86/Windows)
+            # 2013-02-10:                     653 (x86/Windows)
+          ,(wordsize(32), 663, 1)])
             # 2012-08-14: 631 (x86/OSX)
-            # 2012-10-30: 606 (x86/Windows)
+            # 2013-02-10: 663 (x86/OSX)
      ,stats_num_field('max_bytes_used',
           [(wordsize(64), 420105120, 10)
             # 2012-08-14: 428775544 (amd64/Linux)
             # 2012-09-20: 437618008 (amd64/Linux)
             # 2012-10-08: 442768280 (amd64/Linux)
             # 2012-11-12: 420105120 (amd64/Linux)
-          ,(wordsize(32), 220847924, 1)])
+          ,(platform('i386-unknown-mingw32'), 238529512, 1)
+            # 2012-10-30:                     220847924 (x86/Windows)
+            # 2013-02-10:                     238529512 (x86/Windows)
+          ,(wordsize(32), 241785276, 1)])
             # 2012-08-14: 231064920 (x86/OSX)
-            # 2012-10-30: 220847924 (x86/Windows)
+            # 2013-02-10: 241785276 (x86/Windows)
      ,stats_num_field('bytes allocated',
           [(wordsize(64), 25990254632, 10)
             # 2012-08-14: 26070600504 (amd64/Linux)
             # 2012-08-29: 26353100288 (amd64/Linux, new CG)
             # 2012-09-18: 26882813032 (amd64/Linux)
             # 2012-11-12: 25990254632 (amd64/Linux)
+          ,(platform('i386-unknown-mingw32'), 14925262356, 1)
+            # 2012-10-30:                     13773051312 (x86/Windows)
+            # 2013-02-10:                     14925262356 (x86/Windows)
           ,(wordsize(32), 13773051312, 1)])
             # 2012-08-14: 13471797488 (x86/OSX)
-            # 2012-10-30: 13773051312 (x86/Windows)
       ],
      stats,
      ['../../../../compiler/stage2/doc/html/ghc/ghc.haddock.t'])
-- 
GitLab


From ceabf35eac4e6cb863e8456a3cf95db8e1fa0974 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 10 Feb 2013 16:48:24 +0000
Subject: [PATCH 118/223] Rearrange the summary output

In particular, the 3 values you most need to care about (framework
failures, unexpected passes, unexpected failures) are now together
in a block.
---
 driver/testlib.py | 34 ++++++++++++++++++----------------
 1 file changed, 18 insertions(+), 16 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 77b05ed99..e77c7d9c4 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -2217,25 +2217,27 @@ def summary(t, file):
 
     file.write('\n')
     printUnexpectedTests(file, [t.unexpected_passes, t.unexpected_failures])
-    file.write('OVERALL SUMMARY for test run started at ' \
-               + t.start_time + '\n'\
-               + string.rjust(`t.total_tests`, 8) \
-               + ' total tests, which gave rise to\n' \
-               + string.rjust(`t.total_test_cases`, 8) \
-               + ' test cases, of which\n' \
-               + string.rjust(`t.n_framework_failures`, 8) \
-               + ' caused framework failures\n' \
+    file.write('OVERALL SUMMARY for test run started at '
+               + t.start_time + '\n'
+               + string.rjust(`t.total_tests`, 8)
+               + ' total tests, which gave rise to\n'
+               + string.rjust(`t.total_test_cases`, 8)
+               + ' test cases, of which\n'
                + string.rjust(`t.n_tests_skipped`, 8)
-               + ' were skipped\n\n' \
-               + string.rjust(`t.n_expected_passes`, 8)
-               + ' expected passes\n' \
+               + ' were skipped\n'
+               + '\n'
                + string.rjust(`t.n_missing_libs`, 8)
-               + ' had missing libraries\n' \
-               + string.rjust(`t.n_expected_failures`, 8) \
-               + ' expected failures\n' \
-               + string.rjust(`t.n_unexpected_passes`, 8) \
+               + ' had missing libraries\n'
+               + string.rjust(`t.n_expected_passes`, 8)
+               + ' expected passes\n'
+               + string.rjust(`t.n_expected_failures`, 8)
+               + ' expected failures\n'
+               + '\n'
+               + string.rjust(`t.n_framework_failures`, 8)
+               + ' caused framework failures\n'
+               + string.rjust(`t.n_unexpected_passes`, 8)
                + ' unexpected passes\n'
-               + string.rjust(`t.n_unexpected_failures`, 8) \
+               + string.rjust(`t.n_unexpected_failures`, 8)
                + ' unexpected failures\n'
                + '\n')
 
-- 
GitLab


From 85825135675298e34bfd1b30c6d8e67c3008d39a Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 10 Feb 2013 17:05:21 +0000
Subject: [PATCH 119/223] More 32-bit perf updates

---
 tests/perf/should_run/all.T | 42 +++++++++++++++++++++++++------------
 1 file changed, 29 insertions(+), 13 deletions(-)

diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 5b17e452c..ef9bce8ab 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -14,9 +14,13 @@ test('T3586',
      ['-O'])
 
 test('T4830',
-     [stats_num_field('bytes allocated', (99264, 1)),
-             # (amd64/Linux):            127000
-             # (amd64/Linux) 2013-02-07:  99264
+     [stats_num_field('bytes allocated',
+          [(wordsize(64), 99264, 1),
+           #             127000 (amd64/Linux)
+           # 2013-02-07:  99264 (amd64/Linux)
+           (wordsize(32), 70646, 2)]),
+           # 2013-02-10:  69744 (x86/Windows)
+           # 2013-02-10:  71548 (x86/OSX)
       only_ways(['normal'])
       ],
      compile_and_run,
@@ -30,9 +34,13 @@ test('T3245', normal, compile_and_run, ['-O'])
 test('lazy-bs-alloc',
      [stats_num_field('peak_megabytes_allocated', (2, 1)),
                                  # expected value: 2 (amd64/Linux)
-      stats_num_field('bytes allocated', (429744, 1)),
-             # (amd64/Linux):             489776
-             # (amd64/Linux) 2013-02-07:  429744
+      stats_num_field('bytes allocated',
+          [(wordsize(64), 429744, 1),
+            #             489776 (amd64/Linux)
+            # 2013-02-07: 429744 (amd64/Linux)
+           (wordsize(32), 417738, 1)]),
+            # 2013-02-10: 421296 (x86/Windows)
+            # 2013-02-10: 414180 (x86/OSX)
       only_ways(['normal']),
       extra_run_opts('../../numeric/should_run/arith011.stdout'),
       ignore_output
@@ -187,8 +195,10 @@ test('T5237',
 
 test('T5536',
      [stats_num_field('bytes allocated',
-                      [(wordsize(32), 1246287228, 5),
-                    # expected value: 1246287228 (i386/Linux)
+                      [(wordsize(32), 446260520, 1),
+                                   # 1246287228 (i386/Linux)
+                                    # 446328556 (i386/Windows)
+                                    # 446192484 (i386/OSX)
                        (wordsize(64), 892399040, 5)]),
                    # expected value: 2492589480 (amd64/Linux)
                    # 17/1/13:         892399040 (x86_64/Linux)
@@ -218,8 +228,10 @@ test('T7257',
 
 test('Conversions',
      [stats_num_field('bytes allocated',
-                      [(wordsize(32), 55316, 5),
-                        # 2012-12-18: Guessed 64-bit value / 2
+                      [(wordsize(32), 78374, 2),
+                        # 2012-12-18: 55316 Guessed 64-bit value / 2
+                        # 2013-02-10: 77472 (x86/OSX)
+                        # 2013-02-10: 79276 (x86/Windows)
                        (wordsize(64), 110632, 5)]),
                         # 2012-12-18: 109608 (amd64/OS X)
 
@@ -231,9 +243,13 @@ test('T7507', omit_ways(['ghci']), compile_and_run, ['-O'])
 # For 7507, stack overflow is the bad case
 
 test('T7436',
-     [stats_num_field('max_bytes_used', (60360, 1)),
-          # (amd64/Linux):              127000
-          # (amd64/Linux) 2013-02-07:    60360
+     [stats_num_field('max_bytes_used',
+          [(wordsize(64), 60360, 1),
+           #             127000 (amd64/Linux)
+           # 2013-02-07:  60360 (amd64/Linux)
+           (wordsize(32), 58434, 1)]),
+            # 2013-02-10: 58032 (x86/Windows)
+            # 2013-02-10: 58836 (x86/OSX)
       only_ways(['normal'])
       ],
      compile_and_run,
-- 
GitLab


From 6478fc6a1c3cc02e44b3198f7447c074eb43a89b Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 10 Feb 2013 17:33:53 +0000
Subject: [PATCH 120/223] More 32bit perf test bound updates

---
 tests/perf/compiler/all.T | 102 +++++++++++++++++++++-----------------
 1 file changed, 57 insertions(+), 45 deletions(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 20b755bbe..9260df10d 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -7,51 +7,57 @@ setTestOpts(no_lint)
 
 test('T1969',
      [compiler_stats_num_field('peak_megabytes_allocated',
-          [(wordsize(32), 18, 1),
-        # expected value: 14 (x86/Windows 17/05/10)
-        #                 15 (x86/OS X)
-        #                 19 (x86/OS X)
+          [(wordsize(32), 14, 1),
+             # 2010-05-17 14 (x86/Windows)
+             #            15 (x86/OS X)
+             #            19 (x86/OS X)
+             # 2013-02-10 13 (x86/Windows)
+             # 2013-02-10 14 (x86/OSX)
            (wordsize(64), 25, 1)]),
-        # expected value: 28 (amd64/Linux)
-        # expected value: 34 (amd64/Linux)
-        # 2012-09-20      23 (amd64/Linux)
-        # 2012-10-03      25 (amd64/Linux if .hi exists)
+             #            28 (amd64/Linux)
+             #            34 (amd64/Linux)
+             # 2012-09-20 23 (amd64/Linux)
+             # 2012-10-03 25 (amd64/Linux if .hi exists)
       compiler_stats_num_field('max_bytes_used',
-          [(wordsize(32), 6149572, 5),
-        # expected value: 6707308 (x86/OS X)
-        #                 5717704 (x86/Windows 17/05/10)
-        #                 6149572 (x86/Linux, 31/12/09)
+          [(platform('i386-unknown-mingw32'), 5159748, 1),
+                                 # 2010-05-17 5717704 (x86/Windows)
+                                 # 2013-02-10 5159748 (x86/Windows)
+           (wordsize(32), 6149572, 1),
+             #            6707308 (x86/OS X)
+             # 2009-12-31 6149572 (x86/Linux)
            (wordsize(64), 9000000, 20)]),
                # looks like the peak is around 10M, but we're
                # unlikely to GC exactly on the peak.
                # varies quite a lot with CLEANUP and BINDIST,
                # hence 10% range.
       compiler_stats_num_field('bytes allocated',
-          [(wordsize(32), 303930948, 5),
-        # expected value: 215582916 (x86/Windows)
-        #                 221667908 (x86/OS X)
-        #                 274932264 (x86/Linux)
-        # 2012-10-08:     303930948 (x86/Linux, new codegen)
-        # 2012-10-29:     298921816 (x86/Windows; increased range to 5%
+          [(platform('i386-unknown-mingw32'), 303930948, 1),
+                                 #            215582916 (x86/Windows)
+                                 # 2012-10-29 298921816 (x86/Windows)
+           (wordsize(32), 322937684, 1),
+             #            221667908 (x86/OS X)
+             #            274932264 (x86/Linux)
+             # 2012-10-08 303930948 (x86/Linux, new codegen)
+             # 2013-02-10 322937684 (x86/OSX)
            (wordsize(64), 658786936, 5)]),
-        # 17/11/2009:     434845560 (amd64/Linux)
-        # 08/12/2009:     459776680 (amd64/Linux)
-        # 17/05/2010:     519377728 (amd64/Linux)
-        # 05/08/2011:     561382568 (amd64/OS X)
-        # 16/07/2012:     589168872 (amd64/Linux)
-        # 20/07/2012:     595936240 (amd64/Linux)
-        # 23/08/2012:     606230880 (amd64/Linux)
-        # 29/08/2012:     633334184 (amd64/Linux)
-        #                 (^ new codegen)
-        # 18/09/2012:     641959976 (amd64/Linux)
-        # 19/10/2012:     661832592 (amd64/Linux)
-        #                 (^ -fPIC turned on)
-        # 23/10/2012:     642594312 (amd64/Linux)
-        #                 (^ -fPIC turned off again)
-        # 12/11/2012:     658786936 (amd64/Linux)
-        #                 ( UNKNOWN REASON )
-        # 17/1/13:        667160192 (x86_64/Linux)
-        #                 (new demand analyser)
+             # 17/11/2009 434845560 (amd64/Linux)
+             # 08/12/2009 459776680 (amd64/Linux)
+             # 17/05/2010 519377728 (amd64/Linux)
+             # 05/08/2011 561382568 (amd64/OS X)
+             # 16/07/2012 589168872 (amd64/Linux)
+             # 20/07/2012 595936240 (amd64/Linux)
+             # 23/08/2012 606230880 (amd64/Linux)
+             # 29/08/2012 633334184 (amd64/Linux)
+             #            (^ new codegen)
+             # 18/09/2012 641959976 (amd64/Linux)
+             # 19/10/2012 661832592 (amd64/Linux)
+             #            (^ -fPIC turned on)
+             # 23/10/2012 642594312 (amd64/Linux)
+             #            (^ -fPIC turned off again)
+             # 12/11/2012 658786936 (amd64/Linux)
+             #            (^ UNKNOWN REASON )
+             # 17/1/13:   667160192 (x86_64/Linux)
+             #            (^ new demand analyser)
       only_ways(['normal']),
 
       extra_hc_opts('-dcore-lint -static')
@@ -76,9 +82,11 @@ else:
 test('T3294',
      [
       compiler_stats_num_field('max_bytes_used',
-          [(wordsize(32), 17725476, 5),
-        # expected value: 17725476 (x86/OS X)
-        #                 14593500 (Windows)
+          [(wordsize(32), 20712280, 1),
+             #            17725476 (x86/OS X)
+             #            14593500 (Windows)
+             # 2013-02-10 20651576 (x86/Windows)
+             # 2013-02-10 20772984 (x86/OSX)
            (wordsize(64), 44894544, 15)]),
         # prev:           25753192 (amd64/Linux)
         # 29/08/2012:     37724352 (amd64/Linux)
@@ -110,9 +118,9 @@ test('T4801',
            (wordsize(64), 49, 20)]),
             # prev:       50 (amd64/Linux)
             # 19/10/2012: 64 (amd64/Linux)
-            #                (REASON UNKNOWN!)
+            #                (^ REASON UNKNOWN!)
             # 12/11/2012: 49 (amd64/Linux)
-            #                (REASON UNKNOWN!)
+            #                (^ REASON UNKNOWN!)
 
       compiler_stats_num_field('bytes allocated',
           [(platform('x86_64-apple-darwin'), 510938976, 5),
@@ -128,9 +136,11 @@ test('T4801',
 
       compiler_stats_num_field('max_bytes_used',
           [(platform('x86_64-apple-darwin'), 21657520, 5),
-           (wordsize(32), 9651948, 5),
-      #                    expected value: x86/OS X:  9651948
-      #                    expected value:           10290952 (windows)
+           (wordsize(32), 11139444, 1),
+             #             9651948 (x86/OSX)
+             #            10290952 (windows)
+             # 2013-02-10 11071060 (x86/Windows)
+             # 2013-02-10 11207828 (x86/OSX)
            (wordsize(64), 21657520, 15)]),
                 # prev:       20486256 (amd64/OS X)
                 # 30/08/2012: 17305600--20391920 (varies a lot)
@@ -216,8 +226,10 @@ test('T783',
      [ only_ways(['normal']),  # no optimisation for this one
       # expected value: 175,569,928 (x86/Linux)
       compiler_stats_num_field('bytes allocated',
-          [(wordsize(32), 226907420, 10),
+          [(wordsize(32), 333833658, 2),
             # 2012-10-08: 226907420 (x86/Linux)
+            # 2013-02-10: 329202116 (x86/Windows)
+            # 2013-02-10: 338465200 (x86/OSX)
            (wordsize(64), 640324528, 10)]),
             # prev:       349263216 (amd64/Linux)
             # 07/08/2012: 384479856 (amd64/Linux)
-- 
GitLab


From 2ee201b1492c28ca884e05500bd3951d14499ba6 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 10 Feb 2013 17:45:59 +0000
Subject: [PATCH 121/223] More 32bit perf bound fixes

---
 tests/perf/space_leaks/all.T | 16 ++++++++++------
 1 file changed, 10 insertions(+), 6 deletions(-)

diff --git a/tests/perf/space_leaks/all.T b/tests/perf/space_leaks/all.T
index f3260c2eb..a1fd64186 100644
--- a/tests/perf/space_leaks/all.T
+++ b/tests/perf/space_leaks/all.T
@@ -5,11 +5,15 @@ test('space_leak_001',
      #           4 (x86/OS X)
      #           5 (x86/Linux)
      [stats_num_field('peak_megabytes_allocated', (4, 1)),
-      stats_num_field('max_bytes_used', (440000, 10)),
-                       # expected value: 440224 (amd64/Linux)
-                       #                 417016 (x86/OS X)
-                       #                 415672 (x86/Windows)
-                       #                 481456 (unreg amd64/Linux)
+      stats_num_field('max_bytes_used',
+          [(wordsize(64), 440000, 10),
+                        # 440224 (amd64/Linux)
+                        # 417016 (x86/OS X)
+                        # 415672 (x86/Windows)
+                        # 481456 (unreg amd64/Linux)
+           (wordsize(32), 405650, 10)]),
+             # 2013-02-10 372072 (x86/OSX)
+             # 2013-02-10 439228 (x86/OSX)
       stats_num_field('bytes allocated', (9079316016, 1)),
                         # expected value: 9079316016 (amd64/Linux)
                         #                 9331570416 (x86/Linux)
@@ -23,7 +27,7 @@ test('space_leak_001',
 test('T4334',
      # Test for a space leak in Data.List.lines (fixed with #4334)
      [extra_run_opts('1000000 2 t'),
-      stats_num_field('peak_megabytes_allocated', (2, 0)),
+      stats_num_field('peak_megabytes_allocated', (2, 1)),
       # prof ways don't work well with +RTS -V0
       omit_ways(['profasm','profthreaded'])
       ],
-- 
GitLab


From 810fb1fe7fb7294e6c5d25c2a48fafa102dfe949 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 10 Feb 2013 17:53:02 +0000
Subject: [PATCH 122/223] Tweak another 32bit perf bound

---
 tests/perf/compiler/all.T | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 9260df10d..cfbcda672 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -31,9 +31,10 @@ test('T1969',
                # varies quite a lot with CLEANUP and BINDIST,
                # hence 10% range.
       compiler_stats_num_field('bytes allocated',
-          [(platform('i386-unknown-mingw32'), 303930948, 1),
+          [(platform('i386-unknown-mingw32'), 310633884, 1),
                                  #            215582916 (x86/Windows)
                                  # 2012-10-29 298921816 (x86/Windows)
+                                 # 2013-02-10 310633884 (x86/Windows)
            (wordsize(32), 322937684, 1),
              #            221667908 (x86/OS X)
              #            274932264 (x86/Linux)
-- 
GitLab


From 34eda6d37725c2b2d5f93984336ad23c5aa2feb9 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 10 Feb 2013 17:54:30 +0000
Subject: [PATCH 123/223] Tweak another 32bit perf bound

---
 tests/perf/compiler/all.T | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index cfbcda672..1d967d35f 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -19,9 +19,10 @@ test('T1969',
              # 2012-09-20 23 (amd64/Linux)
              # 2012-10-03 25 (amd64/Linux if .hi exists)
       compiler_stats_num_field('max_bytes_used',
-          [(platform('i386-unknown-mingw32'), 5159748, 1),
+          [(platform('i386-unknown-mingw32'), 5094914, 2),
                                  # 2010-05-17 5717704 (x86/Windows)
                                  # 2013-02-10 5159748 (x86/Windows)
+                                 # 2013-02-10 5030080 (x86/Windows)
            (wordsize(32), 6149572, 1),
              #            6707308 (x86/OS X)
              # 2009-12-31 6149572 (x86/Linux)
-- 
GitLab


From 080a08c01b8beb893c3d766f92052745b8fdf74c Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Mon, 11 Feb 2013 08:43:40 +0000
Subject: [PATCH 124/223] Improve bound for T3064

---
 tests/perf/compiler/all.T | 4 +++-
 1 file changed, 3 insertions(+), 1 deletion(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 20b755bbe..7ba0d9ffe 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -163,9 +163,11 @@ test('T3064',
       compiler_stats_num_field('max_bytes_used',
           [(wordsize(32), 5511604, 20),
         # expected value: 2247016 (x86/Linux) (28/6/2011):
-           (wordsize(64), 9819288, 5)]),
+           (wordsize(64), 8945328, 5)]),
             # (amd64/Linux, intree) (28/06/2011):  4032024
             # (amd64/Linux, intree) (07/02/2013):  9819288
+            # (amd64/Linux, intree) (10/02/2013):  8945328 
+            #   apparently courtesy of the b5c18c (Trac #5113)
        only_ways(['normal'])
       ],
      compile,
-- 
GitLab


From 2359f7da9804d97eeb2c4ffb5661d071a2a10c57 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Mon, 11 Feb 2013 08:45:01 +0000
Subject: [PATCH 125/223] T5113 is fixed

---
 tests/perf/should_run/all.T | 3 +--
 1 file changed, 1 insertion(+), 2 deletions(-)

diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index 5b17e452c..b2fdf0a41 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -104,8 +104,7 @@ test('T5113',
      [stats_num_field('bytes allocated',
                       [(wordsize(32), 4000000, 5),
                        (wordsize(64), 8000000, 5)]),
-      only_ways(['normal']),
-      expect_broken(7046)
+      only_ways(['normal'])
       ],
      compile_and_run,
      ['-O'])
-- 
GitLab


From 7e6d754e901ef101a7417e1d48631b2b228b7911 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 13:27:58 +0000
Subject: [PATCH 126/223] Add 'make list_brokens'

Gives a list of tickets that the testsuite thinks are broken, and
what bug it thinks is the reason. This can then be pasted into trac
and 'previewed', which will show any closed tickets with strikeout.
---
 driver/runtests.py    | 45 ++++++++++++++++++++++++-------------------
 driver/testglobals.py |  6 ++++++
 driver/testlib.py     |  6 +++++-
 mk/test.mk            | 10 ++++++++++
 4 files changed, 46 insertions(+), 21 deletions(-)

diff --git a/driver/runtests.py b/driver/runtests.py
index 04d69b734..b736ae55d 100644
--- a/driver/runtests.py
+++ b/driver/runtests.py
@@ -254,28 +254,33 @@ for file in t_files:
         t.n_framework_failures = t.n_framework_failures + 1
         traceback.print_exc()
 
-# Now run all the tests
-if config.use_threads:
-    t.running_threads=0
-for oneTest in parallelTests:
-    if stopping():
-        break
-    oneTest()
-if config.use_threads:
-    t.thread_pool.acquire()
-    while t.running_threads>0:
-        t.thread_pool.wait()
-    t.thread_pool.release()
-config.use_threads = False
-for oneTest in aloneTests:
-    if stopping():
-        break
-    oneTest()
+if config.list_broken:
+    global brokens
+    print 'Broken tests:'
+    print (' '.join(map (lambda (b, n) : '#' + str(b) + '(' + n + ')', brokens)))
+else:
+    # Now run all the tests
+    if config.use_threads:
+        t.running_threads=0
+    for oneTest in parallelTests:
+        if stopping():
+            break
+        oneTest()
+    if config.use_threads:
+        t.thread_pool.acquire()
+        while t.running_threads>0:
+            t.thread_pool.wait()
+        t.thread_pool.release()
+    config.use_threads = False
+    for oneTest in aloneTests:
+        if stopping():
+            break
+        oneTest()
         
-summary(t, sys.stdout)
+    summary(t, sys.stdout)
 
-if config.output_summary != '':
-    summary(t, open(config.output_summary, 'w'))
+    if config.output_summary != '':
+        summary(t, open(config.output_summary, 'w'))
 
 sys.exit(0)
 
diff --git a/driver/testglobals.py b/driver/testglobals.py
index db99ef1b2..b7b60077f 100644
--- a/driver/testglobals.py
+++ b/driver/testglobals.py
@@ -48,6 +48,8 @@ class TestConfig:
         # run the "fast" version of the test suite
         self.fast = 0
 
+        self.list_broken = False
+
         # Compiler type (ghc, hugs, nhc, etc.)
         self.compiler_type = ''
 
@@ -263,3 +265,7 @@ class TestOptions:
 global default_testopts
 default_testopts = TestOptions()
 
+# (bug, name) of tests marked broken
+global brokens
+brokens = []
+
diff --git a/driver/testlib.py b/driver/testlib.py
index e77c7d9c4..985a7b3b4 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -134,6 +134,8 @@ def expect_broken( bug ):
     return lambda name, opts, b=bug: _expect_broken (name, opts, b )
 
 def _expect_broken( name, opts, bug ):
+    global brokens
+    brokens.append((bug, name))
     opts.expect = 'fail';
 
 def ignore_output( name, opts ):
@@ -298,7 +300,9 @@ def skip_if_fast(name, opts):
 # -----
 
 def when(b, f):
-    if b:
+    # When list_brokens is on, we want to see all expect_broken calls,
+    # so we always do f
+    if b or config.list_broken:
         return f
     else:
         return normal
diff --git a/mk/test.mk b/mk/test.mk
index 6c974cc1d..e7604bdd7 100644
--- a/mk/test.mk
+++ b/mk/test.mk
@@ -175,6 +175,12 @@ endif
 RUNTEST_OPTS +=  \
 	$(EXTRA_RUNTEST_OPTS)
 
+ifeq "$(list_broken)" "YES"
+set_list_broken = -e config.list_broken=True
+else
+set_list_broken = 
+endif
+
 ifeq "$(fast)" "YES"
 setfast = -e config.fast=1
 else
@@ -209,6 +215,7 @@ test: $(TIMEOUT_PROGRAM)
 		$(patsubst %, --only=%, $(TESTS)) \
 		$(patsubst %, --way=%, $(WAY)) \
 		$(patsubst %, --skipway=%, $(SKIPWAY)) \
+		$(set_list_broken) \
 		$(setfast) \
 		$(setaccept)
 
@@ -220,3 +227,6 @@ accept:
 fast:
 	$(MAKE) fast=YES
 
+list_broken:
+	$(MAKE) list_broken=YES
+
-- 
GitLab


From f3c626eaa8410bcd52485ab0d0490ccc73dd9bb9 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 13:48:59 +0000
Subject: [PATCH 127/223] Replace 'if_os' and 'unless_os' with 'opsys'

The name 'os' clashes with a python library
---
 driver/testlib.py                  | 13 ++-----------
 tests/concurrent/should_run/all.T  |  4 ++--
 tests/driver/dynamicToo/all.T      |  2 +-
 tests/dynlibs/all.T                |  4 ++--
 tests/ghc-api/dynCompileExpr/all.T |  2 +-
 tests/ghci/linking/all.T           |  8 ++++----
 tests/ghci/should_run/all.T        |  2 +-
 tests/rts/all.T                    | 18 +++++++++---------
 8 files changed, 22 insertions(+), 31 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 985a7b3b4..08df6319f 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -313,17 +313,8 @@ def unless(b, f):
 def platform( plat ):
     return config.platform == plat
 
-def if_os( os, f ):
-    if config.os == os:
-        return f
-    else:
-        return normal
-
-def unless_os( os, f ):
-    if config.os == os:
-        return normal
-    else:
-        return f
+def opsys( os ):
+    return config.os == os
 
 def if_arch( arch, f ):
     if config.arch == arch:
diff --git a/tests/concurrent/should_run/all.T b/tests/concurrent/should_run/all.T
index 97dc4b13a..f0a68dea4 100644
--- a/tests/concurrent/should_run/all.T
+++ b/tests/concurrent/should_run/all.T
@@ -52,7 +52,7 @@ test('numsparks001', only_ways(['threaded1']), compile_and_run, [''])
 
 test('T4262', [ skip, # skip for now, it doesn't give reliable results
                 only_ways(['threaded1']),
-                unless_os('linux',skip),
+                unless(opsys('linux'),skip),
                 if_compiler_lt('ghc', '7.1', expect_fail) ],
               compile_and_run, [''])
 
@@ -171,7 +171,7 @@ test('conc036', skip, compile_and_run, [''])
 
 # Interrupting foreign calls only makes sense if we are threaded
 test('foreignInterruptible', [skip_if_fast,
-                              if_os('mingw32',expect_fail),
+                              when(opsys('mingw32'),expect_fail),
                               # I don't think we support interrupting Sleep()
                               # on Windows.  --SDM
                               only_threaded_ways,
diff --git a/tests/driver/dynamicToo/all.T b/tests/driver/dynamicToo/all.T
index b85ff318e..25d48b05f 100644
--- a/tests/driver/dynamicToo/all.T
+++ b/tests/driver/dynamicToo/all.T
@@ -6,7 +6,7 @@ test('dynamicToo001',
                    'A001.dyn_o',  'B001.dyn_o',  'C001.dyn_o',
                    'A001.dyn_hi', 'B001.dyn_hi', 'C001.dyn_hi',
                    's001', 'd001']),
-      if_os('mingw32', expect_broken(7665)),
+      when(opsys('mingw32'), expect_broken(7665)),
       unless_have_vanilla(skip),
       unless_have_dynamic(skip)],
      run_command,
diff --git a/tests/dynlibs/all.T b/tests/dynlibs/all.T
index 2877c50e1..6a9dfd965 100644
--- a/tests/dynlibs/all.T
+++ b/tests/dynlibs/all.T
@@ -7,7 +7,7 @@ test('T3807',
                    'T3807-export.o', 'T3807-load.o',
                    'T3807test.so',
                    'T3807-load']),
-      if_os('mingw32', skip)],
+      when(opsys('mingw32'), skip)],
      run_command,
      ['$MAKE --no-print-directory -s T3807'])
 
@@ -16,7 +16,7 @@ test('T4464',
       extra_clean(['T4464B.o', 'T4464C.o', 'T4464H.hi', 'T4464H.o',
                    'T4464H_stub.c', 'T4464H_stub.h', 'T4464H_stub.o',
                    'HS4464.dll', 'HS4464.dll.a', 't4464.exe']),
-      unless_os('mingw32', skip)],
+      unless(opsys('mingw32'), skip)],
      run_command,
      ['$MAKE --no-print-directory -s T4464'])
 
diff --git a/tests/ghc-api/dynCompileExpr/all.T b/tests/ghc-api/dynCompileExpr/all.T
index b466a3a59..c6034eab6 100644
--- a/tests/ghc-api/dynCompileExpr/all.T
+++ b/tests/ghc-api/dynCompileExpr/all.T
@@ -1,5 +1,5 @@
 test('dynCompileExpr',
      [ extra_run_opts('"' + config.libdir + '"'),
-       if_os('mingw32', expect_broken_for(5987, ['dyn'])),
+       when(opsys('mingw32'), expect_broken_for(5987, ['dyn'])),
        omit_ways(prof_ways) ], # cannot run interpreted code with -prof
      compile_and_run, ['-package ghc'])
diff --git a/tests/ghci/linking/all.T b/tests/ghci/linking/all.T
index bd87173c8..d4724ca1e 100644
--- a/tests/ghci/linking/all.T
+++ b/tests/ghci/linking/all.T
@@ -12,8 +12,8 @@ test('ghcilink002',
 
 test('ghcilink003',
      [
-       if_os('mingw32', expect_broken(5289)), # still cannot load libstdc++
-                                              # on Windows.  See also #4468.
+       # still cannot load libstdc++ on Windows.  See also #4468.
+       when(opsys('mingw32'), expect_broken(5289)),
        skip_if_no_ghci,
        extra_clean(['dir003/*','dir003'])
      ],
@@ -34,8 +34,8 @@ test('ghcilink005',
 
 test('ghcilink006',
      [
-       if_os('mingw32', expect_broken(5289)), # still cannot load libstdc++
-                                              # on Windows.  See also #4468.
+       # still cannot load libstdc++ on Windows.  See also #4468.
+       when(opsys('mingw32'), expect_broken(5289)),
        skip_if_no_ghci,
        extra_clean(['dir006/*','dir006'])
      ],
diff --git a/tests/ghci/should_run/all.T b/tests/ghci/should_run/all.T
index a2552f6f9..fa03ac116 100644
--- a/tests/ghci/should_run/all.T
+++ b/tests/ghci/should_run/all.T
@@ -12,7 +12,7 @@ test('T2589',      just_ghci, compile_and_run, [''])
 test('T2881',      just_ghci, compile_and_run, [''])
 
 test('T3171',
-     [if_os('mingw32',skip),
+     [when(opsys('mingw32'),skip),
       req_interp,
       combined_output],
      run_command,
diff --git a/tests/rts/all.T b/tests/rts/all.T
index 380ce85c9..2276d3587 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -19,11 +19,11 @@ test('derefnull',
              # Apparently the output can be different on different
              # Linux setups, so just ignore it. As long as we get
              # the right exit code we're OK.
-             if_os('linux', ignore_output),
+             when(opsys('linux'), ignore_output),
              # SIGBUS on OX X (PPC and x86 only; amd64 gives SEGV)
              when(platform('i386-apple-darwin'), exit_code(138)),
              when(platform('powerpc-apple-darwin'), exit_code(138)),
-             if_os('mingw32', exit_code(1))]),
+             when(opsys('mingw32'), exit_code(1))]),
      compile_and_run, [''])
 test('divbyzero',
      composes([
@@ -33,11 +33,11 @@ test('divbyzero',
              # Apparently the output can be different on different
              # Linux setups, so just ignore it. As long as we get
              # the right exit code we're OK.
-             if_os('linux', ignore_output),
-             if_os('mingw32', exit_code(1))]),
+             when(opsys('linux'), ignore_output),
+             when(opsys('mingw32'), exit_code(1))]),
      compile_and_run, [''])
 
-test('outofmem', if_os('darwin', skip), 
+test('outofmem', when(opsys('darwin'), skip), 
                  run_command, ['$MAKE -s --no-print-directory outofmem'])
 test('outofmem2', extra_run_opts('+RTS -M5m -RTS'),
                   run_command, ['$MAKE -s --no-print-directory outofmem2'])
@@ -80,11 +80,11 @@ test('rtsflags002', [ only_ways(['normal']) ], compile_and_run, ['-with-rtsopts=
 
 # Test to see if linker scripts link properly to real ELF files
 test('T2615',
-     [ if_os('mingw32', skip),
+     [ when(opsys('mingw32'), skip),
        # OS X doesn't seem to support linker scripts
-       if_os('darwin', skip),
+       when(opsys('darwin'), skip),
        # Solaris' linker does not support GNUish linker scripts
-       if_os('solaris2', skip),
+       when(opsys('solaris2'), skip),
        pre_cmd('$MAKE -s --no-print-directory T2615-prep'),
        # Add current directory to dlopen search path
        cmd_prefix('LD_LIBRARY_PATH=$LD_LIBRARY_PATH:. '),
@@ -105,7 +105,7 @@ test('T4059',
 
 # Test for #4274
 test('exec_signals', [
-     if_os('mingw32', skip),
+     when(opsys('mingw32'), skip),
      pre_cmd('$MAKE -s --no-print-directory exec_signals-prep'),
      cmd_prefix('./exec_signals_prepare'),
      extra_clean(['exec_signals_child', 'exec_signals_prepare'])
-- 
GitLab


From 47fd31645fcb8eeed86d9775f811e14c5a6bfa56 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 13:52:49 +0000
Subject: [PATCH 128/223] expect_broken_for should also be added to the list of
 brokens

---
 driver/testlib.py | 18 ++++++++++--------
 1 file changed, 10 insertions(+), 8 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 08df6319f..97a292de8 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -130,14 +130,6 @@ def req_smp( name, opts ):
     if not config.have_smp:
         opts.expect = 'fail'
 
-def expect_broken( bug ):
-    return lambda name, opts, b=bug: _expect_broken (name, opts, b )
-
-def _expect_broken( name, opts, bug ):
-    global brokens
-    brokens.append((bug, name))
-    opts.expect = 'fail';
-
 def ignore_output( name, opts ):
     opts.ignore_output = 1
 
@@ -155,10 +147,20 @@ def expect_fail_for( ways ):
 def _expect_fail_for( name, opts, ways ):
     opts.expect_fail_for = ways
 
+def expect_broken( bug ):
+    return lambda name, opts, b=bug: _expect_broken (name, opts, b )
+
+def _expect_broken( name, opts, bug ):
+    global brokens
+    brokens.append((bug, name))
+    opts.expect = 'fail';
+
 def expect_broken_for( bug, ways ):
     return lambda name, opts, b=bug, w=ways: _expect_broken_for( name, opts, b, w )
 
 def _expect_broken_for( name, opts, bug, ways ):
+    global brokens
+    brokens.append((bug, name))
     opts.expect_fail_for = ways
 
 # -----
-- 
GitLab


From 3a8b71f63314a91a697a7659d7aa899f1f081736 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 13:55:40 +0000
Subject: [PATCH 129/223] Handle duplicates in the brokens list

---
 driver/testlib.py | 12 ++++++++----
 1 file changed, 8 insertions(+), 4 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 97a292de8..b9104fc88 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -151,18 +151,22 @@ def expect_broken( bug ):
     return lambda name, opts, b=bug: _expect_broken (name, opts, b )
 
 def _expect_broken( name, opts, bug ):
-    global brokens
-    brokens.append((bug, name))
+    record_broken(name, bug)
     opts.expect = 'fail';
 
 def expect_broken_for( bug, ways ):
     return lambda name, opts, b=bug, w=ways: _expect_broken_for( name, opts, b, w )
 
 def _expect_broken_for( name, opts, bug, ways ):
-    global brokens
-    brokens.append((bug, name))
+    record_broken(name, bug)
     opts.expect_fail_for = ways
 
+def record_broken(name, bug):
+    global brokens
+    me = (bug, name)
+    if not me in brokens:
+        brokens.append(me)
+
 # -----
 
 def omit_ways( ways ):
-- 
GitLab


From 9b9ff6285bf338c40df4872b3ff73e3bbfb0bd12 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 13:59:55 +0000
Subject: [PATCH 130/223] Print a warning if we get framework failures when
 listing brokens

---
 driver/runtests.py | 6 ++++++
 1 file changed, 6 insertions(+)

diff --git a/driver/runtests.py b/driver/runtests.py
index b736ae55d..e1d6f7cdb 100644
--- a/driver/runtests.py
+++ b/driver/runtests.py
@@ -256,8 +256,14 @@ for file in t_files:
 
 if config.list_broken:
     global brokens
+    print ''
     print 'Broken tests:'
     print (' '.join(map (lambda (b, n) : '#' + str(b) + '(' + n + ')', brokens)))
+    print ''
+
+    if t.n_framework_failures != 0:
+        print 'WARNING:', str(t.n_framework_failures), 'framework failures!'
+        print ''
 else:
     # Now run all the tests
     if config.use_threads:
-- 
GitLab


From 71d9b698a8045b19f82991d8f2536f1caa166a09 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 14:03:23 +0000
Subject: [PATCH 131/223] Change '{if,unless}_arch' to 'arch'

---
 driver/testlib.py                  | 13 ++-----------
 tests/codeGen/should_compile/all.T |  4 ++--
 tests/codeGen/should_run/all.T     |  2 +-
 tests/ffi/should_run/all.T         |  2 +-
 4 files changed, 6 insertions(+), 15 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index b9104fc88..02c7ba32b 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -322,17 +322,8 @@ def platform( plat ):
 def opsys( os ):
     return config.os == os
 
-def if_arch( arch, f ):
-    if config.arch == arch:
-        return f
-    else:
-        return normal
-
-def unless_arch( arch, f ):
-    if config.arch == arch:
-        return normal
-    else:
-        return f
+def arch( arch ):
+    return config.arch == arch
 
 def wordsize( ws ):
     return config.wordsize == str(ws)
diff --git a/tests/codeGen/should_compile/all.T b/tests/codeGen/should_compile/all.T
index 046d98ec5..220ff8500 100644
--- a/tests/codeGen/should_compile/all.T
+++ b/tests/codeGen/should_compile/all.T
@@ -15,8 +15,8 @@ test('T3286', extra_clean(['T3286b.o','T3286b.hi']),
 test('T3579', normal, compile, [''])
 test('T2578', normal, run_command, ['$MAKE -s --no-print-directory T2578'])
 # skip llvm on i386 as we don't support fPIC
-test('jmp_tbl', if_arch('i386', omit_ways(['llvm', 'optllvm'])), compile, ['-fPIC -O'])
+test('jmp_tbl', when(arch('i386'), omit_ways(['llvm', 'optllvm'])), compile, ['-fPIC -O'])
 test('massive_array',
-     [ if_arch('i386', omit_ways(['llvm', 'optllvm'])) ],
+     [ when(arch('i386'), omit_ways(['llvm', 'optllvm'])) ],
      compile, ['-fPIC'])
 test('T7237', normal, compile, [''])
diff --git a/tests/codeGen/should_run/all.T b/tests/codeGen/should_run/all.T
index 77224a2e1..d470d7b4a 100644
--- a/tests/codeGen/should_run/all.T
+++ b/tests/codeGen/should_run/all.T
@@ -87,7 +87,7 @@ test('T5149', omit_ways(['ghci']), multi_compile_and_run,
                  ['T5149', [('T5149_cmm.cmm', '')], ''])
 test('T5129', normal, compile_and_run, [''])
 test('T5626', exit_code(1), compile_and_run, [''])
-test('T5747', if_arch('i386', extra_hc_opts('-msse2')), compile_and_run, ['-O2'])
+test('T5747', when(arch('i386'), extra_hc_opts('-msse2')), compile_and_run, ['-O2'])
 test('T5785', normal, compile_and_run, [''])
 test('setByteArray', normal, compile_and_run, [''])
 
diff --git a/tests/ffi/should_run/all.T b/tests/ffi/should_run/all.T
index 09e69447e..a8d62ff70 100644
--- a/tests/ffi/should_run/all.T
+++ b/tests/ffi/should_run/all.T
@@ -32,7 +32,7 @@ test('ffi004', skip, compile_and_run, [''])
 # use of 80-bit internal precision when using the native code generator.
 #
 test('ffi005', [ omit_ways(prof_ways), 
-                 if_arch('i386', skip),
+                 when(arch('i386'), skip),
                  when(platform('i386-apple-darwin'), expect_broken(4105)),
                  exit_code(3) ],
                compile_and_run, [''])
-- 
GitLab


From 18cc9aaf8bac3f99923bc02ce09df720a9bae5eb Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 14:08:58 +0000
Subject: [PATCH 132/223] Convert more helpers to the new scheme

---
 driver/testlib.py  | 27 ++++++---------------------
 tests/driver/all.T |  2 +-
 2 files changed, 7 insertions(+), 22 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 02c7ba32b..51e18be8f 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -328,29 +328,14 @@ def arch( arch ):
 def wordsize( ws ):
     return config.wordsize == str(ws)
 
-def if_unregisterised( f ):
-    if config.unregisterised:
-        return f
-    else:
-        return normal
+def unregisterised( ):
+    return config.unregisterised
 
-def unless_unregisterised( f ):
-    if config.unregisterised:
-        return normal
-    else:
-        return f
+def msys( ):
+    return config.msys
 
-def if_msys( f ):
-    if config.msys:
-        return f
-    else:
-        return normal
-
-def if_cygwin( f ):
-    if config.cygwin:
-        return f
-    else:
-        return normal
+def cygwin( ):
+    return config.cygwin
 
 def when_have_vanilla( f ):
     if config.have_vanilla:
diff --git a/tests/driver/all.T b/tests/driver/all.T
index 1bf7c7e33..0020f1836 100644
--- a/tests/driver/all.T
+++ b/tests/driver/all.T
@@ -362,6 +362,6 @@ test('T7060',
      run_command,
      ['$MAKE -s --no-print-directory T7060'])
 test('T7130', normal, compile_fail, ['-fflul-laziness'])
-test('T7563', if_unregisterised(skip), run_command,
+test('T7563', when(unregisterised(), skip), run_command,
      ['$MAKE -s --no-print-directory T7563'])
 
-- 
GitLab


From 3d7a744ed778dde764322d3b9d6ea5340a415e3b Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 14:18:38 +0000
Subject: [PATCH 133/223] Convert more helper functions to the new scheme

---
 driver/testlib.py             | 39 ++++++-----------------------------
 tests/driver/dynamicToo/all.T |  4 ++--
 2 files changed, 8 insertions(+), 35 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 51e18be8f..6f6ab4a25 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -337,41 +337,14 @@ def msys( ):
 def cygwin( ):
     return config.cygwin
 
-def when_have_vanilla( f ):
-    if config.have_vanilla:
-        return f
-    else:
-        return normal
+def have_vanilla( ):
+    return config.have_vanilla
 
-def unless_have_vanilla( f ):
-    if config.have_vanilla:
-        return normal
-    else:
-        return f
+def have_dynamic( ):
+    return config.have_dynamic
 
-def when_have_dynamic( f ):
-    if config.have_dynamic:
-        return f
-    else:
-        return normal
-
-def unless_have_dynamic( f ):
-    if config.have_dynamic:
-        return normal
-    else:
-        return f
-
-def when_have_profiling( f ):
-    if config.have_profiling:
-        return f
-    else:
-        return normal
-
-def unless_have_profiling( f ):
-    if config.have_profiling:
-        return normal
-    else:
-        return f
+def have_profiling( ):
+    return config.have_profiling
 
 # ---
 
diff --git a/tests/driver/dynamicToo/all.T b/tests/driver/dynamicToo/all.T
index 25d48b05f..6465d1e1f 100644
--- a/tests/driver/dynamicToo/all.T
+++ b/tests/driver/dynamicToo/all.T
@@ -7,8 +7,8 @@ test('dynamicToo001',
                    'A001.dyn_hi', 'B001.dyn_hi', 'C001.dyn_hi',
                    's001', 'd001']),
       when(opsys('mingw32'), expect_broken(7665)),
-      unless_have_vanilla(skip),
-      unless_have_dynamic(skip)],
+      unless(have_vanilla(), skip),
+      unless(have_dynamic(), skip)],
      run_command,
      ['$MAKE -s --no-print-directory dynamicToo001'])
 
-- 
GitLab


From aa04bca1b372fc9d53aa23244663480f7cc70065 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 15:07:12 +0000
Subject: [PATCH 134/223] Convert more helper functions

---
 driver/testlib.py                          | 83 ++++++----------------
 tests/annotations/should_compile/all.T     |  2 +-
 tests/annotations/should_run/all.T         |  2 +-
 tests/arrows/should_fail/all.T             |  2 +-
 tests/concurrent/should_run/all.T          |  2 +-
 tests/deSugar/should_compile/all.T         |  2 +-
 tests/deSugar/should_run/all.T             |  4 +-
 tests/gadt/all.T                           |  8 +--
 tests/ghc-e/should_run/all.T               |  4 +-
 tests/ghci.debugger/scripts/all.T          |  4 +-
 tests/ghci.debugger/scripts/break022/all.T |  2 +-
 tests/ghci.debugger/scripts/break023/all.T |  2 +-
 tests/ghci/linking/all.T                   |  4 +-
 tests/ghci/scripts/all.T                   |  2 +-
 tests/ghci/should_run/all.T                |  2 +-
 tests/indexed-types/should_compile/all.T   |  2 +-
 tests/indexed-types/should_fail/all.T      |  2 +-
 tests/layout/all.T                         |  2 +-
 tests/module/all.T                         |  2 +-
 tests/module/base01/all.T                  |  2 +-
 tests/parser/should_compile/all.T          |  6 +-
 tests/parser/should_fail/all.T             |  6 +-
 tests/parser/should_run/all.T              |  2 +-
 tests/perf/haddock/all.T                   |  6 +-
 tests/plugins/all.T                        |  2 +-
 tests/programs/life_space_leak/test.T      |  2 +-
 tests/rename/should_compile/all.T          |  2 +-
 tests/rts/all.T                            |  2 +-
 tests/simplCore/should_compile/all.T       |  4 +-
 tests/th/T2014/all.T                       |  2 +-
 tests/th/TH_import_loop/TH_import_loop.T   |  2 +-
 tests/th/TH_spliceViewPat/test.T           |  2 +-
 tests/th/all.T                             |  6 +-
 tests/typecheck/should_compile/all.T       |  6 +-
 tests/typecheck/should_fail/all.T          |  4 +-
 35 files changed, 75 insertions(+), 114 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 6f6ab4a25..942a7222e 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -348,75 +348,36 @@ def have_profiling( ):
 
 # ---
 
-def if_ghci_dynamic( f ):
-    if config.ghc_dynamic_by_default:
-        return f
-    else:
-        return normal
+def ghci_dynamic( ):
+    return config.ghc_dynamic_by_default
 
-def if_in_tree_compiler( f ):
-    if config.in_tree_compiler:
-        return f
-    else:
-        return normal
+def in_tree_compiler( ):
+    return config.in_tree_compiler
 
-def unless_in_tree_compiler( f ):
-    if config.in_tree_compiler:
-        return normal
-    else:
-        return f
+def compiler_type( compiler ):
+    return config.compiler_type == compiler
 
-def if_compiler_type( compiler, f ):
-    if config.compiler_type == compiler:
-        return f
-    else:
-        return normal
+def compiler_profiled( ):
+    return config.compiler_profiled
 
-def if_compiler_profiled( f ):
-    if config.compiler_profiled:
-        return f
-    else:
-        return normal
+def compiler_lt( compiler, version ):
+    return config.compiler_type == compiler and \
+           version_lt(config.compiler_version, version)
 
-def unless_compiler_profiled( f ):
-    if config.compiler_profiled:
-        return normal
-    else:
-        return f
+def compiler_le( compiler, version ):
+    return config.compiler_type == compiler and \
+           version_le(config.compiler_version, version)
 
-def if_compiler_lt( compiler, version, f ):
-    if config.compiler_type == compiler and \
-       version_lt(config.compiler_version, version):
-        return f
-    else:
-        return normal
+def compiler_gt( compiler, version ):
+    return config.compiler_type == compiler and \
+           version_gt(config.compiler_version, version)
 
-def if_compiler_le( compiler, version, f ):
-    if config.compiler_type == compiler and \
-       version_le(config.compiler_version, version):
-        return f
-    else:
-        return normal
+def compiler_ge( compiler, version ):
+    return config.compiler_type == compiler and \
+           version_ge(config.compiler_version, version)
 
-def if_compiler_gt( compiler, version, f ):
-    if config.compiler_type == compiler and \
-       version_gt(config.compiler_version, version):
-        return f
-    else:
-        return normal
-
-def if_compiler_ge( compiler, version, f ):
-    if config.compiler_type == compiler and \
-       version_ge(config.compiler_version, version):
-        return f
-    else:
-        return normal
-
-def if_compiler_debugged( f ):
-    if config.compiler_debugged:
-        return f
-    else:
-        return normal
+def compiler_debugged( ):
+    return config.compiler_debugged
 
 def namebase( nb ):
    return lambda opts, nb=nb: _namebase(opts, nb)
diff --git a/tests/annotations/should_compile/all.T b/tests/annotations/should_compile/all.T
index e13c24e72..1c6690b2b 100644
--- a/tests/annotations/should_compile/all.T
+++ b/tests/annotations/should_compile/all.T
@@ -1,5 +1,5 @@
 
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 
 # Annotations, like Template Haskell, require runtime evaluation.  In
 # order for this to work with profiling, we would have to build the
diff --git a/tests/annotations/should_run/all.T b/tests/annotations/should_run/all.T
index 871b40916..6616de5df 100644
--- a/tests/annotations/should_run/all.T
+++ b/tests/annotations/should_run/all.T
@@ -1,4 +1,4 @@
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 # These tests are very slow due to their use of package GHC
 setTestOpts(skip_if_fast)
 
diff --git a/tests/arrows/should_fail/all.T b/tests/arrows/should_fail/all.T
index 557929454..6b7920d31 100644
--- a/tests/arrows/should_fail/all.T
+++ b/tests/arrows/should_fail/all.T
@@ -1,7 +1,7 @@
 setTestOpts(only_compiler_types(['ghc']))
 
 test('arrowfail001',
-     if_compiler_debugged(expect_broken(5267)),
+     when(compiler_debugged(), expect_broken(5267)),
      compile_fail,
      [''])
  # arrowfail001 gets an ASSERT error in the stage1 compiler
diff --git a/tests/concurrent/should_run/all.T b/tests/concurrent/should_run/all.T
index f0a68dea4..d5ceb7257 100644
--- a/tests/concurrent/should_run/all.T
+++ b/tests/concurrent/should_run/all.T
@@ -53,7 +53,7 @@ test('numsparks001', only_ways(['threaded1']), compile_and_run, [''])
 test('T4262', [ skip, # skip for now, it doesn't give reliable results
                 only_ways(['threaded1']),
                 unless(opsys('linux'),skip),
-                if_compiler_lt('ghc', '7.1', expect_fail) ],
+                when(compiler_lt('ghc', '7.1'), expect_fail) ],
               compile_and_run, [''])
 
 test('T4813', normal, compile_and_run, [''])
diff --git a/tests/deSugar/should_compile/all.T b/tests/deSugar/should_compile/all.T
index 979b1e764..6328b3048 100644
--- a/tests/deSugar/should_compile/all.T
+++ b/tests/deSugar/should_compile/all.T
@@ -76,7 +76,7 @@ test('GadtOverlap', normal, compile, ['-Wall'])
 test('T2395', normal, compile, [''])
 test('T4371', normal, compile, [''])
 test('T4439', normal, compile, [''])
-test('T4488', if_compiler_lt('ghc', '7.1', expect_fail), compile, [''])
+test('T4488', when(compiler_lt('ghc', '7.1'), expect_fail), compile, [''])
 test('T4870',
      [only_ways(['optasm']),
       only_compiler_types(['ghc']),
diff --git a/tests/deSugar/should_run/all.T b/tests/deSugar/should_run/all.T
index 7f0df9c0f..90d76a964 100644
--- a/tests/deSugar/should_run/all.T
+++ b/tests/deSugar/should_run/all.T
@@ -38,5 +38,5 @@ test('mc06', normal, compile_and_run, [''])
 test('mc07', normal, compile_and_run, [''])
 test('mc08', normal, compile_and_run, [''])
 test('T5742', normal, compile_and_run, [''])
-test('DsLambdaCase', if_compiler_lt('ghc', '7.5', skip), compile_and_run, [''])
-test('DsMultiWayIf', if_compiler_lt('ghc', '7.5', skip), compile_and_run, [''])
+test('DsLambdaCase', when(compiler_lt('ghc', '7.5'), skip), compile_and_run, [''])
+test('DsMultiWayIf', when(compiler_lt('ghc', '7.5'), skip), compile_and_run, [''])
diff --git a/tests/gadt/all.T b/tests/gadt/all.T
index 1b46565fd..d55aef64e 100644
--- a/tests/gadt/all.T
+++ b/tests/gadt/all.T
@@ -102,10 +102,10 @@ test('gadt25', normal, compile, [''])
 test('T3651', normal, compile_fail, [''])
 test('T3638', normal, compile, [''])
 
-test('gadtSyntax001', if_compiler_lt('ghc', '7.1', expect_fail), compile, [''])
-test('gadtSyntaxFail001', if_compiler_lt('ghc', '7.1', expect_fail), compile_fail, [''])
-test('gadtSyntaxFail002', if_compiler_lt('ghc', '7.1', expect_fail), compile_fail, [''])
-test('gadtSyntaxFail003', if_compiler_lt('ghc', '7.1', expect_fail), compile_fail, [''])
+test('gadtSyntax001', when(compiler_lt('ghc', '7.1'), expect_fail), compile, [''])
+test('gadtSyntaxFail001', when(compiler_lt('ghc', '7.1'), expect_fail), compile_fail, [''])
+test('gadtSyntaxFail002', when(compiler_lt('ghc', '7.1'), expect_fail), compile_fail, [''])
+test('gadtSyntaxFail003', when(compiler_lt('ghc', '7.1'), expect_fail), compile_fail, [''])
 test('T3169', normal, compile_fail, [''])
 test('T5424',
      extra_clean(['T5424a.hi', 'T5424a.o']),
diff --git a/tests/ghc-e/should_run/all.T b/tests/ghc-e/should_run/all.T
index da14b703c..4ab756735 100644
--- a/tests/ghc-e/should_run/all.T
+++ b/tests/ghc-e/should_run/all.T
@@ -1,5 +1,5 @@
 
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 
 test('ghc-e001', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e001'])
 test('ghc-e002', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e002'])
@@ -8,7 +8,7 @@ test('ghc-e004', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e0
 test('ghc-e005', req_interp, run_command, ['$MAKE --no-print-directory -s ghc-e005'])
 
 test('T2228',
-     [req_interp, if_ghci_dynamic(expect_broken(7298))],
+     [req_interp, when(ghci_dynamic(), expect_broken(7298))],
      run_command,
      ['$MAKE --no-print-directory -s T2228'])
 test('T2636', req_interp, run_command, ['$MAKE --no-print-directory -s T2636'])
diff --git a/tests/ghci.debugger/scripts/all.T b/tests/ghci.debugger/scripts/all.T
index 9eef1f62b..76a8f0ff5 100644
--- a/tests/ghci.debugger/scripts/all.T
+++ b/tests/ghci.debugger/scripts/all.T
@@ -1,5 +1,5 @@
 setTestOpts(composes([extra_run_opts('-ignore-dot-ghci'),
-                     if_compiler_profiled(skip),
+                     when(compiler_profiled(), skip),
                      normalise_slashes]))
 
 test('print001', normal, ghci_script, ['print001.script'])
@@ -36,7 +36,7 @@ test('print032', normal, ghci_script, ['print032.script'])
 test('print033', normal, ghci_script, ['print033.script'])
 test('print034', normal, ghci_script, ['print034.script'])
 test('print035',
-     if_ghci_dynamic(expect_broken(7326)),
+     when(ghci_dynamic(), expect_broken(7326)),
      ghci_script,
      ['print035.script'])
 
diff --git a/tests/ghci.debugger/scripts/break022/all.T b/tests/ghci.debugger/scripts/break022/all.T
index d8cf081ed..497ad7e41 100644
--- a/tests/ghci.debugger/scripts/break022/all.T
+++ b/tests/ghci.debugger/scripts/break022/all.T
@@ -1,4 +1,4 @@
 setTestOpts(extra_run_opts('-ignore-dot-ghci'))
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 
 test('break022', extra_clean(['A.hs']), ghci_script, ['break022.script'])
diff --git a/tests/ghci.debugger/scripts/break023/all.T b/tests/ghci.debugger/scripts/break023/all.T
index 0c33302e4..22b608e31 100644
--- a/tests/ghci.debugger/scripts/break023/all.T
+++ b/tests/ghci.debugger/scripts/break023/all.T
@@ -1,4 +1,4 @@
 setTestOpts(extra_run_opts('-ignore-dot-ghci'))
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 
 test('break023', extra_clean(['A.hs']), ghci_script, ['break023.script'])
diff --git a/tests/ghci/linking/all.T b/tests/ghci/linking/all.T
index d4724ca1e..ce00b3e58 100644
--- a/tests/ghci/linking/all.T
+++ b/tests/ghci/linking/all.T
@@ -1,5 +1,5 @@
 test('ghcilink001',
-     [if_ghci_dynamic(expect_fail), # dynamic ghci can't load '.a's
+     [when(ghci_dynamic(), expect_fail), # dynamic ghci can't load '.a's
       skip_if_no_ghci,
       extra_clean(['dir001/*','dir001'])],
      run_command,
@@ -21,7 +21,7 @@ test('ghcilink003',
      ['$MAKE -s --no-print-directory ghcilink003'])
 
 test('ghcilink004',
-     [if_ghci_dynamic(expect_fail), # dynamic ghci can't load '.a's
+     [when(ghci_dynamic(), expect_fail), # dynamic ghci can't load '.a's
       skip_if_no_ghci,
       extra_clean(['dir004/*','dir004'])],
      run_command,
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index 0b8f62e99..e558bf6b2 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -1,6 +1,6 @@
 # coding=utf8
 
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 
 test('ghci001', combined_output, ghci_script, ['ghci001.script'])
 test('ghci002', combined_output, ghci_script, ['ghci002.script'])
diff --git a/tests/ghci/should_run/all.T b/tests/ghci/should_run/all.T
index fa03ac116..f4d06a6f9 100644
--- a/tests/ghci/should_run/all.T
+++ b/tests/ghci/should_run/all.T
@@ -1,5 +1,5 @@
 
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 
 # We only want to run these tests with GHCi
 def just_ghci( name, opts ):
diff --git a/tests/indexed-types/should_compile/all.T b/tests/indexed-types/should_compile/all.T
index 019c5aca4..a73f5fd64 100644
--- a/tests/indexed-types/should_compile/all.T
+++ b/tests/indexed-types/should_compile/all.T
@@ -159,7 +159,7 @@ test('T4484', normal, compile, [''])
 test('T4492', normal, compile, [''])
 test('T4494', normal, compile, [''])
 test('DataFamDeriv', normal, compile, [''])
-test('T1769', if_compiler_lt('ghc', '7.1', expect_fail), compile, [''])
+test('T1769', when(compiler_lt('ghc', '7.1'), expect_fail), compile, [''])
 test('T4497', normal, compile, [''])
 test('T3484', normal, compile, [''])
 test('T3460', normal, compile, [''])
diff --git a/tests/indexed-types/should_fail/all.T b/tests/indexed-types/should_fail/all.T
index 19b05e63d..e99b79676 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -65,7 +65,7 @@ test('T2239', normal, compile_fail, [''])
 test('T3440', normal, compile_fail, [''])
 test('T4485', normal, compile_fail, [''])
 test('T4174', normal, compile_fail, [''])
-test('DerivUnsatFam', if_compiler_lt('ghc', '7.1', expect_fail), compile_fail, [''])
+test('DerivUnsatFam', when(compiler_lt('ghc', '7.1'), expect_fail), compile_fail, [''])
 test('T2664', normal, compile_fail, [''])
 test('T2664a', normal, compile, [''])
 test('T2544', normal, compile_fail, [''])
diff --git a/tests/layout/all.T b/tests/layout/all.T
index 026ad465a..e8ed2fe5b 100644
--- a/tests/layout/all.T
+++ b/tests/layout/all.T
@@ -39,7 +39,7 @@ test('layout007',
      [req_interp,
       extra_clean(['layout007.hi', 'layout007.o']),
       only_compiler_types(['ghc']),
-      if_compiler_profiled(skip)],
+      when(compiler_profiled(), skip)],
      run_command,
      ['$MAKE -s --no-print-directory layout007'])
 
diff --git a/tests/module/all.T b/tests/module/all.T
index b8a5355a9..8eaa1d521 100644
--- a/tests/module/all.T
+++ b/tests/module/all.T
@@ -251,7 +251,7 @@ test('mod150', normal, compile_fail, [''])
 test('mod151', normal, compile_fail, [''])
 test('mod152', normal, compile_fail, [''])
 test('mod153', normal, compile_fail, [''])
-test('mod154', if_compiler_type('hugs', expect_fail), compile, [''])
+test('mod154', when(compiler_type('hugs'), expect_fail), compile, [''])
 test('mod155', normal, compile_fail, [''])
 test('mod156', normal, compile, [''])
 test('mod157', 
diff --git a/tests/module/base01/all.T b/tests/module/base01/all.T
index d0dbb2960..6fa3e5c37 100644
--- a/tests/module/base01/all.T
+++ b/tests/module/base01/all.T
@@ -1,7 +1,7 @@
 setTestOpts(only_compiler_types(['ghc']))
 
 test('base01',
-     [if_compiler_lt('ghc', '7.1', expect_fail),
+     [when(compiler_lt('ghc', '7.1'), expect_fail),
       normalise_slashes,
       clean_cmd('$MAKE -s clean')],
      run_command,
diff --git a/tests/parser/should_compile/all.T b/tests/parser/should_compile/all.T
index 9d3b4e698..b10cd2ccf 100644
--- a/tests/parser/should_compile/all.T
+++ b/tests/parser/should_compile/all.T
@@ -45,8 +45,8 @@ test('read029', normal, compile, [''])
 test('read030', normal, compile, [''])
 test('read031', normal, compile, [''])
 test('read032', normal, compile, [''])
-test('read033', if_compiler_type('hugs', expect_fail), compile, [''])
-test('read034', if_compiler_type('hugs', expect_fail), compile, [''])
+test('read033', when(compiler_type('hugs'), expect_fail), compile, [''])
+test('read034', when(compiler_type('hugs'), expect_fail), compile, [''])
 test('read036', normal, compile, [''])
 test('read037', normal, compile, [''])
 test('read038', normal, compile, [''])
@@ -90,7 +90,7 @@ test('NondecreasingIndentation', normal, compile, [''])
 test('mc15', normal, compile, [''])
 test('mc16', normal, compile, [''])
 test('EmptyDecls', normal, compile, [''])
-test('ParserLambdaCase', if_compiler_lt('ghc', '7.5', skip), compile, [''])
+test('ParserLambdaCase', when(compiler_lt('ghc', '7.5'), skip), compile, [''])
 
 test('T5243', extra_clean(['T5243A.hi', 'T5243A.o']),
      multimod_compile, ['T5243',''])
diff --git a/tests/parser/should_fail/all.T b/tests/parser/should_fail/all.T
index 114524aff..a09b76df1 100644
--- a/tests/parser/should_fail/all.T
+++ b/tests/parser/should_fail/all.T
@@ -23,7 +23,7 @@ test('readFail020', normal, compile_fail, [''])
 # empty file (length zero) is not a legal Haskell module.  It fails to compile
 # because it doesn't contain a definition of Main.main.  GHC 5.02 crashed
 # on this example.
-test('readFail021', if_compiler_type('hugs', expect_fail), compile_fail, [''])
+test('readFail021', when(compiler_type('hugs'), expect_fail), compile_fail, [''])
 
 test('readFail022', normal, compile_fail, [''])
 test('readFail023', normal, compile_fail, [''])
@@ -72,8 +72,8 @@ test('NondecreasingIndentationFail', normal, compile_fail, [''])
 test('readFailTraditionalRecords1', normal, compile_fail, [''])
 test('readFailTraditionalRecords2', normal, compile_fail, [''])
 test('readFailTraditionalRecords3', normal, compile_fail, [''])
-test('ParserNoLambdaCase', if_compiler_lt('ghc', '7.5', skip), compile_fail, [''])
-test('ParserNoMultiWayIf', if_compiler_lt('ghc', '7.5', skip), compile_fail, [''])
+test('ParserNoLambdaCase', when(compiler_lt('ghc', '7.5'), skip), compile_fail, [''])
+test('ParserNoMultiWayIf', when(compiler_lt('ghc', '7.5'), skip), compile_fail, [''])
 
 test('T5425', normal, compile_fail, [''])
 test('T984', normal, compile_fail, [''])
diff --git a/tests/parser/should_run/all.T b/tests/parser/should_run/all.T
index 03951a1ed..eee0330e5 100644
--- a/tests/parser/should_run/all.T
+++ b/tests/parser/should_run/all.T
@@ -5,4 +5,4 @@ test('readRun004', normal, compile_and_run, ['-fobject-code'])
 test('T1344', normal, compile_and_run, [''])
 test('operator', normal, compile_and_run, [''])
 test('operator2', normal, compile_and_run, [''])
-test('ParserMultiWayIf', if_compiler_lt('ghc', '7.5', skip), compile_and_run, [''])
+test('ParserMultiWayIf', when(compiler_lt('ghc', '7.5'), skip), compile_and_run, [''])
diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T
index baeb1801a..f8238df7e 100644
--- a/tests/perf/haddock/all.T
+++ b/tests/perf/haddock/all.T
@@ -1,6 +1,6 @@
 
 test('haddock.base',
-     [unless_in_tree_compiler(skip)
+     [unless(in_tree_compiler(), skip)
      ,stats_num_field('peak_megabytes_allocated',
           [(wordsize(64), 274, 10)
             # 2012-08-14: 240 (amd64/Linux)
@@ -41,7 +41,7 @@ test('haddock.base',
      ['../../../../libraries/base/dist-install/doc/html/base/base.haddock.t'])
 
 test('haddock.Cabal',
-     [unless_in_tree_compiler(skip)
+     [unless(in_tree_compiler(), skip)
      ,stats_num_field('peak_megabytes_allocated',
           [(wordsize(64), 217, 10)
             # 2012-08-14: 202 (amd64/Linux)
@@ -80,7 +80,7 @@ test('haddock.Cabal',
      ['../../../../libraries/Cabal/Cabal/dist-install/doc/html/Cabal/Cabal.haddock.t'])
 
 test('haddock.compiler',
-     [unless_in_tree_compiler(skip)
+     [unless(in_tree_compiler(), skip)
      ,stats_num_field('peak_megabytes_allocated',
           [(wordsize(64), 1240, 10)
             # 2012-08-14: 1203 (amd64/Linux)
diff --git a/tests/plugins/all.T b/tests/plugins/all.T
index 2f0fc44c9..874fcdb40 100644
--- a/tests/plugins/all.T
+++ b/tests/plugins/all.T
@@ -3,7 +3,7 @@ def f(name, opts):
 	opts.skip = 1
 
 setTestOpts(f)
-setTestOpts(if_compiler_lt('ghc', '7.1', skip))
+setTestOpts(when(compiler_lt('ghc', '7.1'), skip))
 
 test('plugins01',
      [pre_cmd('$MAKE -s --no-print-directory -C simple-plugin package.plugins01'),
diff --git a/tests/programs/life_space_leak/test.T b/tests/programs/life_space_leak/test.T
index 417342f38..a0cdc2c76 100644
--- a/tests/programs/life_space_leak/test.T
+++ b/tests/programs/life_space_leak/test.T
@@ -2,7 +2,7 @@
 test('life_space_leak',
      [skip_if_fast,
       extra_clean(['Main.hi', 'Main.o']),
-      if_compiler_type('hugs', expect_fail)],
+      when(compiler_type('hugs'), expect_fail)],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/rename/should_compile/all.T b/tests/rename/should_compile/all.T
index a1f1965bd..db1f4913e 100644
--- a/tests/rename/should_compile/all.T
+++ b/tests/rename/should_compile/all.T
@@ -161,7 +161,7 @@ test('T4240',
      ['$MAKE -s --no-print-directory T4240'])
 
 test('T4489', normal, compile, [''])
-test('T4478', if_compiler_lt('ghc', '7.1', expect_fail), compile, [''])
+test('T4478', when(compiler_lt('ghc', '7.1'), expect_fail), compile, [''])
 test('T4534', normal, compile, [''])
 
 test('mc09', normal, compile, [''])
diff --git a/tests/rts/all.T b/tests/rts/all.T
index 2276d3587..8da87aae6 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -51,7 +51,7 @@ test('T2783', [ omit_ways(['ghci']), exit_code(1) ], compile_and_run, [''])
 
 # Test the work-stealing deque implementation.  We run this test in
 # both threaded1 (-threaded -debug) and threaded2 (-threaded) ways.
-test('testwsdeque', [unless_in_tree_compiler(skip),
+test('testwsdeque', [unless(in_tree_compiler(), skip),
                     c_src, only_ways(['threaded1', 'threaded2'])],
                     compile_and_run, ['-I../../../rts'])
 
diff --git a/tests/simplCore/should_compile/all.T b/tests/simplCore/should_compile/all.T
index 57871490c..765a12826 100644
--- a/tests/simplCore/should_compile/all.T
+++ b/tests/simplCore/should_compile/all.T
@@ -64,7 +64,7 @@ test('T4908', only_ways(['optasm']),
               compile,
               ['-O2 -ddump-simpl -dsuppress-uniques'])
 
-test('T4930', [if_compiler_lt('ghc', '7.1', expect_fail),
+test('T4930', [when(compiler_lt('ghc', '7.1'), expect_fail),
                only_ways(['optasm'])],
               compile,
               ['-O -ddump-simpl -dsuppress-uniques'])
@@ -109,7 +109,7 @@ test('T4918',
      ['$MAKE -s --no-print-directory T4918'])
 
 test('T4945',
-     if_compiler_lt('ghc', '7.1', expect_fail),
+     when(compiler_lt('ghc', '7.1'), expect_fail),
      run_command,
      ['$MAKE -s --no-print-directory T4945'])
 
diff --git a/tests/th/T2014/all.T b/tests/th/T2014/all.T
index 212690d6f..77709c23c 100644
--- a/tests/th/T2014/all.T
+++ b/tests/th/T2014/all.T
@@ -1,4 +1,4 @@
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 
 test('T2014',
      [req_interp,
diff --git a/tests/th/TH_import_loop/TH_import_loop.T b/tests/th/TH_import_loop/TH_import_loop.T
index 37059e1d6..8a4a180c2 100644
--- a/tests/th/TH_import_loop/TH_import_loop.T
+++ b/tests/th/TH_import_loop/TH_import_loop.T
@@ -1,5 +1,5 @@
 
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 
 test('TH_import_loop',
      [extra_clean(['ModuleA.o-boot', 'ModuleA.hi-boot',
diff --git a/tests/th/TH_spliceViewPat/test.T b/tests/th/TH_spliceViewPat/test.T
index b177c075b..23b4f6a1b 100644
--- a/tests/th/TH_spliceViewPat/test.T
+++ b/tests/th/TH_spliceViewPat/test.T
@@ -6,7 +6,7 @@ def f(name, opts):
 setTestOpts(f)
 setTestOpts(only_compiler_types(['ghc']))
 setTestOpts(only_ways(['normal','ghci']))
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 
 test('TH_spliceViewPat',
      extra_clean(['Main.o', 'Main.hi', 'A.o', 'A.hi']),
diff --git a/tests/th/all.T b/tests/th/all.T
index e9c6c08cd..caaa3df16 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -1,7 +1,7 @@
 
 # This test needs to come before the setTestOpts calls below, as we want
-# to run it !if_compiler_profiled
-test('T4255', unless_compiler_profiled(skip), compile_fail, ['-v0'])
+# to run it if !compiler_profiled
+test('T4255', unless(compiler_profiled(), skip), compile_fail, ['-v0'])
 
 def f(name, opts):
   opts.extra_hc_opts = '-XTemplateHaskell -package template-haskell'
@@ -11,7 +11,7 @@ def f(name, opts):
 setTestOpts(f)
 setTestOpts(only_compiler_types(['ghc']))
 setTestOpts(only_ways(['normal','ghci']))
-setTestOpts(if_compiler_profiled(skip))
+setTestOpts(when(compiler_profiled(), skip))
 
 test('TH_mkName', normal, compile, ['-v0'])
 test('TH_1tuple', normal, compile_fail, ['-v0'])
diff --git a/tests/typecheck/should_compile/all.T b/tests/typecheck/should_compile/all.T
index da9123369..0fdb2ad46 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -84,7 +84,7 @@ test('tc079', normal, compile, [''])
 test('tc080', normal, compile, [''])
 test('tc081', normal, compile, [''])
 test('tc082', normal, compile, [''])
-test('tc084', if_compiler_type('hugs', expect_fail), compile, [''])
+test('tc084', when(compiler_type('hugs'), expect_fail), compile, [''])
 test('tc085', only_compiler_types(['ghc']), compile, [''])
 test('tc086', normal, compile, [''])
 test('tc087', normal, compile, [''])
@@ -96,7 +96,7 @@ test('tc092', normal, compile, [''])
 test('tc093', normal, compile, [''])
 test('tc094', normal, compile, [''])
 test('tc095', normal, compile, [''])
-test('tc096', if_compiler_type('hugs', expect_fail), compile, [''])
+test('tc096', when(compiler_type('hugs'), expect_fail), compile, [''])
 test('tc097', normal, compile, [''])
 test('tc098', normal, compile, [''])
 test('tc099', normal, compile, [''])
@@ -380,7 +380,7 @@ test('T6055', normal, compile, [''])
 test('DfltProb1', normal, compile, [''])
 test('DfltProb2', normal, compile, [''])
 test('T6134', normal, compile, [''])
-test('TcLambdaCase', if_compiler_lt('ghc', '7.5', skip), compile, [''])
+test('TcLambdaCase', when(compiler_lt('ghc', '7.5'), skip), compile, [''])
 test('T7147', normal, compile, [''])
 test('T7171',normal,run_command,
      ['$MAKE -s --no-print-directory T7171'])
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index 1241e587f..9cffd3d98 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -24,7 +24,7 @@ test('tcfail023', normal, compile_fail, [''])
 test('tcfail027', normal, compile_fail, [''])
 test('tcfail028', normal, compile_fail, [''])
 test('tcfail029', normal, compile_fail, [''])
-test('tcfail030', if_compiler_type('hugs', expect_fail), compile_fail, [''])
+test('tcfail030', when(compiler_type('hugs'), expect_fail), compile_fail, [''])
 test('tcfail031', normal, compile_fail, [''])
 test('tcfail032', normal, compile_fail, [''])
 test('tcfail033', normal, compile_fail, [''])
@@ -278,7 +278,7 @@ test('FDsFromGivens', normal, compile_fail, [''])
 test('T7019', normal, compile_fail,[''])
 test('T7019a', normal, compile_fail,[''])
 test('T5978', normal, compile_fail, [''])
-test('TcMultiWayIfFail', if_compiler_lt('ghc', '7.5', skip), compile_fail, [''])
+test('TcMultiWayIfFail', when(compiler_lt('ghc', '7.5'), skip), compile_fail, [''])
 test('T2534', normal, compile_fail, [''])
 test('T7175', normal, compile_fail, [''])
 test('T7210', normal, compile_fail, [''])
-- 
GitLab


From 46e40965bef66206b0e39dc362e7591a46f8953e Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 15:11:52 +0000
Subject: [PATCH 135/223] Convert more helpers

---
 driver/testlib.py | 13 ++-----------
 tests/esc/all.T   |  2 +-
 2 files changed, 3 insertions(+), 12 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 942a7222e..7fcdaefe8 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -387,17 +387,8 @@ def _namebase( opts, nb ):
 
 # ---
 
-def if_tag( tag, f ):
-    if tag in config.compiler_tags:
-        return f
-    else:
-        return normal
-
-def unless_tag( tag, f ):
-    if not (tag in config.compiler_tags):
-        return f
-    else:
-        return normal
+def tag( t ):
+    return t in config.compiler_tags
 
 # ---
 def high_memory_usage(name, opts):
diff --git a/tests/esc/all.T b/tests/esc/all.T
index 55b21ee2a..31a4ba525 100644
--- a/tests/esc/all.T
+++ b/tests/esc/all.T
@@ -1,4 +1,4 @@
-esc = unless_tag('esc', skip)
+esc = unless(tag('esc'), skip)
 
 test('TestList', esc, compile, ['-fesc'])
 test('TestImport', esc, compile, ['-fesc'])
-- 
GitLab


From 53c525b5d64911efec1b806978e6893490f239e9 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 15:39:12 +0000
Subject: [PATCH 136/223] More helper conversions

---
 driver/testlib.py                            |  9 ++----
 tests/annotations/should_run/all.T           |  2 +-
 tests/array/should_run/all.T                 | 34 ++++++++++----------
 tests/arrows/should_run/all.T                |  4 +--
 tests/concurrent/T2317/all.T                 |  2 +-
 tests/concurrent/prog001/all.T               |  2 +-
 tests/concurrent/prog002/all.T               |  2 +-
 tests/concurrent/prog003/all.T               |  2 +-
 tests/concurrent/should_run/all.T            |  4 +--
 tests/deSugar/should_run/all.T               |  4 +--
 tests/deriving/should_run/all.T              | 34 ++++++++++----------
 tests/dph/diophantine/dph-diophantine.T      |  2 +-
 tests/dph/dotp/dph-dotp.T                    |  4 +--
 tests/dph/nbody/dph-nbody.T                  |  4 +--
 tests/dph/primespj/dph-primespj.T            |  2 +-
 tests/dph/quickhull/dph-quickhull.T          |  4 +--
 tests/dph/smvm/dph-smvm.T                    |  4 +--
 tests/dph/words/dph-words.T                  |  4 +--
 tests/driver/dynamic_flags_001/all.T         |  2 +-
 tests/driver/dynamic_flags_002/all.T         | 16 ++++++---
 tests/driver/recomp001/all.T                 |  2 +-
 tests/driver/recomp002/all.T                 |  2 +-
 tests/driver/recomp005/all.T                 |  2 +-
 tests/driver/recomp006/all.T                 |  3 +-
 tests/driver/recomp007/all.T                 |  2 +-
 tests/driver/recomp008/all.T                 |  2 +-
 tests/ffi/should_run/all.T                   |  2 +-
 tests/gadt/all.T                             | 12 +++----
 tests/ghc-api/T4891/all.T                    |  2 +-
 tests/ghc-api/all.T                          |  2 +-
 tests/ghc-api/apirecomp001/all.T             |  5 ++-
 tests/ghci/scripts/all.T                     |  2 +-
 tests/programs/10queens/test.T               |  2 +-
 tests/programs/Queens/test.T                 |  2 +-
 tests/programs/andre_monad/test.T            |  2 +-
 tests/programs/andy_cherry/test.T            |  2 +-
 tests/programs/barton-mangler-bug/test.T     |  2 +-
 tests/programs/cholewo-eval/test.T           |  2 +-
 tests/programs/cvh_unboxing/test.T           |  2 +-
 tests/programs/fast2haskell/test.T           |  2 +-
 tests/programs/fun_insts/test.T              |  2 +-
 tests/programs/galois_raytrace/test.T        |  2 +-
 tests/programs/jl_defaults/test.T            |  2 +-
 tests/programs/joao-circular/test.T          |  2 +-
 tests/programs/jq_readsPrec/test.T           |  2 +-
 tests/programs/jtod_circint/test.T           |  2 +-
 tests/programs/jules_xref/test.T             |  2 +-
 tests/programs/jules_xref2/test.T            |  2 +-
 tests/programs/launchbury/test.T             |  2 +-
 tests/programs/lennart_range/test.T          |  2 +-
 tests/programs/lex/test.T                    |  2 +-
 tests/programs/life_space_leak/test.T        |  2 +-
 tests/programs/maessen-hashtab/test.T        |  2 +-
 tests/programs/north_array/test.T            |  2 +-
 tests/programs/okeefe_neural/test.T          |  2 +-
 tests/programs/record_upd/test.T             |  2 +-
 tests/programs/rittri/test.T                 |  2 +-
 tests/programs/sanders_array/test.T          |  2 +-
 tests/programs/seward-space-leak/test.T      |  2 +-
 tests/programs/strict_anns/test.T            |  2 +-
 tests/programs/thurston-modular-arith/test.T |  2 +-
 tests/quasiquotation/qq005/test.T            |  2 +-
 tests/quasiquotation/qq006/test.T            |  2 +-
 tests/quasiquotation/qq007/test.T            |  2 +-
 tests/quasiquotation/qq008/test.T            |  2 +-
 tests/rts/all.T                              |  2 +-
 tests/simplCore/should_compile/all.T         |  4 +--
 tests/typecheck/prog001/test.T               |  2 +-
 tests/typecheck/prog002/test.T               |  2 +-
 tests/typecheck/testeq1/test.T               |  2 +-
 70 files changed, 132 insertions(+), 125 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 7fcdaefe8..89d6c2e04 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -299,12 +299,6 @@ def skip_if_no_ghci(name, opts):
 
 # ----
 
-def skip_if_fast(name, opts):
-    if config.fast:
-        opts.skip = 1
-
-# -----
-
 def when(b, f):
     # When list_brokens is on, we want to see all expect_broken calls,
     # so we always do f
@@ -316,6 +310,9 @@ def when(b, f):
 def unless(b, f):
     return when(not b, f)
 
+def fast():
+    return config.fast
+
 def platform( plat ):
     return config.platform == plat
 
diff --git a/tests/annotations/should_run/all.T b/tests/annotations/should_run/all.T
index 6616de5df..444ac3091 100644
--- a/tests/annotations/should_run/all.T
+++ b/tests/annotations/should_run/all.T
@@ -1,6 +1,6 @@
 setTestOpts(when(compiler_profiled(), skip))
 # These tests are very slow due to their use of package GHC
-setTestOpts(skip_if_fast)
+setTestOpts(when(fast(), skip))
 
 # Annotations, like Template Haskell, require runtime evaluation.  In
 # order for this to work with profiling, we would have to build the
diff --git a/tests/array/should_run/all.T b/tests/array/should_run/all.T
index eee3b123d..a0cfc6be3 100644
--- a/tests/array/should_run/all.T
+++ b/tests/array/should_run/all.T
@@ -4,23 +4,23 @@
 #               extra run flags
 #               expected process return value, if not zero
 
-test('arr001', skip_if_fast, compile_and_run, [''])
-test('arr002', skip_if_fast, compile_and_run, [''])
-test('arr003', compose(skip_if_fast,exit_code(1)), compile_and_run, [''])
-test('arr004', compose(skip_if_fast,exit_code(1)), compile_and_run, [''])
-test('arr005', skip_if_fast, compile_and_run, [''])
-test('arr006', skip_if_fast, compile_and_run, [''])
-test('arr007', compose(skip_if_fast,exit_code(1)), compile_and_run, [''])
-test('arr008', compose(skip_if_fast,exit_code(1)), compile_and_run, [''])
-test('arr009', skip_if_fast, compile_and_run, [''])
-test('arr010', skip_if_fast, compile_and_run, [''])
-test('arr011', skip_if_fast, compile_and_run, [''])
-test('arr012', skip_if_fast, compile_and_run, [''])
-test('arr013', skip_if_fast, compile_and_run, [''])
-test('arr014', skip_if_fast, compile_and_run, [''])
-test('arr015', skip_if_fast, compile_and_run, [''])
+test('arr001', when(fast(), skip), compile_and_run, [''])
+test('arr002', when(fast(), skip), compile_and_run, [''])
+test('arr003', compose(when(fast(), skip),exit_code(1)), compile_and_run, [''])
+test('arr004', compose(when(fast(), skip),exit_code(1)), compile_and_run, [''])
+test('arr005', when(fast(), skip), compile_and_run, [''])
+test('arr006', when(fast(), skip), compile_and_run, [''])
+test('arr007', compose(when(fast(), skip),exit_code(1)), compile_and_run, [''])
+test('arr008', compose(when(fast(), skip),exit_code(1)), compile_and_run, [''])
+test('arr009', when(fast(), skip), compile_and_run, [''])
+test('arr010', when(fast(), skip), compile_and_run, [''])
+test('arr011', when(fast(), skip), compile_and_run, [''])
+test('arr012', when(fast(), skip), compile_and_run, [''])
+test('arr013', when(fast(), skip), compile_and_run, [''])
+test('arr014', when(fast(), skip), compile_and_run, [''])
+test('arr015', when(fast(), skip), compile_and_run, [''])
 test('arr016', reqlib('random'), compile_and_run, [''])
-test('arr017', skip_if_fast, compile_and_run, [''])
-test('arr018', skip_if_fast, compile_and_run, [''])
+test('arr017', when(fast(), skip), compile_and_run, [''])
+test('arr018', when(fast(), skip), compile_and_run, [''])
 test('arr019', normal, compile_and_run, [''])
 test('arr020', normal, compile_and_run, [''])
diff --git a/tests/arrows/should_run/all.T b/tests/arrows/should_run/all.T
index a9867dd39..ec26c1fa9 100644
--- a/tests/arrows/should_run/all.T
+++ b/tests/arrows/should_run/all.T
@@ -1,8 +1,8 @@
 setTestOpts(only_compiler_types(['ghc']))
 
 test('arrowrun001', normal, compile_and_run, [''])
-test('arrowrun002', skip_if_fast, compile_and_run, [''])
+test('arrowrun002', when(fast(), skip), compile_and_run, [''])
 test('arrowrun003', normal, compile_and_run, [''])
-test('arrowrun004', skip_if_fast, compile_and_run, [''])
+test('arrowrun004', when(fast(), skip), compile_and_run, [''])
 test('T3822', normal, compile_and_run, [''])
 
diff --git a/tests/concurrent/T2317/all.T b/tests/concurrent/T2317/all.T
index 0ad9db3dc..c9bcda243 100644
--- a/tests/concurrent/T2317/all.T
+++ b/tests/concurrent/T2317/all.T
@@ -1,5 +1,5 @@
 test('T2317',
-     [skip_if_fast,
+     [when(fast(), skip),
       reqlib('parallel'), reqlib('random')],
      multimod_compile_and_run,
      ['T2317',''])
diff --git a/tests/concurrent/prog001/all.T b/tests/concurrent/prog001/all.T
index 70f38dca4..a3ba7b61f 100644
--- a/tests/concurrent/prog001/all.T
+++ b/tests/concurrent/prog001/all.T
@@ -13,7 +13,7 @@
 # right now. --SDM 1/4/2010
 
 test('concprog001',
-     [skip_if_fast,
+     [when(fast(), skip),
       only_ways(['threaded2']),
       extra_clean(['Arithmetic.hi', 'Arithmetic.o',
                    'Converter.hi',  'Converter.o',
diff --git a/tests/concurrent/prog002/all.T b/tests/concurrent/prog002/all.T
index bef9de3bb..54613a7e4 100644
--- a/tests/concurrent/prog002/all.T
+++ b/tests/concurrent/prog002/all.T
@@ -13,7 +13,7 @@ test('concprog002',
      [only_ways(['threaded2','threaded2_hT']),
       extra_ways(ways),
       exit_code(1),
-      skip_if_fast,
+      when(fast(), skip),
       reqlib('random'),
       extra_clean(['Event.hi',     'Event.o',
                    'Scheduler.hi', 'Scheduler.o',
diff --git a/tests/concurrent/prog003/all.T b/tests/concurrent/prog003/all.T
index 874b3967d..7522b1001 100644
--- a/tests/concurrent/prog003/all.T
+++ b/tests/concurrent/prog003/all.T
@@ -10,7 +10,7 @@
 # occasionally, but at least the test is here for posterity.
 
 test('concprog003',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean([
            'BackList2.hi', 'BackList2.o',
            'ImmList.hi', 'ImmList.o',
diff --git a/tests/concurrent/should_run/all.T b/tests/concurrent/should_run/all.T
index d5ceb7257..0a0778b6b 100644
--- a/tests/concurrent/should_run/all.T
+++ b/tests/concurrent/should_run/all.T
@@ -127,7 +127,7 @@ if config.platform == 'i386-unknown-mingw32':
 else:
    conc023_ways = normal
 
-test('conc023', composes([skip_if_fast,
+test('conc023', composes([when(fast(), skip),
                           only_compiler_types(['ghc']),
                           reqlib('random'),
                           conc023_ways]), compile_and_run, [''])
@@ -170,7 +170,7 @@ test('conc036', skip, compile_and_run, [''])
 
 
 # Interrupting foreign calls only makes sense if we are threaded
-test('foreignInterruptible', [skip_if_fast,
+test('foreignInterruptible', [when(fast(), skip),
                               when(opsys('mingw32'),expect_fail),
                               # I don't think we support interrupting Sleep()
                               # on Windows.  --SDM
diff --git a/tests/deSugar/should_run/all.T b/tests/deSugar/should_run/all.T
index 90d76a964..352a65239 100644
--- a/tests/deSugar/should_run/all.T
+++ b/tests/deSugar/should_run/all.T
@@ -13,8 +13,8 @@ test('dsrun007', exit_code(1), compile_and_run, [''])
 test('dsrun008', exit_code(1), compile_and_run, [''])
 test('dsrun009', normal, compile_and_run, [''])
 test('dsrun010', normal, compile_and_run, [''])
-test('dsrun011', skip_if_fast, compile_and_run, [''])
-test('dsrun012', skip_if_fast, compile_and_run, [''])
+test('dsrun011', when(fast(), skip), compile_and_run, [''])
+test('dsrun012', when(fast(), skip), compile_and_run, [''])
 test('dsrun013', normal, compile_and_run, [''])
 test('dsrun014', normal, compile_and_run, ['-fobject-code'])
 test('dsrun015', normal, compile_and_run, [''])
diff --git a/tests/deriving/should_run/all.T b/tests/deriving/should_run/all.T
index 480bdbada..eeda9aa72 100644
--- a/tests/deriving/should_run/all.T
+++ b/tests/deriving/should_run/all.T
@@ -3,24 +3,24 @@
 #	extra run flags
 #	expected process return value, if not zero
 
-test('drvrun001', skip_if_fast, compile_and_run, [''])
-test('drvrun002', skip_if_fast, compile_and_run, [''])
-test('drvrun003', skip_if_fast, compile_and_run, [''])
-test('drvrun004', skip_if_fast, compile_and_run, [''])
-test('drvrun005', skip_if_fast, compile_and_run, [''])
+test('drvrun001', when(fast(), skip), compile_and_run, [''])
+test('drvrun002', when(fast(), skip), compile_and_run, [''])
+test('drvrun003', when(fast(), skip), compile_and_run, [''])
+test('drvrun004', when(fast(), skip), compile_and_run, [''])
+test('drvrun005', when(fast(), skip), compile_and_run, [''])
 test('drvrun006', normal, compile_and_run, [''])
-test('drvrun007', skip_if_fast, compile_and_run, [''])
-test('drvrun008', skip_if_fast, compile_and_run, ['-funbox-strict-fields'])
-test('drvrun009', skip_if_fast, compile_and_run, [''])
-test('drvrun010', skip_if_fast, compile_and_run, [''])
-test('drvrun011', skip_if_fast, compile_and_run, [''])
-test('drvrun012', skip_if_fast, compile_and_run, [''])
-test('drvrun013', skip_if_fast, compile_and_run, [''])
-test('drvrun014', skip_if_fast, compile_and_run, [''])
-test('drvrun015', skip_if_fast, compile_and_run, [''])
-test('drvrun016', skip_if_fast, compile_and_run, ['-funbox-strict-fields'])
-test('drvrun017', compose(skip_if_fast, only_compiler_types(['ghc'])), compile_and_run, [''])
-test('drvrun018', skip_if_fast, compile_and_run, [''])
+test('drvrun007', when(fast(), skip), compile_and_run, [''])
+test('drvrun008', when(fast(), skip), compile_and_run, ['-funbox-strict-fields'])
+test('drvrun009', when(fast(), skip), compile_and_run, [''])
+test('drvrun010', when(fast(), skip), compile_and_run, [''])
+test('drvrun011', when(fast(), skip), compile_and_run, [''])
+test('drvrun012', when(fast(), skip), compile_and_run, [''])
+test('drvrun013', when(fast(), skip), compile_and_run, [''])
+test('drvrun014', when(fast(), skip), compile_and_run, [''])
+test('drvrun015', when(fast(), skip), compile_and_run, [''])
+test('drvrun016', when(fast(), skip), compile_and_run, ['-funbox-strict-fields'])
+test('drvrun017', compose(when(fast(), skip), only_compiler_types(['ghc'])), compile_and_run, [''])
+test('drvrun018', when(fast(), skip), compile_and_run, [''])
 test('drvrun019', normal, compile_and_run, [''])
 test('drvrun020', normal, compile_and_run, [''])
 test('drvrun021', normal, compile_and_run, [''])
diff --git a/tests/dph/diophantine/dph-diophantine.T b/tests/dph/diophantine/dph-diophantine.T
index b2b772179..1636f5aaa 100644
--- a/tests/dph/diophantine/dph-diophantine.T
+++ b/tests/dph/diophantine/dph-diophantine.T
@@ -1,6 +1,6 @@
 
 test    ('dph-diophantine-copy-opt' 
-        , [ skip_if_fast
+        , [ when(fast(), skip)
           , outputdir('opt')
           , reqlib('dph-lifted-copy')
           , reqlib('dph-prim-par')
diff --git a/tests/dph/dotp/dph-dotp.T b/tests/dph/dotp/dph-dotp.T
index bfdf7a2c7..8800d8430 100644
--- a/tests/dph/dotp/dph-dotp.T
+++ b/tests/dph/dotp/dph-dotp.T
@@ -1,7 +1,7 @@
 
 test    ('dph-dotp-copy-opt' 
         , [ outputdir('copy-opt')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-copy')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
@@ -11,7 +11,7 @@ test    ('dph-dotp-copy-opt'
 
 test    ('dph-dotp-vseg-opt' 
         , [ outputdir('vseg-opt')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-vseg')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
diff --git a/tests/dph/nbody/dph-nbody.T b/tests/dph/nbody/dph-nbody.T
index 429ef8fa3..9c0031d16 100644
--- a/tests/dph/nbody/dph-nbody.T
+++ b/tests/dph/nbody/dph-nbody.T
@@ -2,7 +2,7 @@
 test    ('dph-nbody-vseg-opt' 
         , [ high_memory_usage
           , outputdir('vseg-opt')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-vseg')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
@@ -14,7 +14,7 @@ test    ('dph-nbody-vseg-opt'
 test    ('dph-nbody-copy-opt' 
         , [ high_memory_usage
           , outputdir('copy-opt')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-copy')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
diff --git a/tests/dph/primespj/dph-primespj.T b/tests/dph/primespj/dph-primespj.T
index 6976974ed..84f41f9e2 100644
--- a/tests/dph/primespj/dph-primespj.T
+++ b/tests/dph/primespj/dph-primespj.T
@@ -1,7 +1,7 @@
 
 test    ('dph-primespj-copy-opt' 
         , [ outputdir('opt')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-copy')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
diff --git a/tests/dph/quickhull/dph-quickhull.T b/tests/dph/quickhull/dph-quickhull.T
index 14922821f..bae69814a 100644
--- a/tests/dph/quickhull/dph-quickhull.T
+++ b/tests/dph/quickhull/dph-quickhull.T
@@ -2,7 +2,7 @@
 test    ('dph-quickhull-copy-opt' 
         , [ high_memory_usage
           , outputdir('copy-opt')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-copy')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
@@ -14,7 +14,7 @@ test    ('dph-quickhull-copy-opt'
 test    ('dph-quickhull-vseg-opt' 
         , [ high_memory_usage
           , outputdir('vseg-opt')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-vseg')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2']) ] 
diff --git a/tests/dph/smvm/dph-smvm.T b/tests/dph/smvm/dph-smvm.T
index 14705a638..ae01eff83 100644
--- a/tests/dph/smvm/dph-smvm.T
+++ b/tests/dph/smvm/dph-smvm.T
@@ -17,7 +17,7 @@ elif config.platform.startswith('sparc-'):
 if testFile != 'nothing':
  test   ('dph-smvm-copy'
         , [ outputdir('copy')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-copy')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2'])
@@ -29,7 +29,7 @@ if testFile != 'nothing':
 
  test   ('dph-smvm-vseg'
         , [ outputdir('vseg')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-vseg')
           , reqlib('dph-prim-par')
           , only_ways(['normal', 'threaded1', 'threaded2'])
diff --git a/tests/dph/words/dph-words.T b/tests/dph/words/dph-words.T
index 04cddaee4..5301f08a9 100644
--- a/tests/dph/words/dph-words.T
+++ b/tests/dph/words/dph-words.T
@@ -2,7 +2,7 @@
 test    ('dph-words-copy-opt' 
         , [ high_memory_usage
           , outputdir('copy-opt')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-copy')
           , reqlib('dph-prim-par')
           , only_ways(['normal']) ] 
@@ -14,7 +14,7 @@ test    ('dph-words-copy-opt'
 test    ('dph-words-vseg-opt' 
         , [ high_memory_usage
           , outputdir('vseg-opt')
-          , skip_if_fast
+          , when(fast(), skip)
           , reqlib('dph-lifted-vseg')
           , reqlib('dph-prim-par')
           , only_ways(['normal']) ] 
diff --git a/tests/driver/dynamic_flags_001/all.T b/tests/driver/dynamic_flags_001/all.T
index c487a0cb7..19ed656e7 100644
--- a/tests/driver/dynamic_flags_001/all.T
+++ b/tests/driver/dynamic_flags_001/all.T
@@ -1,5 +1,5 @@
 test('dynamic_flags_001',
-     [skip_if_fast,
+     [when(fast(), skip),
       clean_cmd('$MAKE -s clean')],
      run_command,
      ['$MAKE -s --no-print-directory dynamic_flags_001'])
diff --git a/tests/driver/dynamic_flags_002/all.T b/tests/driver/dynamic_flags_002/all.T
index 3b0072ba6..e5a4a564f 100644
--- a/tests/driver/dynamic_flags_002/all.T
+++ b/tests/driver/dynamic_flags_002/all.T
@@ -1,6 +1,12 @@
-test('dynamic_flags_002A', skip_if_fast, multimod_compile, ['A_Main', '-v0'])
-test('dynamic_flags_002B', skip_if_fast, multimod_compile, ['B_Main', '-v0'])
-test('dynamic_flags_002C', skip_if_fast, multimod_compile, ['C_Main', '-v0'])
-test('dynamic_flags_002D', skip_if_fast, multimod_compile, ['D_Main', '-v0'])
-test('dynamic_flags_002Many', skip_if_fast, multimod_compile, ['ManyFirst ManySecond ManyThird', '-v0'])
+test('dynamic_flags_002A',
+     when(fast(), skip), multimod_compile, ['A_Main', '-v0'])
+test('dynamic_flags_002B',
+     when(fast(), skip), multimod_compile, ['B_Main', '-v0'])
+test('dynamic_flags_002C',
+     when(fast(), skip), multimod_compile, ['C_Main', '-v0'])
+test('dynamic_flags_002D',
+     when(fast(), skip), multimod_compile, ['D_Main', '-v0'])
+test('dynamic_flags_002Many',
+     when(fast(), skip), multimod_compile,
+     ['ManyFirst ManySecond ManyThird', '-v0'])
 
diff --git a/tests/driver/recomp001/all.T b/tests/driver/recomp001/all.T
index f3672fa2f..33202d624 100644
--- a/tests/driver/recomp001/all.T
+++ b/tests/driver/recomp001/all.T
@@ -1,5 +1,5 @@
 test('recomp001',
-     [skip_if_fast,
+     [when(fast(), skip),
       clean_cmd('$MAKE -s clean')],
      run_command,
      ['$MAKE -s --no-print-directory recomp001'])
diff --git a/tests/driver/recomp002/all.T b/tests/driver/recomp002/all.T
index 5f8ddf5f1..68f1a7967 100644
--- a/tests/driver/recomp002/all.T
+++ b/tests/driver/recomp002/all.T
@@ -1,5 +1,5 @@
 test('recomp002',
-     [skip_if_fast,
+     [when(fast(), skip),
       clean_cmd('$MAKE -s clean')],
      run_command,
      ['$MAKE -s --no-print-directory recomp002'])
diff --git a/tests/driver/recomp005/all.T b/tests/driver/recomp005/all.T
index d5d89b171..5282c5b68 100644
--- a/tests/driver/recomp005/all.T
+++ b/tests/driver/recomp005/all.T
@@ -1,5 +1,5 @@
 test('recomp005',
-     [skip_if_fast,
+     [when(fast(), skip),
       clean_cmd('$MAKE -s clean')],
      run_command, ['$MAKE -s --no-print-directory recomp005'])
 
diff --git a/tests/driver/recomp006/all.T b/tests/driver/recomp006/all.T
index bc4f915ba..f234e58e8 100644
--- a/tests/driver/recomp006/all.T
+++ b/tests/driver/recomp006/all.T
@@ -1,3 +1,4 @@
 test('recomp006',
-     [ skip_if_fast, extra_clean(['A.o','A.hi','B.o','B.hi','err','out']) ],
+     [ when(fast(), skip),
+       extra_clean(['A.o','A.hi','B.o','B.hi','err','out']) ],
      run_command, ['$MAKE -s --no-print-directory recomp006'])
diff --git a/tests/driver/recomp007/all.T b/tests/driver/recomp007/all.T
index 5a93a12d6..de562b627 100644
--- a/tests/driver/recomp007/all.T
+++ b/tests/driver/recomp007/all.T
@@ -3,7 +3,7 @@
 #   "Fix a recompilation checking bug when a package dependency changes"
 
 test('recomp007',
-     [ skip_if_fast, clean_cmd('$MAKE -s clean'), normalise_slashes ],
+     [ when(fast(), skip), clean_cmd('$MAKE -s clean'), normalise_slashes ],
      run_command,
      ['$MAKE -s --no-print-directory recomp007'])
 
diff --git a/tests/driver/recomp008/all.T b/tests/driver/recomp008/all.T
index a59b1512e..caf81d5ba 100644
--- a/tests/driver/recomp008/all.T
+++ b/tests/driver/recomp008/all.T
@@ -1,7 +1,7 @@
 # Test for #4469, a recompilation bug related to instances
 
 test('recomp008',
-     [ skip_if_fast, clean_cmd('$MAKE -s clean'), normalise_slashes ],
+     [ when(fast(), skip), clean_cmd('$MAKE -s clean'), normalise_slashes ],
      run_command,
      ['$MAKE -s --no-print-directory recomp008'])
 
diff --git a/tests/ffi/should_run/all.T b/tests/ffi/should_run/all.T
index a8d62ff70..01c60112b 100644
--- a/tests/ffi/should_run/all.T
+++ b/tests/ffi/should_run/all.T
@@ -67,7 +67,7 @@ if config.platform.startswith('i386-'):
    else:
         maybe_skip = only_ways(['ghci'])
 
-test('ffi009', [skip_if_fast, expect_fail_for(['extcore','optextcore']),
+test('ffi009', [when(fast(), skip), expect_fail_for(['extcore','optextcore']),
                 reqlib('random'),
                 maybe_skip] ,compile_and_run, [opts])
 
diff --git a/tests/gadt/all.T b/tests/gadt/all.T
index d55aef64e..e5f3c5c34 100644
--- a/tests/gadt/all.T
+++ b/tests/gadt/all.T
@@ -6,10 +6,10 @@ setTestOpts(only_compiler_types(['ghc']))
 # In fast mode, we omit all the compile_and_run tests except a couple
 
 test('gadt1', normal, compile, [''])
-test('gadt2', skip_if_fast, compile_and_run, [''])
+test('gadt2', when(fast(), skip), compile_and_run, [''])
 test('gadt3', normal, compile, [''])
-test('gadt4', skip_if_fast, compile_and_run, [''])
-test('gadt5', skip_if_fast, compile_and_run, [''])
+test('gadt4', when(fast(), skip), compile_and_run, [''])
+test('gadt5', when(fast(), skip), compile_and_run, [''])
 test('gadt6', normal, compile, [''])
 test('gadt7', normal, compile_fail, [''])
 test('gadt8', normal, compile, [''])
@@ -40,7 +40,7 @@ test('gadt23',
 test('gadt24', normal, compile, [''])
 
 test('red-black', normal, compile, [''])
-test('type-rep', skip_if_fast, compile_and_run, [''])
+test('type-rep', when(fast(), skip), compile_and_run, [''])
 test('equal', normal, compile, [''])
 test('nbe', normal, compile, [''])
 test('while', normal, compile_and_run, [''])
@@ -50,13 +50,13 @@ test('lazypatok', expect_fail, compile, [''])
 test('tc', normal, compile_and_run, [''])
 test('arrow', normal, compile, [''])
 test('tdpe', normal, compile, [''])
-test('Nilsson', skip_if_fast, compile, [''])
+test('Nilsson', when(fast(), skip), compile, [''])
 
 if config.fast:
     test('records', normal, compile, [''])
 else:
     test('records', normal, compile_and_run, [''])
-test('ubx-records', skip_if_fast, compile_and_run, [''])
+test('ubx-records', when(fast(), skip), compile_and_run, [''])
 test('records-fail1', normal, compile_fail, [''])
 
 test('doaitse', normal, compile, [''])
diff --git a/tests/ghc-api/T4891/all.T b/tests/ghc-api/T4891/all.T
index 5217e5371..64c25912f 100644
--- a/tests/ghc-api/T4891/all.T
+++ b/tests/ghc-api/T4891/all.T
@@ -1,3 +1,3 @@
-test('T4891', [skip_if_fast, extra_clean(['X.hi', 'X.o'])],
+test('T4891', [when(fast(), skip), extra_clean(['X.hi', 'X.o'])],
               run_command,
               ['$MAKE -s --no-print-directory T4891'])
diff --git a/tests/ghc-api/all.T b/tests/ghc-api/all.T
index 62cd1b50a..9fa767276 100644
--- a/tests/ghc-api/all.T
+++ b/tests/ghc-api/all.T
@@ -1,3 +1,3 @@
-test('T6145', [skip_if_fast],
+test('T6145', when(fast(), skip),
               run_command,
               ['$MAKE -s --no-print-directory T6145'])
diff --git a/tests/ghc-api/apirecomp001/all.T b/tests/ghc-api/apirecomp001/all.T
index 0aa92874d..f8f5abdf0 100644
--- a/tests/ghc-api/apirecomp001/all.T
+++ b/tests/ghc-api/apirecomp001/all.T
@@ -1 +1,4 @@
-test('apirecomp001', skip_if_fast, run_command, ['$MAKE -s --no-print-directory apirecomp001'])
+test('apirecomp001',
+     when(fast(), skip),
+     run_command,
+     ['$MAKE -s --no-print-directory apirecomp001'])
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index e558bf6b2..ee34ce97a 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -37,7 +37,7 @@ test('ghci022', normal, ghci_script, ['ghci022.script'])
 
 test('ghci023', normal, ghci_script, ['ghci023.script'])
 test('ghci024',
-     [skip_if_fast,
+     [when(fast(), skip),
       when(platform("powerpc-apple-darwin"), expect_broken(1845))],
      run_command,
      ['$MAKE -s --no-print-directory ghci024'])
diff --git a/tests/programs/10queens/test.T b/tests/programs/10queens/test.T
index 4d2b7579b..ac0435150 100644
--- a/tests/programs/10queens/test.T
+++ b/tests/programs/10queens/test.T
@@ -1,6 +1,6 @@
 
 test('10queens',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
diff --git a/tests/programs/Queens/test.T b/tests/programs/Queens/test.T
index 044ebf6a2..77cf3750b 100644
--- a/tests/programs/Queens/test.T
+++ b/tests/programs/Queens/test.T
@@ -1,6 +1,6 @@
 
 test('queens',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Main.hi', 'Main.o'])],
      compile_and_run,
      [''])
diff --git a/tests/programs/andre_monad/test.T b/tests/programs/andre_monad/test.T
index e5ad78fed..619f4fd1e 100644
--- a/tests/programs/andre_monad/test.T
+++ b/tests/programs/andre_monad/test.T
@@ -1,6 +1,6 @@
 # exhausts Hugs's heap (CAF leak)
 test('andre_monad',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Main.hi', 'Main.o']),
       omit_compiler_types(['hugs'])],
      multimod_compile_and_run,
diff --git a/tests/programs/andy_cherry/test.T b/tests/programs/andy_cherry/test.T
index 4d14ee306..511eac505 100644
--- a/tests/programs/andy_cherry/test.T
+++ b/tests/programs/andy_cherry/test.T
@@ -1,6 +1,6 @@
 
 test('andy_cherry',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['DataTypes.hi',   'DataTypes.o',
                    'GenUtils.hi',    'GenUtils.o',
                    'Interp.hi',      'Interp.o',
diff --git a/tests/programs/barton-mangler-bug/test.T b/tests/programs/barton-mangler-bug/test.T
index 966b971ae..bb140f56f 100644
--- a/tests/programs/barton-mangler-bug/test.T
+++ b/tests/programs/barton-mangler-bug/test.T
@@ -1,7 +1,7 @@
 # Exhausts Hugs's heap (CAF leak)
 
 test('barton-mangler-bug',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Basic.hi',             'Basic.o',
                    'Expected.hi',          'Expected.o',
                    'Main.hi',              'Main.o',
diff --git a/tests/programs/cholewo-eval/test.T b/tests/programs/cholewo-eval/test.T
index 32efd68f7..3b418d4ac 100644
--- a/tests/programs/cholewo-eval/test.T
+++ b/tests/programs/cholewo-eval/test.T
@@ -1,5 +1,5 @@
 test('cholewo-eval',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Main.hi', 'Main.o', 'Arr.hi', 'Arr.o'])],
      multimod_compile_and_run,
      ['Main', ''])
diff --git a/tests/programs/cvh_unboxing/test.T b/tests/programs/cvh_unboxing/test.T
index 4208a7f2a..6cc5ca4f6 100644
--- a/tests/programs/cvh_unboxing/test.T
+++ b/tests/programs/cvh_unboxing/test.T
@@ -1,7 +1,7 @@
 setTestOpts(only_compiler_types(['ghc']))
 
 test('cvh_unboxing',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Append.hi', 'Append.o',
                    'Main.hi',   'Main.o',
                    'Types.hi',  'Types.o'])],
diff --git a/tests/programs/fast2haskell/test.T b/tests/programs/fast2haskell/test.T
index a730ffdfe..621c58918 100644
--- a/tests/programs/fast2haskell/test.T
+++ b/tests/programs/fast2haskell/test.T
@@ -1,6 +1,6 @@
 
 test('fast2haskell',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Main.hi',         'Main.o',
                    'Fast2haskell.hi', 'Fast2haskell.o'])],
      multimod_compile_and_run,
diff --git a/tests/programs/fun_insts/test.T b/tests/programs/fun_insts/test.T
index 515148803..98bcf3a32 100644
--- a/tests/programs/fun_insts/test.T
+++ b/tests/programs/fun_insts/test.T
@@ -1,6 +1,6 @@
 
 test('fun_insts',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/galois_raytrace/test.T b/tests/programs/galois_raytrace/test.T
index 169e162d6..3bdcb75fc 100644
--- a/tests/programs/galois_raytrace/test.T
+++ b/tests/programs/galois_raytrace/test.T
@@ -6,7 +6,7 @@ if config.platform.startswith('i386-') and \
     setTestOpts(expect_fail_for(['hpc','optasm','profasm','threaded2','profthreaded']))
 
 test('galois_raytrace',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['CSG.hi',           'CSG.o',
                    'Construct.hi',     'Construct.o',
                    'Data.hi',          'Data.o',
diff --git a/tests/programs/jl_defaults/test.T b/tests/programs/jl_defaults/test.T
index 0f6e4cbd6..b17c0b8cb 100644
--- a/tests/programs/jl_defaults/test.T
+++ b/tests/programs/jl_defaults/test.T
@@ -1,6 +1,6 @@
 
 test('jl_defaults',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/joao-circular/test.T b/tests/programs/joao-circular/test.T
index 935ec7e6f..3f229ab47 100644
--- a/tests/programs/joao-circular/test.T
+++ b/tests/programs/joao-circular/test.T
@@ -1,5 +1,5 @@
 test('joao-circular',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Data_Lazy.hi',         'Data_Lazy.o',
                    'Funcs_Lexer.hi',       'Funcs_Lexer.o',
                    'Funcs_Parser_Lazy.hi', 'Funcs_Parser_Lazy.o',
diff --git a/tests/programs/jq_readsPrec/test.T b/tests/programs/jq_readsPrec/test.T
index 393f82c4b..dcad28cd7 100644
--- a/tests/programs/jq_readsPrec/test.T
+++ b/tests/programs/jq_readsPrec/test.T
@@ -1,6 +1,6 @@
 
 test('jq_readsPrec',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/jtod_circint/test.T b/tests/programs/jtod_circint/test.T
index 47338d7b8..b6ad840a2 100644
--- a/tests/programs/jtod_circint/test.T
+++ b/tests/programs/jtod_circint/test.T
@@ -1,6 +1,6 @@
 
 test('jtod_circint',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Bit.hi',    'Bit.o',
                    'LogFun.hi', 'LogFun.o',
                    'Main.hi',   'Main.o',
diff --git a/tests/programs/jules_xref/test.T b/tests/programs/jules_xref/test.T
index 07da9cbd0..a8941e033 100644
--- a/tests/programs/jules_xref/test.T
+++ b/tests/programs/jules_xref/test.T
@@ -1,6 +1,6 @@
 # exhausts Hugs's heap
 test('jules_xref',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Main.hi', 'Main.o']),
       omit_compiler_types(['hugs'])],
      multimod_compile_and_run,
diff --git a/tests/programs/jules_xref2/test.T b/tests/programs/jules_xref2/test.T
index 384155c8c..2e627ab89 100644
--- a/tests/programs/jules_xref2/test.T
+++ b/tests/programs/jules_xref2/test.T
@@ -1,6 +1,6 @@
 
 test('jules_xref2',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/launchbury/test.T b/tests/programs/launchbury/test.T
index 937bb94a6..0af619f4c 100644
--- a/tests/programs/launchbury/test.T
+++ b/tests/programs/launchbury/test.T
@@ -1,6 +1,6 @@
 
 test('launchbury',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/lennart_range/test.T b/tests/programs/lennart_range/test.T
index f308f0039..0cc5a351f 100644
--- a/tests/programs/lennart_range/test.T
+++ b/tests/programs/lennart_range/test.T
@@ -1,6 +1,6 @@
 
 test('lennart_range',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/lex/test.T b/tests/programs/lex/test.T
index da6e227a6..79459772a 100644
--- a/tests/programs/lex/test.T
+++ b/tests/programs/lex/test.T
@@ -1,6 +1,6 @@
 
 test('lex',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/life_space_leak/test.T b/tests/programs/life_space_leak/test.T
index a0cdc2c76..11f73e0eb 100644
--- a/tests/programs/life_space_leak/test.T
+++ b/tests/programs/life_space_leak/test.T
@@ -1,6 +1,6 @@
 # exhausts Hugs's heap (CAF leak)
 test('life_space_leak',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Main.hi', 'Main.o']),
       when(compiler_type('hugs'), expect_fail)],
      multimod_compile_and_run,
diff --git a/tests/programs/maessen-hashtab/test.T b/tests/programs/maessen-hashtab/test.T
index 807cb85e8..e21d2bb1c 100644
--- a/tests/programs/maessen-hashtab/test.T
+++ b/tests/programs/maessen-hashtab/test.T
@@ -3,7 +3,7 @@ test('maessen_hashtab',
      [reqlib('QuickCheck'),
       extra_clean(['HashTest.hi', 'HashTest.o',
                    'Data/HashTab.hi', 'Data/HashTab.o']),
-      skip_if_fast,
+      when(fast(), skip),
 # this test runs out of time when not optimised:
       omit_ways(['normal','ghci','threaded1']),
       extra_run_opts('99999')],
diff --git a/tests/programs/north_array/test.T b/tests/programs/north_array/test.T
index e2b89b450..d822897d5 100644
--- a/tests/programs/north_array/test.T
+++ b/tests/programs/north_array/test.T
@@ -1,6 +1,6 @@
 
 test('north_array',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/okeefe_neural/test.T b/tests/programs/okeefe_neural/test.T
index 326dd6b0f..e905ec0b9 100644
--- a/tests/programs/okeefe_neural/test.T
+++ b/tests/programs/okeefe_neural/test.T
@@ -5,7 +5,7 @@ def set_opts( name, opts ):
   opts.expect = 'fail'
 
 test('okeefe_neural',
-     [skip_if_fast,
+     [when(fast(), skip),
       set_opts,
       extra_clean(['Main.hi'])],
      multimod_compile_and_run,
diff --git a/tests/programs/record_upd/test.T b/tests/programs/record_upd/test.T
index e98b70c43..46149575b 100644
--- a/tests/programs/record_upd/test.T
+++ b/tests/programs/record_upd/test.T
@@ -1,6 +1,6 @@
 
 test('record_upd',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/rittri/test.T b/tests/programs/rittri/test.T
index 2e14f6fdc..57e7805ea 100644
--- a/tests/programs/rittri/test.T
+++ b/tests/programs/rittri/test.T
@@ -1,6 +1,6 @@
 
 test('rittri',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/sanders_array/test.T b/tests/programs/sanders_array/test.T
index 03c4d4eec..6e0a8c6e7 100644
--- a/tests/programs/sanders_array/test.T
+++ b/tests/programs/sanders_array/test.T
@@ -1,6 +1,6 @@
 
 test('sanders_array',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/seward-space-leak/test.T b/tests/programs/seward-space-leak/test.T
index bdb775927..491da8e6c 100644
--- a/tests/programs/seward-space-leak/test.T
+++ b/tests/programs/seward-space-leak/test.T
@@ -1,7 +1,7 @@
 setTestOpts(omit_compiler_types(['hugs']))	# takes much too long
 
 test('seward-space-leak',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/strict_anns/test.T b/tests/programs/strict_anns/test.T
index 77ed9dab5..e64ee2fb7 100644
--- a/tests/programs/strict_anns/test.T
+++ b/tests/programs/strict_anns/test.T
@@ -1,6 +1,6 @@
 
 test('strict_anns',
-     [skip_if_fast, extra_clean(['Main.hi', 'Main.o'])],
+     [when(fast(), skip), extra_clean(['Main.hi', 'Main.o'])],
      multimod_compile_and_run,
      ['Main', ''])
 
diff --git a/tests/programs/thurston-modular-arith/test.T b/tests/programs/thurston-modular-arith/test.T
index 812fb07ba..0af870e0d 100644
--- a/tests/programs/thurston-modular-arith/test.T
+++ b/tests/programs/thurston-modular-arith/test.T
@@ -1,6 +1,6 @@
 # uses GHC-specific scoped type variables
 test('thurston-modular-arith',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Main.hi', 'Main.o', 'TypeVal.hi', 'TypeVal.o']),
       only_compiler_types(['ghc'])],
      multimod_compile_and_run,
diff --git a/tests/quasiquotation/qq005/test.T b/tests/quasiquotation/qq005/test.T
index 52671ef83..efa7b9d95 100644
--- a/tests/quasiquotation/qq005/test.T
+++ b/tests/quasiquotation/qq005/test.T
@@ -1,5 +1,5 @@
 test('qq005',
-     [skip_if_fast,
+     [when(fast(), skip),
       reqlib('parsec'),
       only_compiler_types(['ghc']),
       # We'd need to jump through some hoops to run this test the
diff --git a/tests/quasiquotation/qq006/test.T b/tests/quasiquotation/qq006/test.T
index 21d9a3db1..be471de9c 100644
--- a/tests/quasiquotation/qq006/test.T
+++ b/tests/quasiquotation/qq006/test.T
@@ -1,5 +1,5 @@
 test('qq006',
-     [skip_if_fast,
+     [when(fast(), skip),
       reqlib('parsec'),
       extra_clean(['Expr.hi', 'Expr.o']),
       only_compiler_types(['ghc'])],
diff --git a/tests/quasiquotation/qq007/test.T b/tests/quasiquotation/qq007/test.T
index 6b7ef6dcd..61374e571 100644
--- a/tests/quasiquotation/qq007/test.T
+++ b/tests/quasiquotation/qq007/test.T
@@ -1,5 +1,5 @@
 test('qq007',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['QQ.hi', 'QQ.o', 'Test.hi', 'Test.o']),
       # We'd need to jump through some hoops to run this test the
       # profiling ways, due to the TH use, so for now we just
diff --git a/tests/quasiquotation/qq008/test.T b/tests/quasiquotation/qq008/test.T
index 02b88dbd0..5d4199963 100644
--- a/tests/quasiquotation/qq008/test.T
+++ b/tests/quasiquotation/qq008/test.T
@@ -1,5 +1,5 @@
 test('qq008',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['QQ.hi', 'QQ.o', 'Test.hi', 'Test.o']),
       # We'd need to jump through some hoops to run this test the
       # profiling ways, due to the TH use, so for now we just
diff --git a/tests/rts/all.T b/tests/rts/all.T
index 8da87aae6..3ccd14297 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -69,7 +69,7 @@ test('stack003', [ omit_ways('ghci'), # uses unboxed tuples
 test('atomicinc', [ c_src, only_ways(['normal']) ], compile_and_run, [''])
 
 test('T3424', # it's slow:
-              [ skip_if_fast, only_ways(['normal','threaded1','ghci']) ],
+              [ when(fast(), skip), only_ways(['normal','threaded1','ghci']) ],
               compile_and_run, [''])
 
 # Test for out-of-range heap size
diff --git a/tests/simplCore/should_compile/all.T b/tests/simplCore/should_compile/all.T
index 765a12826..570f295c1 100644
--- a/tests/simplCore/should_compile/all.T
+++ b/tests/simplCore/should_compile/all.T
@@ -29,7 +29,7 @@ test('simpl-T1370', normal, compile, [''])
 test('T2520', normal, compile, [''])
 
 
-test('spec001', skip_if_fast, compile, [''])
+test('spec001', when(fast(), skip), compile, [''])
 test('spec002', normal, compile, [''])
 test('spec003', normal, compile, [''])
 
@@ -44,7 +44,7 @@ test('T4203', normal, compile, [''])
 
 # With -prof -fvia-C, this test makes gcc go out to lunch, and the
 # testsuite driver times out.
-test('T3016', skip_if_fast, compile, [''])
+test('T3016', when(fast(), skip), compile, [''])
 
 test('T1647', normal, compile, ['-fdicts-strict -dcore-lint'])
 
diff --git a/tests/typecheck/prog001/test.T b/tests/typecheck/prog001/test.T
index 09bb3f0f3..1f0d67cba 100644
--- a/tests/typecheck/prog001/test.T
+++ b/tests/typecheck/prog001/test.T
@@ -1,6 +1,6 @@
 
 test('typecheck.prog001',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['A.hi', 'A.o', 'B.hi', 'B.o', 'C.hi', 'C.o'])],
      multimod_compile,
 	 ['C', '-v0'])
diff --git a/tests/typecheck/prog002/test.T b/tests/typecheck/prog002/test.T
index 24625bad0..adac6d502 100644
--- a/tests/typecheck/prog002/test.T
+++ b/tests/typecheck/prog002/test.T
@@ -1,7 +1,7 @@
 setTestOpts(only_compiler_types(['ghc']))
 
 test('typecheck.prog002',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['A.hi', 'A.o', 'B.hi', 'B.o'])],
      multimod_compile,
      ['B', '-v0'])
diff --git a/tests/typecheck/testeq1/test.T b/tests/typecheck/testeq1/test.T
index dbb63fb9f..c1b97e90f 100644
--- a/tests/typecheck/testeq1/test.T
+++ b/tests/typecheck/testeq1/test.T
@@ -1,6 +1,6 @@
 
 test('typecheck.testeq1',
-     [skip_if_fast,
+     [when(fast(), skip),
       extra_clean(['Main.hi', 'Main.o',
                    'TypeCast.hi', 'TypeCast.o',
                    'FakePrelude.hi', 'FakePrelude.o',
-- 
GitLab


From 4bcc9b96b65dd6e8937187aeb00be545fd613894 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 15:47:02 +0000
Subject: [PATCH 137/223] More conversions

---
 driver/testlib.py              |  9 +++------
 tests/ghci/linking/all.T       | 12 ++++++------
 tests/rename/should_fail/all.T |  2 +-
 3 files changed, 10 insertions(+), 13 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 89d6c2e04..8a627f477 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -293,12 +293,6 @@ def _compiler_stats_num_field( name, opts, field, expecteds ):
 
 # -----
 
-def skip_if_no_ghci(name, opts):
-    if not ('ghci' in config.run_ways):
-        opts.skip = 1
-
-# ----
-
 def when(b, f):
     # When list_brokens is on, we want to see all expect_broken calls,
     # so we always do f
@@ -313,6 +307,9 @@ def unless(b, f):
 def fast():
     return config.fast
 
+def doing_ghci():
+    return 'ghci' in config.run_ways
+
 def platform( plat ):
     return config.platform == plat
 
diff --git a/tests/ghci/linking/all.T b/tests/ghci/linking/all.T
index ce00b3e58..2360030ba 100644
--- a/tests/ghci/linking/all.T
+++ b/tests/ghci/linking/all.T
@@ -1,12 +1,12 @@
 test('ghcilink001',
      [when(ghci_dynamic(), expect_fail), # dynamic ghci can't load '.a's
-      skip_if_no_ghci,
+      unless(doing_ghci, skip),
       extra_clean(['dir001/*','dir001'])],
      run_command,
      ['$MAKE -s --no-print-directory ghcilink001'])
 
 test('ghcilink002',
-     [skip_if_no_ghci, extra_clean(['dir002/*','dir002'])],
+     [unless(doing_ghci, skip), extra_clean(['dir002/*','dir002'])],
      run_command,
      ['$MAKE -s --no-print-directory ghcilink002'])
 
@@ -14,7 +14,7 @@ test('ghcilink003',
      [
        # still cannot load libstdc++ on Windows.  See also #4468.
        when(opsys('mingw32'), expect_broken(5289)),
-       skip_if_no_ghci,
+       unless(doing_ghci, skip),
        extra_clean(['dir003/*','dir003'])
      ],
      run_command,
@@ -22,13 +22,13 @@ test('ghcilink003',
 
 test('ghcilink004',
      [when(ghci_dynamic(), expect_fail), # dynamic ghci can't load '.a's
-      skip_if_no_ghci,
+      unless(doing_ghci, skip),
       extra_clean(['dir004/*','dir004'])],
      run_command,
      ['$MAKE -s --no-print-directory ghcilink004'])
 
 test('ghcilink005',
-     [skip_if_no_ghci, extra_clean(['dir005/*','dir005'])],
+     [unless(doing_ghci, skip), extra_clean(['dir005/*','dir005'])],
      run_command,
      ['$MAKE -s --no-print-directory ghcilink005'])
 
@@ -36,7 +36,7 @@ test('ghcilink006',
      [
        # still cannot load libstdc++ on Windows.  See also #4468.
        when(opsys('mingw32'), expect_broken(5289)),
-       skip_if_no_ghci,
+       unless(doing_ghci, skip),
        extra_clean(['dir006/*','dir006'])
      ],
      run_command,
diff --git a/tests/rename/should_fail/all.T b/tests/rename/should_fail/all.T
index 4ced172c6..c05662bde 100644
--- a/tests/rename/should_fail/all.T
+++ b/tests/rename/should_fail/all.T
@@ -44,7 +44,7 @@ test('rnfail040',
 test('rnfail041', normal, compile_fail, [''])
 test('rnfail042', normal, compile_fail, [''])
 
-test('rnfail043', skip_if_no_ghci, compile_fail, ['-v0'])
+test('rnfail043', unless(doing_ghci, skip), compile_fail, ['-v0'])
 test('rnfail044', normal, compile_fail, [''])
 test('rnfail045', normal, compile_fail, [''])
 test('rnfail046', normal, compile_fail, [''])
-- 
GitLab


From 2fb008a5be4962e516e5f5184ef6eb5fbebab572 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 17:36:06 +0000
Subject: [PATCH 138/223] Ticket #1845 is closed, so ghci024 presumably works
 on PPC/OSX now

---
 tests/ghci/scripts/all.T | 3 +--
 1 file changed, 1 insertion(+), 2 deletions(-)

diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index ee34ce97a..398efb4f0 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -37,8 +37,7 @@ test('ghci022', normal, ghci_script, ['ghci022.script'])
 
 test('ghci023', normal, ghci_script, ['ghci023.script'])
 test('ghci024',
-     [when(fast(), skip),
-      when(platform("powerpc-apple-darwin"), expect_broken(1845))],
+     when(fast(), skip),
      run_command,
      ['$MAKE -s --no-print-directory ghci024'])
 test('ghci025', normal, ghci_script, ['ghci025.script'])
-- 
GitLab


From c6b5bd8c8340b0307e751057e2c6166da746ec45 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 17:36:40 +0000
Subject: [PATCH 139/223] Tweak the brokens list to include the directory the
 test is in

---
 driver/runtests.py    | 2 +-
 driver/testglobals.py | 2 +-
 driver/testlib.py     | 8 ++++----
 3 files changed, 6 insertions(+), 6 deletions(-)

diff --git a/driver/runtests.py b/driver/runtests.py
index e1d6f7cdb..1b8ddb171 100644
--- a/driver/runtests.py
+++ b/driver/runtests.py
@@ -258,7 +258,7 @@ if config.list_broken:
     global brokens
     print ''
     print 'Broken tests:'
-    print (' '.join(map (lambda (b, n) : '#' + str(b) + '(' + n + ')', brokens)))
+    print (' '.join(map (lambda (b, d, n) : '#' + str(b) + '(' + d + '/' + n + ')', brokens)))
     print ''
 
     if t.n_framework_failures != 0:
diff --git a/driver/testglobals.py b/driver/testglobals.py
index b7b60077f..a9595570f 100644
--- a/driver/testglobals.py
+++ b/driver/testglobals.py
@@ -265,7 +265,7 @@ class TestOptions:
 global default_testopts
 default_testopts = TestOptions()
 
-# (bug, name) of tests marked broken
+# (bug, directory, name) of tests marked broken
 global brokens
 brokens = []
 
diff --git a/driver/testlib.py b/driver/testlib.py
index 8a627f477..56e1b4604 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -151,19 +151,19 @@ def expect_broken( bug ):
     return lambda name, opts, b=bug: _expect_broken (name, opts, b )
 
 def _expect_broken( name, opts, bug ):
-    record_broken(name, bug)
+    record_broken(name, opts, bug)
     opts.expect = 'fail';
 
 def expect_broken_for( bug, ways ):
     return lambda name, opts, b=bug, w=ways: _expect_broken_for( name, opts, b, w )
 
 def _expect_broken_for( name, opts, bug, ways ):
-    record_broken(name, bug)
+    record_broken(name, opts, bug)
     opts.expect_fail_for = ways
 
-def record_broken(name, bug):
+def record_broken(name, opts, bug):
     global brokens
-    me = (bug, name)
+    me = (bug, opts.testdir, name)
     if not me in brokens:
         brokens.append(me)
 
-- 
GitLab


From 29d5edda1e6b61b8dbfa417120bbc0011f84990d Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 18:22:02 +0000
Subject: [PATCH 140/223] Remove T5763

It was added in fbb1f167657bcdb4d9a67e9b97734faeb82c8a25 without
an accompanying source file. Also, it was marked as being broken by
5673, so I'm not even sure which ticket it was supposed to be a
test for.
---
 tests/indexed-types/should_fail/all.T | 1 -
 1 file changed, 1 deletion(-)

diff --git a/tests/indexed-types/should_fail/all.T b/tests/indexed-types/should_fail/all.T
index e99b79676..0196f543e 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -72,7 +72,6 @@ test('T2544', normal, compile_fail, [''])
 test('T1897b', normal, compile_fail, [''])
 test('T5439', normal, compile_fail, [''])
 test('T5515', normal, compile_fail, [''])
-test('T5763', expect_broken(5673), compile_fail, [''])
 test('T5934', normal, compile_fail, [''])
 test('T6123', normal, compile_fail, [''])
 test('ExtraTcsUntch', normal, compile_fail, [''])
-- 
GitLab


From 96ce462eb872c17f5164959056ade6cbb24dafa5 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 18:30:24 +0000
Subject: [PATCH 141/223] Add expected output for T6117, which is now working

---
 tests/typecheck/should_run/T6117.stdout | 1 +
 tests/typecheck/should_run/all.T        | 2 +-
 2 files changed, 2 insertions(+), 1 deletion(-)
 create mode 100644 tests/typecheck/should_run/T6117.stdout

diff --git a/tests/typecheck/should_run/T6117.stdout b/tests/typecheck/should_run/T6117.stdout
new file mode 100644
index 000000000..a32a4347a
--- /dev/null
+++ b/tests/typecheck/should_run/T6117.stdout
@@ -0,0 +1 @@
+1234567890
diff --git a/tests/typecheck/should_run/all.T b/tests/typecheck/should_run/all.T
index 083088c3e..17b7b0e83 100755
--- a/tests/typecheck/should_run/all.T
+++ b/tests/typecheck/should_run/all.T
@@ -96,6 +96,6 @@ test('T5573a', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compil
 test('T5573b', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compile_and_run, [''])
 test('T7023', normal, compile_and_run, [''])
 test('T7126', normal, compile_and_run, [''])
-test('T6117', expect_broken(6117), compile_and_run, [''])
+test('T6117', normal, compile_and_run, [''])
 test('T5751', normal, compile_and_run, [''])
 test('T5913', normal, compile_and_run, [''])
-- 
GitLab


From 0e0d918281858e6afaff7b34f2a5d2ca61f28dae Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 18:32:34 +0000
Subject: [PATCH 142/223] Remove ds061

It was a failing test for a defunct feature (NPlusKPatterns) (#851)
---
 tests/deSugar/should_compile/all.T    |  1 -
 tests/deSugar/should_compile/ds061.hs | 14 --------------
 2 files changed, 15 deletions(-)
 delete mode 100644 tests/deSugar/should_compile/ds061.hs

diff --git a/tests/deSugar/should_compile/all.T b/tests/deSugar/should_compile/all.T
index 6328b3048..bf3b068ec 100644
--- a/tests/deSugar/should_compile/all.T
+++ b/tests/deSugar/should_compile/all.T
@@ -64,7 +64,6 @@ test('ds057', normal, compile, [''])
 test('ds058', normal, compile, ['-W'])
 test('ds059', normal, compile, ['-W'])
 test('ds060', expect_broken(322), compile, [''])
-test('ds061', expect_broken(851), compile, [''])
 test('ds062', normal, compile, [''])
 test('ds063', normal, compile, [''])
 
diff --git a/tests/deSugar/should_compile/ds061.hs b/tests/deSugar/should_compile/ds061.hs
deleted file mode 100644
index 271bbbbc6..000000000
--- a/tests/deSugar/should_compile/ds061.hs
+++ /dev/null
@@ -1,14 +0,0 @@
-{-# LANGUAGE NPlusKPatterns #-}
-{-# OPTIONS_GHC -fwarn-incomplete-patterns -Wall #-}
-
--- Test for trac #851
--- Should not give a non-exhaustive pattern warning
-
-module ShouldCompile where
-
-import Data.Word
-
-f :: Word -> Bool
-f 0 = True
-f (_n + 1) = False
-
-- 
GitLab


From 941bcf45cd5ed45d26358fd15eb4a1089c95841d Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 18:35:02 +0000
Subject: [PATCH 143/223] Update the reason for T5267 being broken

---
 tests/arrows/should_compile/all.T | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/arrows/should_compile/all.T b/tests/arrows/should_compile/all.T
index 24e95e8ef..0a1e6516c 100644
--- a/tests/arrows/should_compile/all.T
+++ b/tests/arrows/should_compile/all.T
@@ -16,5 +16,5 @@ test('arrowrec1', normal, compile, [''])
 test('arrowpat', normal, compile, [''])
 test('T3964', normal, compile, [''])
 test('T5283', normal, compile, [''])
-test('T5267', expect_broken(5605), compile, [''])
+test('T5267', expect_broken(5267), compile, [''])
 test('T5022', normal, compile, [''])
-- 
GitLab


From 02f093ab5198eb30b51232136363c8333d4391b3 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 18:51:27 +0000
Subject: [PATCH 144/223] Add expected warnings for print020

---
 tests/ghci.debugger/scripts/print020.stderr | 31 +++++++++++++++++++++
 1 file changed, 31 insertions(+)
 create mode 100644 tests/ghci.debugger/scripts/print020.stderr

diff --git a/tests/ghci.debugger/scripts/print020.stderr b/tests/ghci.debugger/scripts/print020.stderr
new file mode 100644
index 000000000..296718dae
--- /dev/null
+++ b/tests/ghci.debugger/scripts/print020.stderr
@@ -0,0 +1,31 @@
+
+GenericTemplate.hs:219:14: Warning:
+    Pattern bindings containing unlifted types should use an outermost bang pattern:
+      sts1@((HappyCons (st1@(action)) (_)))
+        = happyDrop k (HappyCons (st) (sts))
+    In an equation for `happyMonadReduce':
+        happyMonadReduce k nt fn j tk st sts stk
+          = happyThen1
+              (fn stk tk)
+              (\ r -> happyGoto nt j tk st1 sts1 (r `HappyStk` drop_stk))
+          where
+              sts1@((HappyCons (st1@(action)) (_)))
+                = happyDrop k (HappyCons (st) (sts))
+              drop_stk = happyDropStk k stk
+
+GenericTemplate.hs:226:14: Warning:
+    Pattern bindings containing unlifted types should use an outermost bang pattern:
+      sts1@((HappyCons (st1@(action)) (_)))
+        = happyDrop k (HappyCons (st) (sts))
+    In an equation for `happyMonad2Reduce':
+        happyMonad2Reduce k nt fn j tk st sts stk
+          = happyThen1
+              (fn stk tk)
+              (\ r -> happyNewToken new_state sts1 (r `HappyStk` drop_stk))
+          where
+              sts1@((HappyCons (st1@(action)) (_)))
+                = happyDrop k (HappyCons (st) (sts))
+              drop_stk = happyDropStk k stk
+              off = indexShortOffAddr happyGotoOffsets st1
+              off_i = (off +# nt)
+              ....
-- 
GitLab


From 34a1e43cafeaabb1ccae1bc0e13c63abd112f015 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 18:51:36 +0000
Subject: [PATCH 145/223] HappyTest needs MagicHash

---
 tests/ghci.debugger/HappyTest.hs | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/ghci.debugger/HappyTest.hs b/tests/ghci.debugger/HappyTest.hs
index 9be54402a..ad444f716 100644
--- a/tests/ghci.debugger/HappyTest.hs
+++ b/tests/ghci.debugger/HappyTest.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP #-}
+{-# LANGUAGE CPP, MagicHash #-}
 import Data.Char
 import Data.Array
 import GHC.Exts
-- 
GitLab


From d11afce2568d3e031450827216b5cdd66efde8b8 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 18:53:04 +0000
Subject: [PATCH 146/223] Update print020 expected output

---
 tests/ghci.debugger/scripts/print020.stdout | 4 ++--
 1 file changed, 2 insertions(+), 2 deletions(-)

diff --git a/tests/ghci.debugger/scripts/print020.stdout b/tests/ghci.debugger/scripts/print020.stdout
index ee10c3a57..452fd064a 100644
--- a/tests/ghci.debugger/scripts/print020.stdout
+++ b/tests/ghci.debugger/scripts/print020.stdout
@@ -1,5 +1,5 @@
-Breakpoint 0 activated at ../HappyTest.hs:(229,0)-(240,34)
-Stopped at ../HappyTest.hs:(229,0)-(240,34)
+Breakpoint 0 activated at ../HappyTest.hs:(216,1)-(227,35)
+Stopped at ../HappyTest.hs:(216,1)-(227,35)
 _result :: [Token] = _
 *** Ignoring breakpoint
 *** Ignoring breakpoint
-- 
GitLab


From e5db4c411f2e6db7377f4b2fad4b013a8dd55bf0 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 18:54:37 +0000
Subject: [PATCH 147/223] print020 now passes

---
 tests/ghci.debugger/scripts/all.T | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/ghci.debugger/scripts/all.T b/tests/ghci.debugger/scripts/all.T
index 76a8f0ff5..4ddc9bc78 100644
--- a/tests/ghci.debugger/scripts/all.T
+++ b/tests/ghci.debugger/scripts/all.T
@@ -20,7 +20,7 @@ test('print016', normal, ghci_script, ['print016.script'])
 test('print017', normal, ghci_script, ['print017.script'])
 test('print018', normal, ghci_script, ['print018.script'])
 test('print019', normal, ghci_script, ['print019.script'])
-test('print020', expect_broken(2806), ghci_script, ['print020.script'])
+test('print020', normal, ghci_script, ['print020.script'])
 test('print021', normal, ghci_script, ['print021.script'])
 test('print022', normal, ghci_script, ['print022.script'])
 test('print023', normal, ghci_script, ['print023.script'])
-- 
GitLab


From 41a46e05d4f50351e987f75d869d7aab1310714c Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 11 Feb 2013 19:06:33 +0000
Subject: [PATCH 148/223] Fix result001

---
 tests/ghci.debugger/scripts/all.T            | 2 +-
 tests/ghci.debugger/scripts/result001.stdout | 4 ++++
 2 files changed, 5 insertions(+), 1 deletion(-)
 create mode 100644 tests/ghci.debugger/scripts/result001.stdout

diff --git a/tests/ghci.debugger/scripts/all.T b/tests/ghci.debugger/scripts/all.T
index 4ddc9bc78..e2d545876 100644
--- a/tests/ghci.debugger/scripts/all.T
+++ b/tests/ghci.debugger/scripts/all.T
@@ -76,7 +76,7 @@ test('dynbrk007', normal, ghci_script, ['dynbrk007.script'])
 test('dynbrk008', normal, ghci_script, ['dynbrk008.script'])
 test('dynbrk009', normal, ghci_script, ['dynbrk009.script'])
 
-test('result001', expect_broken(1531), ghci_script, ['result001.script'])
+test('result001', normal, ghci_script, ['result001.script'])
 
 test('listCommand001', combined_output, ghci_script, ['listCommand001.script'])
 test('listCommand002', normal, ghci_script, ['listCommand002.script'])
diff --git a/tests/ghci.debugger/scripts/result001.stdout b/tests/ghci.debugger/scripts/result001.stdout
new file mode 100644
index 000000000..0d2173dcd
--- /dev/null
+++ b/tests/ghci.debugger/scripts/result001.stdout
@@ -0,0 +1,4 @@
+Breakpoint 0 activated at result001.hs:1:13-21
+Stopped at result001.hs:1:13-21
+_result :: [b] = _
+xs :: [b] = _
-- 
GitLab


From ab6e6711358704cc40cf26935dd7a36ae10ada25 Mon Sep 17 00:00:00 2001
From: Richard Eisenberg <eir@cis.upenn.edu>
Date: Mon, 11 Feb 2013 23:06:41 -0500
Subject: [PATCH 149/223] Added testcase for Trac #7681, a Template Haskell
 missing feature.

---
 tests/th/T7681.hs | 12 ++++++++++++
 tests/th/all.T    |  1 +
 2 files changed, 13 insertions(+)
 create mode 100644 tests/th/T7681.hs

diff --git a/tests/th/T7681.hs b/tests/th/T7681.hs
new file mode 100644
index 000000000..c7f43e779
--- /dev/null
+++ b/tests/th/T7681.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE EmptyCase, TemplateHaskell, LambdaCase #-}
+
+module T7681 where
+
+data Void
+
+foo :: Void -> a
+foo x = $( [| case x of {} |] )
+
+bar :: Void -> a
+bar = $( [| \case {} |] )
+
diff --git a/tests/th/all.T b/tests/th/all.T
index caaa3df16..b279dcd6e 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -269,3 +269,4 @@ test('T7532',
      ['T7532', '-v0'])
 test('T2222', normal, compile, ['-v0'])
 test('T1849', normal, ghci_script, ['T1849.script'])
+test('T7681', normal, compile, ['-v0'])
\ No newline at end of file
-- 
GitLab


From 38c064dc3ca59404de379f4a3d0b27ec98f1dd40 Mon Sep 17 00:00:00 2001
From: Johan Tibell <johan.tibell@gmail.com>
Date: Fri, 8 Feb 2013 16:59:16 -0800
Subject: [PATCH 150/223] Update test to match new I/O manager behavior

The new I/O manager has a separate thread for tracking timeouts.
---
 tests/rts/T4850.hs     | 7 ++++---
 tests/rts/T4850.stdout | 2 +-
 2 files changed, 5 insertions(+), 4 deletions(-)

diff --git a/tests/rts/T4850.hs b/tests/rts/T4850.hs
index 72616d97e..fa06ffbea 100644
--- a/tests/rts/T4850.hs
+++ b/tests/rts/T4850.hs
@@ -10,11 +10,12 @@ foreign import ccall "wrapper" mkF :: Fun -> IO (FunPtr Fun)
 
 foreign import ccall "dynamic" callF :: FunPtr Fun -> Fun
 
--- This test should create 4 OS threads only:
+-- This test should create 5 OS threads only:
 --   one for main
 --   worker 1 for the IO manager
---   worker 2 to run the first forkIO
---   worker 3 created when worker 2 makes its foreign call
+--   worker 1 for the timeout manager
+--   worker 3 to run the first forkIO
+--   worker 4 created when worker 2 makes its foreign call
 
 -- Due to #4850, an extra worker was being created because worker 2 was
 -- lost after returning from its foreign call.
diff --git a/tests/rts/T4850.stdout b/tests/rts/T4850.stdout
index b8626c4cf..7ed6ff82d 100644
--- a/tests/rts/T4850.stdout
+++ b/tests/rts/T4850.stdout
@@ -1 +1 @@
-4
+5
-- 
GitLab


From b89b2bb7784f2122ddaa4a603a57333ee6f6235c Mon Sep 17 00:00:00 2001
From: Jose Pedro Magalhaes <jpm@cs.ox.ac.uk>
Date: Thu, 7 Feb 2013 13:59:51 +0000
Subject: [PATCH 151/223] Implement poly-kinded Typeable

This patch makes the Data.Typeable.Typeable class work with arguments of any
kind. In particular, this removes the Typeable1..7 class hierarchy, greatly
simplyfing the whole Typeable story. Also added is the AutoDeriveTypeable
language extension, which will automatically derive Typeable for all types and
classes declared in that module. Since there is now no good reason to give
handwritten instances of the Typeable class, those are ignored (for backwards
compatibility), and a warning is emitted.

The old, kind-* Typeable class is now called OldTypeable, and lives in the
Data.OldTypeable module. It is deprecated, and should be removed in some future
version of GHC.
---
 tests/annotations/should_fail/annfail06.hs     |  2 +-
 tests/deriving/should_compile/T2378.hs         |  2 +-
 tests/deriving/should_compile/T3965.hs         | 11 +++--------
 tests/deriving/should_compile/T4302.hs         |  2 +-
 tests/deriving/should_compile/all.T            |  1 +
 tests/deriving/should_compile/drv021.hs        |  2 +-
 tests/deriving/should_compile/drv021.stderr    | 13 +++++++++++++
 .../drvfail010.hs => should_compile/drv022.hs} |  6 +++---
 tests/deriving/should_fail/T2604.stderr        |  4 ++--
 tests/deriving/should_fail/all.T               |  1 -
 tests/deriving/should_fail/drvfail010.stderr   | 11 -----------
 .../should_fail/drvfail010.stderr-hugs         |  1 -
 tests/deriving/should_fail/drvfail014.hs       |  2 +-
 tests/driver/T4437.hs                          |  3 ++-
 tests/indexed-types/should_compile/T1769.hs    |  2 +-
 tests/perf/should_run/T3245.hs                 |  7 ++-----
 tests/rename/should_compile/T4003A.hs-boot     |  2 +-
 tests/safeHaskell/ghci/p15.script              |  2 +-
 tests/safeHaskell/ghci/p15.stderr              |  8 ++++++++
 .../safeInfered/UnsafeInfered07.stderr         | 18 ++++++++++++++++++
 .../safeInfered/UnsafeInfered07_A.hs           |  2 +-
 tests/safeHaskell/safeLanguage/SafeLang13.hs   |  2 +-
 tests/safeHaskell/safeLanguage/SafeLang14.hs   |  2 +-
 tests/safeHaskell/unsafeLibs/BadImport02.hs    |  2 +-
 tests/safeHaskell/unsafeLibs/BadImport03.hs    |  2 +-
 tests/typecheck/should_compile/T2433.hs        |  4 ++--
 26 files changed, 67 insertions(+), 47 deletions(-)
 create mode 100644 tests/deriving/should_compile/drv021.stderr
 rename tests/deriving/{should_fail/drvfail010.hs => should_compile/drv022.hs} (70%)
 delete mode 100644 tests/deriving/should_fail/drvfail010.stderr
 delete mode 100644 tests/deriving/should_fail/drvfail010.stderr-hugs

diff --git a/tests/annotations/should_fail/annfail06.hs b/tests/annotations/should_fail/annfail06.hs
index 51c922098..671f0c748 100644
--- a/tests/annotations/should_fail/annfail06.hs
+++ b/tests/annotations/should_fail/annfail06.hs
@@ -7,7 +7,7 @@ import Data.Data
 import Data.Typeable
 
 instance Typeable InstancesInWrongModule where
-    typeOf _ = undefined
+    typeRep _ = undefined
 
 instance Data InstancesInWrongModule where
     gfoldl = undefined
diff --git a/tests/deriving/should_compile/T2378.hs b/tests/deriving/should_compile/T2378.hs
index e3118cb86..4f12313fc 100644
--- a/tests/deriving/should_compile/T2378.hs
+++ b/tests/deriving/should_compile/T2378.hs
@@ -7,4 +7,4 @@ import Data.Data
 
 newtype T f = MkT Int
 
-deriving instance Typeable1 T
+deriving instance Typeable T
diff --git a/tests/deriving/should_compile/T3965.hs b/tests/deriving/should_compile/T3965.hs
index 2ccaaadfd..99217acba 100644
--- a/tests/deriving/should_compile/T3965.hs
+++ b/tests/deriving/should_compile/T3965.hs
@@ -3,16 +3,11 @@ module T3965 where
 
 import Data.Data
 
-data T f e = Inl (f e) deriving (Data, Eq)
+data T f e = Inl (f e) deriving (Data, Typeable, Eq)
 
-instance (Typeable1 f) => Typeable1 (T f) where
-  typeOf1 _ = error "urk"
+newtype Expr f = In (f (Expr f)) deriving Typeable
 
-newtype Expr f = In (f (Expr f))
-instance Typeable1 f => Typeable (Expr f) where
-  typeOf _ = error "urk"
-
-deriving instance (Typeable1 a, Data (a (Expr a))) => Data (Expr a)
+deriving instance (Typeable a, Data (a (Expr a))) => Data (Expr a)
 
 data Var e = Var String deriving (Data, Eq, Typeable)
 
diff --git a/tests/deriving/should_compile/T4302.hs b/tests/deriving/should_compile/T4302.hs
index 50369632f..53035cf59 100644
--- a/tests/deriving/should_compile/T4302.hs
+++ b/tests/deriving/should_compile/T4302.hs
@@ -11,7 +11,7 @@ data Test a
 
 deriving instance Eq (Test a) 
 deriving instance Ord (Test a) 
-deriving instance Typeable1 Test
+deriving instance Typeable Test
 deriving instance Data a => Data (Test a) 
 deriving instance Functor Test 
 deriving instance Foldable Test 
diff --git a/tests/deriving/should_compile/all.T b/tests/deriving/should_compile/all.T
index 6fbe38331..5e9af5ee4 100644
--- a/tests/deriving/should_compile/all.T
+++ b/tests/deriving/should_compile/all.T
@@ -15,6 +15,7 @@ test('drv014', normal, compile, [''])
 test('drv015', normal, compile, [''])
 test('drv020', normal, compile, [''])
 test('drv021', normal, compile, [''])
+test('drv022', normal, compile, [''])
 test('deriving-1935', normal, compile, [''])
 test('T2378', normal, compile, [''])
 test('T2856', normal, compile, [''])
diff --git a/tests/deriving/should_compile/drv021.hs b/tests/deriving/should_compile/drv021.hs
index c9800508d..977372a51 100644
--- a/tests/deriving/should_compile/drv021.hs
+++ b/tests/deriving/should_compile/drv021.hs
@@ -6,7 +6,7 @@
 
 module ShouldCompile where
 
-import Data.Typeable
+import Data.OldTypeable
 
 data T1 a   = T1 a
 data T2 a b = T2 a b 
diff --git a/tests/deriving/should_compile/drv021.stderr b/tests/deriving/should_compile/drv021.stderr
new file mode 100644
index 000000000..8143dfee6
--- /dev/null
+++ b/tests/deriving/should_compile/drv021.stderr
@@ -0,0 +1,13 @@
+
+drv021.hs:9:1: Warning:
+    Module `Data.OldTypeable' is deprecated: Use Data.Typeable instead
+
+drv021.hs:14:19: Warning:
+    In the use of type constructor or class `Typeable1'
+    (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
+    Deprecated: "Use Data.Typeable.Internal instead"
+
+drv021.hs:15:19: Warning:
+    In the use of type constructor or class `Typeable2'
+    (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
+    Deprecated: "Use Data.Typeable.Internal instead"
diff --git a/tests/deriving/should_fail/drvfail010.hs b/tests/deriving/should_compile/drv022.hs
similarity index 70%
rename from tests/deriving/should_fail/drvfail010.hs
rename to tests/deriving/should_compile/drv022.hs
index efecf07cf..9a3e8dba4 100644
--- a/tests/deriving/should_fail/drvfail010.hs
+++ b/tests/deriving/should_compile/drv022.hs
@@ -1,10 +1,10 @@
 {-# LANGUAGE DeriveDataTypeable #-}
 
-module ShouldFail where
+module ShouldCompile where
 import Data.Typeable
 
 data A a b c d e f g h i j = A deriving (Typeable)
-	-- Too many args
+  -- Many args
 
 data B a b = B (a b) deriving (Typeable)
-	-- Non type-kind args
\ No newline at end of file
+  -- Non type-kind args
\ No newline at end of file
diff --git a/tests/deriving/should_fail/T2604.stderr b/tests/deriving/should_fail/T2604.stderr
index 6cda6c36c..8fe5ffff5 100644
--- a/tests/deriving/should_fail/T2604.stderr
+++ b/tests/deriving/should_fail/T2604.stderr
@@ -1,10 +1,10 @@
 
 T2604.hs:7:35:
-    Can't make a derived instance of `Typeable (DList a)':
+    Can't make a derived instance of `Typeable * (DList a)':
       You need -XDeriveDataTypeable to derive an instance for this class
     In the data declaration for `DList'
 
 T2604.hs:9:38:
-    Can't make a derived instance of `Typeable (NList a)':
+    Can't make a derived instance of `Typeable * (NList a)':
       You need -XDeriveDataTypeable to derive an instance for this class
     In the newtype declaration for `NList'
diff --git a/tests/deriving/should_fail/all.T b/tests/deriving/should_fail/all.T
index 5fface82b..e7cb909c2 100644
--- a/tests/deriving/should_fail/all.T
+++ b/tests/deriving/should_fail/all.T
@@ -8,7 +8,6 @@ test('drvfail006', reqlib('mtl'), compile_fail, [''])
 test('drvfail007', normal, compile_fail, [''])
 test('drvfail008', reqlib('mtl'), compile_fail, [''])
 test('drvfail009', normal, compile_fail, [''])
-test('drvfail010', normal, compile_fail, [''])
 test('drvfail011', normal, compile_fail, [''])
 test('drvfail012', normal, compile_fail, [''])
 test('drvfail013', normal, compile_fail, [''])
diff --git a/tests/deriving/should_fail/drvfail010.stderr b/tests/deriving/should_fail/drvfail010.stderr
deleted file mode 100644
index cf2baa644..000000000
--- a/tests/deriving/should_fail/drvfail010.stderr
+++ /dev/null
@@ -1,11 +0,0 @@
-
-drvfail010.hs:6:42:
-    Can't make a derived instance of
-      `Typeable (A a b c d e f g h i j)':
-      `A' must have 7 or fewer arguments
-    In the data declaration for `A'
-
-drvfail010.hs:9:32:
-    Can't make a derived instance of `Typeable (B a b)':
-      `B' must only have arguments of kind `*'
-    In the data declaration for `B'
diff --git a/tests/deriving/should_fail/drvfail010.stderr-hugs b/tests/deriving/should_fail/drvfail010.stderr-hugs
deleted file mode 100644
index f6479975a..000000000
--- a/tests/deriving/should_fail/drvfail010.stderr-hugs
+++ /dev/null
@@ -1 +0,0 @@
-ERROR "drvfail010.hs":6 - Cannot derive instances of class "Typeable"
diff --git a/tests/deriving/should_fail/drvfail014.hs b/tests/deriving/should_fail/drvfail014.hs
index 9039332f2..117b7d54a 100644
--- a/tests/deriving/should_fail/drvfail014.hs
+++ b/tests/deriving/should_fail/drvfail014.hs
@@ -3,7 +3,7 @@
 -- See Trac #1825
 
 module ShouldFail where
-import Data.Typeable
+import Data.OldTypeable
 
 data T1 a = T1 a deriving( Typeable1 )
 
diff --git a/tests/driver/T4437.hs b/tests/driver/T4437.hs
index ca1f149fd..23be89bfc 100644
--- a/tests/driver/T4437.hs
+++ b/tests/driver/T4437.hs
@@ -37,7 +37,8 @@ expectedGhcOnlyExtensions = [
                              "AlternativeLayoutRuleTransitional",
                              "ExplicitNamespaces",
                              "TypeHoles",
-                             "EmptyCase" ]
+                             "EmptyCase",
+                             "AutoDeriveTypeable"]
 
 expectedCabalOnlyExtensions :: [String]
 expectedCabalOnlyExtensions = ["Generics",
diff --git a/tests/indexed-types/should_compile/T1769.hs b/tests/indexed-types/should_compile/T1769.hs
index 57b966051..7a256e1fd 100644
--- a/tests/indexed-types/should_compile/T1769.hs
+++ b/tests/indexed-types/should_compile/T1769.hs
@@ -5,7 +5,7 @@ module T1769 where
 import Data.Typeable
 
 data family T a
-deriving instance Typeable1 T
+deriving instance Typeable T
 -- deriving instance Functor T
 
 data instance T [b] = T1 | T2 b 
diff --git a/tests/perf/should_run/T3245.hs b/tests/perf/should_run/T3245.hs
index f52fc2730..d345fed38 100644
--- a/tests/perf/should_run/T3245.hs
+++ b/tests/perf/should_run/T3245.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE ExistentialQuantification #-}
+{-# LANGUAGE ExistentialQuantification, DeriveDataTypeable #-}
 
 -- The second version (count2) took ages with GHC 6.12
 -- because the typeOf function was not properly memoised
@@ -44,7 +44,4 @@ main = do
   doTime $ count1 x
   doTime $ count1 x
 
-data T = MkT
-tcname :: TyCon
-tcname = mkTyCon "T"
-instance Typeable T where { typeOf _ = mkTyConApp tcname [] }
+data T = MkT deriving Typeable
diff --git a/tests/rename/should_compile/T4003A.hs-boot b/tests/rename/should_compile/T4003A.hs-boot
index b750e4747..a615301e5 100644
--- a/tests/rename/should_compile/T4003A.hs-boot
+++ b/tests/rename/should_compile/T4003A.hs-boot
@@ -4,5 +4,5 @@ import Data.Data
 
 data HsExpr i
 
-instance Typeable1 HsExpr
+instance Typeable HsExpr
 instance Data i => Data (HsExpr i)
diff --git a/tests/safeHaskell/ghci/p15.script b/tests/safeHaskell/ghci/p15.script
index 3faeec9df..81f2033ea 100644
--- a/tests/safeHaskell/ghci/p15.script
+++ b/tests/safeHaskell/ghci/p15.script
@@ -4,7 +4,7 @@
 :set -XDeriveDataTypeable
 :set -XStandaloneDeriving
 
-:m + Data.Typeable
+:m + Data.OldTypeable
 
 data H = H {h :: String} deriving (Typeable, Show)
 
diff --git a/tests/safeHaskell/ghci/p15.stderr b/tests/safeHaskell/ghci/p15.stderr
index bc1069c87..f50d460ed 100644
--- a/tests/safeHaskell/ghci/p15.stderr
+++ b/tests/safeHaskell/ghci/p15.stderr
@@ -1,4 +1,12 @@
 
+Top level: Warning:
+    Module `Data.OldTypeable' is deprecated: Use Data.Typeable instead
+
+<interactive>:10:36: Warning:
+    In the use of type constructor or class `Typeable'
+    (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
+    Deprecated: "Use Data.Typeable.Internal instead"
+
 <interactive>:14:10:
     Can't create hand written instances of Typeable in Safe Haskell! Can only derive them
 
diff --git a/tests/safeHaskell/safeInfered/UnsafeInfered07.stderr b/tests/safeHaskell/safeInfered/UnsafeInfered07.stderr
index 98a7e808f..4a83680d5 100644
--- a/tests/safeHaskell/safeInfered/UnsafeInfered07.stderr
+++ b/tests/safeHaskell/safeInfered/UnsafeInfered07.stderr
@@ -1,4 +1,22 @@
 [1 of 2] Compiling UnsafeInfered07_A ( UnsafeInfered07_A.hs, UnsafeInfered07_A.o )
+
+UnsafeInfered07_A.hs:4:1: Warning:
+    Module `Data.OldTypeable' is deprecated: Use Data.Typeable instead
+
+UnsafeInfered07_A.hs:8:10: Warning:
+    In the use of type constructor or class `Typeable'
+    (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
+    Deprecated: "Use Data.Typeable.Internal instead"
+
+UnsafeInfered07_A.hs:8:10: Warning:
+    In the use of type constructor or class `Typeable'
+    (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
+    Deprecated: "Use Data.Typeable.Internal instead"
+
+UnsafeInfered07_A.hs:9:16: Warning:
+    In the use of `typeOf'
+    (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
+    Deprecated: "Use Data.Typeable.Internal instead"
 [2 of 2] Compiling UnsafeInfered07  ( UnsafeInfered07.hs, UnsafeInfered07.o )
 
 UnsafeInfered07.hs:4:1:
diff --git a/tests/safeHaskell/safeInfered/UnsafeInfered07_A.hs b/tests/safeHaskell/safeInfered/UnsafeInfered07_A.hs
index ffc11597a..9bd6b452d 100644
--- a/tests/safeHaskell/safeInfered/UnsafeInfered07_A.hs
+++ b/tests/safeHaskell/safeInfered/UnsafeInfered07_A.hs
@@ -1,7 +1,7 @@
 -- | Unsafe as hand crafts a typeable instance
 module UnsafeInfered07_A where
 
-import Data.Typeable
+import Data.OldTypeable
 
 data G = G Int
 
diff --git a/tests/safeHaskell/safeLanguage/SafeLang13.hs b/tests/safeHaskell/safeLanguage/SafeLang13.hs
index 9be68a3ab..e11b61658 100644
--- a/tests/safeHaskell/safeLanguage/SafeLang13.hs
+++ b/tests/safeHaskell/safeLanguage/SafeLang13.hs
@@ -5,7 +5,7 @@
 module Main where
 
 import SafeLang13_A
-import Data.Typeable
+import Data.OldTypeable
 
 data H = H String deriving (Typeable, Show)
 
diff --git a/tests/safeHaskell/safeLanguage/SafeLang14.hs b/tests/safeHaskell/safeLanguage/SafeLang14.hs
index 59e8386ac..98e29fbce 100644
--- a/tests/safeHaskell/safeLanguage/SafeLang14.hs
+++ b/tests/safeHaskell/safeLanguage/SafeLang14.hs
@@ -5,7 +5,7 @@
 module Main where
 
 import SafeLang14_A
-import Data.Typeable
+import Data.OldTypeable
 
 data H = H String deriving (Typeable, Show)
 
diff --git a/tests/safeHaskell/unsafeLibs/BadImport02.hs b/tests/safeHaskell/unsafeLibs/BadImport02.hs
index e9d5ca757..80eba6288 100644
--- a/tests/safeHaskell/unsafeLibs/BadImport02.hs
+++ b/tests/safeHaskell/unsafeLibs/BadImport02.hs
@@ -3,7 +3,7 @@
 -- | Here we used typeable to produce an illegal value
 module Main where
 
-import Data.Typeable
+import Data.OldTypeable
 
 import BadImport02_A
 
diff --git a/tests/safeHaskell/unsafeLibs/BadImport03.hs b/tests/safeHaskell/unsafeLibs/BadImport03.hs
index 9b8a5651a..9c06d34ba 100644
--- a/tests/safeHaskell/unsafeLibs/BadImport03.hs
+++ b/tests/safeHaskell/unsafeLibs/BadImport03.hs
@@ -5,7 +5,7 @@
 -- Now using SAFE though so will fail
 module Main where
 
-import Data.Typeable
+import Data.OldTypeable
 
 import BadImport03_A
 
diff --git a/tests/typecheck/should_compile/T2433.hs b/tests/typecheck/should_compile/T2433.hs
index 345c96102..727ec6bb9 100644
--- a/tests/typecheck/should_compile/T2433.hs
+++ b/tests/typecheck/should_compile/T2433.hs
@@ -5,7 +5,7 @@
 
 module T2433 where
 
- import Data.Typeable(Typeable1)
+ import Data.Typeable(Typeable)
  import T2433_Help( T )
 
- deriving instance Typeable1 T
+ deriving instance Typeable T
-- 
GitLab


From b7afbc004d09b51440603d266640db0d8034e1ce Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Tue, 12 Feb 2013 18:08:26 +0000
Subject: [PATCH 152/223] Error message wibble

---
 tests/indexed-types/should_fail/SimpleFail2a.stderr | 1 -
 1 file changed, 1 deletion(-)

diff --git a/tests/indexed-types/should_fail/SimpleFail2a.stderr b/tests/indexed-types/should_fail/SimpleFail2a.stderr
index 9c1f1c904..c8ac4513d 100644
--- a/tests/indexed-types/should_fail/SimpleFail2a.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail2a.stderr
@@ -2,6 +2,5 @@
 SimpleFail2a.hs:11:3:
     Type indexes must match class instance head
     Found `a' but expected `Int'
-    In the data declaration for `Sd'
     In the data instance declaration for `Sd'
     In the instance declaration for `C Int'
-- 
GitLab


From 6cb1a76f061ad18950b7f6fba04fa40c229fdf2d Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Tue, 12 Feb 2013 18:08:42 +0000
Subject: [PATCH 153/223] Bump bounds slightly

---
 tests/perf/compiler/all.T | 7 +++----
 tests/perf/haddock/all.T  | 3 ++-
 2 files changed, 5 insertions(+), 5 deletions(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 93b2c7dbb..50c152124 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -160,9 +160,10 @@ test('T3064',
       compiler_stats_num_field('peak_megabytes_allocated',
           [(wordsize(32), 14, 1),
         # expected value: 14 (x86/Linux 28-06-2012):
-           (wordsize(64), 26, 1)]),
+           (wordsize(64), 23, 1)]),
             # (amd64/Linux):            18
             # (amd64/Linux) 2012-02-07: 26
+            # (amd64/Linux) 2013-02-12: 23
 
       compiler_stats_num_field('bytes allocated',
           [(wordsize(32), 111189536, 10),
@@ -175,11 +176,9 @@ test('T3064',
       compiler_stats_num_field('max_bytes_used',
           [(wordsize(32), 5511604, 20),
         # expected value: 2247016 (x86/Linux) (28/6/2011):
-           (wordsize(64), 8945328, 5)]),
+           (wordsize(64), 9819288, 5)]),
             # (amd64/Linux, intree) (28/06/2011):  4032024
             # (amd64/Linux, intree) (07/02/2013):  9819288
-            # (amd64/Linux, intree) (10/02/2013):  8945328 
-            #   apparently courtesy of the b5c18c (Trac #5113)
        only_ways(['normal'])
       ],
      compile,
diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T
index f8238df7e..ba25e146b 100644
--- a/tests/perf/haddock/all.T
+++ b/tests/perf/haddock/all.T
@@ -25,11 +25,12 @@ test('haddock.base',
           ,(wordsize(32), 52237984, 1)])
             # 2013-02-10: 52237984 (x86/OSX)
      ,stats_num_field('bytes allocated',
-          [(wordsize(64), 6064874536, 2)
+          [(wordsize(64), 6282746976, 5)
             # 2012-08-14: 5920822352 (amd64/Linux)
             # 2012-09-20: 5829972376 (amd64/Linux)
             # 2012-10-08: 5902601224 (amd64/Linux)
             # 2013-01-17: 6064874536 (x86_64/Linux)
+            # 2013-02-10: 6282746976 (x86_64/Linux)
           ,(platform('i386-unknown-mingw32'), 3358693084, 1)
             # 2013-02-10:                     3358693084 (x86/Windows)
           ,(wordsize(32), 3146596848, 1)])
-- 
GitLab


From dcda42979d9d369e3be052399912ecdce141d895 Mon Sep 17 00:00:00 2001
From: Jose Pedro Magalhaes <jpm@cs.ox.ac.uk>
Date: Wed, 13 Feb 2013 10:03:13 +0000
Subject: [PATCH 154/223] Proxy is now defined in Data.Typeable

---
 tests/typecheck/should_run/T3731.hs | 1 -
 1 file changed, 1 deletion(-)

diff --git a/tests/typecheck/should_run/T3731.hs b/tests/typecheck/should_run/T3731.hs
index af858e570..3024629ec 100644
--- a/tests/typecheck/should_run/T3731.hs
+++ b/tests/typecheck/should_run/T3731.hs
@@ -13,7 +13,6 @@ import Data.Typeable
 class Sat a where
     dict :: a
 
-data Proxy (a :: * -> *)
 
 class ( Sat (ctx a)) => Data ctx a where
     gunfold :: Proxy ctx
-- 
GitLab


From 0f6885e23486e673ec3e45b2eb435952b61a63c3 Mon Sep 17 00:00:00 2001
From: Jose Pedro Magalhaes <jpm@cs.ox.ac.uk>
Date: Wed, 13 Feb 2013 10:03:43 +0000
Subject: [PATCH 155/223] Proxy comes from Data.Typeable, Typeable1/2 no longer
 exist

---
 tests/typecheck/should_run/T1735_Help/Basics.hs | 9 ++-------
 1 file changed, 2 insertions(+), 7 deletions(-)

diff --git a/tests/typecheck/should_run/T1735_Help/Basics.hs b/tests/typecheck/should_run/T1735_Help/Basics.hs
index c7fad9139..d444db705 100644
--- a/tests/typecheck/should_run/T1735_Help/Basics.hs
+++ b/tests/typecheck/should_run/T1735_Help/Basics.hs
@@ -21,11 +21,6 @@ module T1735_Help.Basics (
 import Data.Typeable
 import T1735_Help.Context
 
-#ifdef __HADDOCK__
-data Proxy
-#else
-data Proxy (a :: * -> *)
-#endif
 
 ------------------------------------------------------------------------------
 -- The ingenious Data class
@@ -61,14 +56,14 @@ class (Typeable a, Sat (ctx a)) => Data ctx a
      dataTypeOf _ _ = undefined
 
      -- | Mediate types and unary type constructors
-     dataCast1 :: Typeable1 t
+     dataCast1 :: Typeable t
                => Proxy ctx
                -> (forall b. Data ctx b => w (t b))
                -> Maybe (w a)
      dataCast1 _ _ = Nothing
 
      -- | Mediate types and binary type constructors
-     dataCast2 :: Typeable2 t
+     dataCast2 :: Typeable t
                => Proxy ctx
                -> (forall b c. (Data ctx b, Data ctx c) => w (t b c))
                -> Maybe (w a)
-- 
GitLab


From fc09a8620ecd52dce75c54e5cff85ae0fd235bba Mon Sep 17 00:00:00 2001
From: Jose Pedro Magalhaes <jpm@cs.ox.ac.uk>
Date: Wed, 13 Feb 2013 10:39:34 +0000
Subject: [PATCH 156/223] Test #7631

---
 tests/generics/GenNewtype.hs     | 10 ++++++++++
 tests/generics/GenNewtype.stdout |  1 +
 tests/generics/all.T             |  1 +
 3 files changed, 12 insertions(+)
 create mode 100644 tests/generics/GenNewtype.hs
 create mode 100644 tests/generics/GenNewtype.stdout

diff --git a/tests/generics/GenNewtype.hs b/tests/generics/GenNewtype.hs
new file mode 100644
index 000000000..c1161fe7f
--- /dev/null
+++ b/tests/generics/GenNewtype.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE DeriveGeneric #-}
+
+module Main where
+
+import GHC.Generics
+
+data    X = X   deriving Generic
+newtype Y = Y X deriving Generic
+
+main = print [isNewtype (from X), isNewtype (from (Y X))]
diff --git a/tests/generics/GenNewtype.stdout b/tests/generics/GenNewtype.stdout
new file mode 100644
index 000000000..a9896e7d7
--- /dev/null
+++ b/tests/generics/GenNewtype.stdout
@@ -0,0 +1 @@
+[False,True]
diff --git a/tests/generics/all.T b/tests/generics/all.T
index 1541a4725..7a88487fe 100644
--- a/tests/generics/all.T
+++ b/tests/generics/all.T
@@ -9,6 +9,7 @@ test('GenCannotDoRep0', normal, compile_fail, [''])
 test('GenCannotDoRep1', normal, compile_fail, [''])
 test('GenCannotDoRep2', normal, compile_fail, [''])
 test('T5884',           normal, compile, [''])
+test('GenNewtype',      normal, compile_and_run, [''])
 
 test('GenCanDoRep1_0',    normal, compile, [''])
 test('GenDerivOutput1_0',  normal, compile, ['-dsuppress-uniques'])
-- 
GitLab


From 72c22fa9292734acf1c9a58dac62c4371434ca8d Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 13 Feb 2013 17:03:01 +0000
Subject: [PATCH 157/223] TH empty case expressions now ok (with -XEmptyCase)

---
 tests/th/TH_emptycase.hs     | 4 ++--
 tests/th/TH_emptycase.stderr | 6 ------
 tests/th/all.T               | 2 +-
 3 files changed, 3 insertions(+), 9 deletions(-)
 delete mode 100644 tests/th/TH_emptycase.stderr

diff --git a/tests/th/TH_emptycase.hs b/tests/th/TH_emptycase.hs
index d68ca9a8e..fc75cfe5b 100644
--- a/tests/th/TH_emptycase.hs
+++ b/tests/th/TH_emptycase.hs
@@ -1,6 +1,6 @@
-{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TemplateHaskell, EmptyCase #-}
 -- Trac #2431: empty case expression
---             currently rejected
+--             now accepted
 
 module Main where
 
diff --git a/tests/th/TH_emptycase.stderr b/tests/th/TH_emptycase.stderr
deleted file mode 100644
index 2de068769..000000000
--- a/tests/th/TH_emptycase.stderr
+++ /dev/null
@@ -1,6 +0,0 @@
-
-TH_emptycase.hs:10:7:
-    Case expression with no alternatives
-    When splicing a TH expression: case 'a' of
-    In the expression: $(caseE (litE $ CharL 'a') [])
-    In an equation for `f': f = $(caseE (litE $ CharL 'a') [])
diff --git a/tests/th/all.T b/tests/th/all.T
index b279dcd6e..fa185aa4c 100644
--- a/tests/th/all.T
+++ b/tests/th/all.T
@@ -138,7 +138,7 @@ test('T2817', normal, compile, ['-v0'])
 test('T2713', normal, compile_fail, ['-v0'])
 test('T2674', normal, compile_fail, ['-v0'])
 test('T2931', normal, compile, ['-v0'])
-test('TH_emptycase', normal, compile_fail, ['-v0'])
+test('TH_emptycase', normal, compile, ['-v0'])
 
 test('T2386', extra_clean(['T2386_Lib.hi', 'T2386_Lib.o']),
 	      run_command,
-- 
GitLab


From 71ec33f721ed0b30e42e407cc1f235bf1cb5aeae Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Wed, 13 Feb 2013 17:08:52 +0000
Subject: [PATCH 158/223] Reorder some functions to group them

Predicates now match the order they are documented on the wiki
---
 driver/testlib.py | 35 +++++++++++++++++------------------
 1 file changed, 17 insertions(+), 18 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 56e1b4604..de8ab9012 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -304,12 +304,15 @@ def when(b, f):
 def unless(b, f):
     return when(not b, f)
 
-def fast():
-    return config.fast
-
 def doing_ghci():
     return 'ghci' in config.run_ways
 
+def ghci_dynamic( ):
+    return config.ghc_dynamic_by_default
+
+def fast():
+    return config.fast
+
 def platform( plat ):
     return config.platform == plat
 
@@ -322,9 +325,6 @@ def arch( arch ):
 def wordsize( ws ):
     return config.wordsize == str(ws)
 
-def unregisterised( ):
-    return config.unregisterised
-
 def msys( ):
     return config.msys
 
@@ -340,20 +340,12 @@ def have_dynamic( ):
 def have_profiling( ):
     return config.have_profiling
 
-# ---
-
-def ghci_dynamic( ):
-    return config.ghc_dynamic_by_default
-
 def in_tree_compiler( ):
     return config.in_tree_compiler
 
 def compiler_type( compiler ):
     return config.compiler_type == compiler
 
-def compiler_profiled( ):
-    return config.compiler_profiled
-
 def compiler_lt( compiler, version ):
     return config.compiler_type == compiler and \
            version_lt(config.compiler_version, version)
@@ -370,9 +362,20 @@ def compiler_ge( compiler, version ):
     return config.compiler_type == compiler and \
            version_ge(config.compiler_version, version)
 
+def unregisterised( ):
+    return config.unregisterised
+
+def compiler_profiled( ):
+    return config.compiler_profiled
+
 def compiler_debugged( ):
     return config.compiler_debugged
 
+def tag( t ):
+    return t in config.compiler_tags
+
+# ---
+
 def namebase( nb ):
    return lambda opts, nb=nb: _namebase(opts, nb)
 
@@ -381,10 +384,6 @@ def _namebase( opts, nb ):
 
 # ---
 
-def tag( t ):
-    return t in config.compiler_tags
-
-# ---
 def high_memory_usage(name, opts):
     opts.alone = True
 
-- 
GitLab


From 7e1fb1728fbddf5422642765c8c31f36fc1921f6 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 13 Feb 2013 17:30:45 +0000
Subject: [PATCH 159/223] peak_megabytes_allocated bounces around a lot

---
 tests/perf/compiler/all.T | 6 ++++--
 1 file changed, 4 insertions(+), 2 deletions(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 50c152124..a7ac4e2d8 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -13,11 +13,12 @@ test('T1969',
              #            19 (x86/OS X)
              # 2013-02-10 13 (x86/Windows)
              # 2013-02-10 14 (x86/OSX)
-           (wordsize(64), 25, 1)]),
+           (wordsize(64), 23, 10)]),
              #            28 (amd64/Linux)
              #            34 (amd64/Linux)
              # 2012-09-20 23 (amd64/Linux)
              # 2012-10-03 25 (amd64/Linux if .hi exists)
+             # 2013-02-13 23, but unstable so increased to 10% range
       compiler_stats_num_field('max_bytes_used',
           [(platform('i386-unknown-mingw32'), 5094914, 2),
                                  # 2010-05-17 5717704 (x86/Windows)
@@ -160,10 +161,11 @@ test('T3064',
       compiler_stats_num_field('peak_megabytes_allocated',
           [(wordsize(32), 14, 1),
         # expected value: 14 (x86/Linux 28-06-2012):
-           (wordsize(64), 23, 1)]),
+           (wordsize(64), 26, 10)]),
             # (amd64/Linux):            18
             # (amd64/Linux) 2012-02-07: 26
             # (amd64/Linux) 2013-02-12: 23
+            # (amd64/Linux) 2013-02-13: back to 26; increased range to 10%
 
       compiler_stats_num_field('bytes allocated',
           [(wordsize(32), 111189536, 10),
-- 
GitLab


From c3c9babf10990ccc36451b3758d6f19d749b879d Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 13 Feb 2013 17:31:34 +0000
Subject: [PATCH 160/223] Significant (15%) bytes-allocated reduction in
 haddock.Cabal and haddock.base

I'm not sure why, but I'm happy!
---
 tests/perf/haddock/all.T | 6 ++++--
 1 file changed, 4 insertions(+), 2 deletions(-)

diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T
index ba25e146b..e1fdd869e 100644
--- a/tests/perf/haddock/all.T
+++ b/tests/perf/haddock/all.T
@@ -25,12 +25,13 @@ test('haddock.base',
           ,(wordsize(32), 52237984, 1)])
             # 2013-02-10: 52237984 (x86/OSX)
      ,stats_num_field('bytes allocated',
-          [(wordsize(64), 6282746976, 5)
+          [(wordsize(64), 5184155784, 5)
             # 2012-08-14: 5920822352 (amd64/Linux)
             # 2012-09-20: 5829972376 (amd64/Linux)
             # 2012-10-08: 5902601224 (amd64/Linux)
             # 2013-01-17: 6064874536 (x86_64/Linux)
             # 2013-02-10: 6282746976 (x86_64/Linux)
+            # 2013-02-13: 5184155784 (x86_64/Linux)
           ,(platform('i386-unknown-mingw32'), 3358693084, 1)
             # 2013-02-10:                     3358693084 (x86/Windows)
           ,(wordsize(32), 3146596848, 1)])
@@ -67,10 +68,11 @@ test('haddock.Cabal',
             # 2012-08-14: 47461532 (x86/OSX)
             # 2013-02-10: 46563344 (x86/OSX)
      ,stats_num_field('bytes allocated',
-          [(wordsize(64), 3373401360, 2)
+          [(wordsize(64), 2809307464, 5)
             # 2012-08-14: 3255435248 (amd64/Linux)
             # 2012-08-29: 3324606664 (amd64/Linux, new codegen)
             # 2012-10-08: 3373401360 (amd64/Linux)
+            # 2013-02-13: 2809307464 (amd64/Linux)
           ,(platform('i386-unknown-mingw32'), 1906532680, 1)
             # 2012-10-30:                     1733638168 (x86/Windows)
             # 2013-02-10:                     1906532680 (x86/Windows)
-- 
GitLab


From 38d2e6f158b445d171e4efc1087907fb5839500d Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 13 Feb 2013 17:41:08 +0000
Subject: [PATCH 161/223] Test Trac #7649

---
 tests/stranal/should_run/T7649.hs     | 32 +++++++++++++++++++++++++++
 tests/stranal/should_run/T7649.stdout |  6 +++++
 tests/stranal/should_run/all.T        |  2 +-
 3 files changed, 39 insertions(+), 1 deletion(-)
 create mode 100644 tests/stranal/should_run/T7649.hs
 create mode 100644 tests/stranal/should_run/T7649.stdout

diff --git a/tests/stranal/should_run/T7649.hs b/tests/stranal/should_run/T7649.hs
new file mode 100644
index 000000000..cbf3d7177
--- /dev/null
+++ b/tests/stranal/should_run/T7649.hs
@@ -0,0 +1,32 @@
+{-# LANGUAGE ViewPatterns, BangPatterns #-}
+module Main where
+
+import Control.Exception
+main :: IO ()
+main = do print (f False)
+          print (f True)
+          print (g undefined) `catchE` \_ -> putStrLn "g exception"
+          print (h undefined) `catchE` \_ -> putStrLn "h exception"
+          print (i undefined) `catchE` \_ -> putStrLn "i exception"
+          putStrLn "Done"
+
+catchE :: IO a -> (ErrorCall -> IO a) -> IO a
+catchE = catch
+
+f :: Bool -> String
+f (view -> Nothing) = "Got Nothing"
+f (view -> Just x)  = "Got Just " ++ show x
+
+g :: Bool -> String
+g (view -> x) = "g Got something"
+
+h :: Bool -> String
+h (view -> !x) = "h Got something"
+
+i :: Bool -> String
+i !(view -> x) = "i Got something"
+
+view :: Bool -> Maybe Int
+view False = Nothing
+view True = Just 5
+
diff --git a/tests/stranal/should_run/T7649.stdout b/tests/stranal/should_run/T7649.stdout
new file mode 100644
index 000000000..56f7f53b5
--- /dev/null
+++ b/tests/stranal/should_run/T7649.stdout
@@ -0,0 +1,6 @@
+"Got Nothing"
+"Got Just 5"
+"g Got something"
+h exception
+i exception
+Done
diff --git a/tests/stranal/should_run/all.T b/tests/stranal/should_run/all.T
index d94a7c492..0c43aac8c 100644
--- a/tests/stranal/should_run/all.T
+++ b/tests/stranal/should_run/all.T
@@ -6,4 +6,4 @@ test('strun002', exit_code(1), compile_and_run, [''])
 test('strun003', normal, compile_and_run, [''])
 test('strun004', normal, compile_and_run, [''])
 test('T2756b', normal, compile_and_run, [''])
-
+test('T7649', normal, compile_and_run, [''])
-- 
GitLab


From b6b212538ab4ecd65f3aeaad0d2606639df67e82 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Wed, 13 Feb 2013 17:41:23 +0000
Subject: [PATCH 162/223] Test Trac #7669

---
 tests/deSugar/should_compile/T7669.hs | 11 +++++++++++
 tests/deSugar/should_compile/all.T    |  1 +
 2 files changed, 12 insertions(+)
 create mode 100644 tests/deSugar/should_compile/T7669.hs

diff --git a/tests/deSugar/should_compile/T7669.hs b/tests/deSugar/should_compile/T7669.hs
new file mode 100644
index 000000000..b665b6543
--- /dev/null
+++ b/tests/deSugar/should_compile/T7669.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE EmptyCase #-}
+{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}  
+
+module T7669 where
+
+data Void
+
+foo :: Void -> ()
+foo x = case x of {}
+-- Should not get incomplete-pattern warning
+
diff --git a/tests/deSugar/should_compile/all.T b/tests/deSugar/should_compile/all.T
index bf3b068ec..4551709e6 100644
--- a/tests/deSugar/should_compile/all.T
+++ b/tests/deSugar/should_compile/all.T
@@ -101,3 +101,4 @@ test('T5252Take2',
      run_command, 
      ['$MAKE -s --no-print-directory T5252Take2'])
 test('T2431', normal, compile, ['-ddump-simpl -dsuppress-uniques'])
+test('T7669', normal, compile, [''])
-- 
GitLab


From cd7895eef086ac9ff7befbea01e3b3657d42c29c Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 14 Feb 2013 08:32:39 +0000
Subject: [PATCH 163/223] Test Trac #876

---
 tests/perf/should_run/T876.hs     | 11 +++++++++++
 tests/perf/should_run/T876.stdout |  1 +
 tests/perf/should_run/all.T       | 11 +++++++++++
 3 files changed, 23 insertions(+)
 create mode 100644 tests/perf/should_run/T876.hs
 create mode 100644 tests/perf/should_run/T876.stdout

diff --git a/tests/perf/should_run/T876.hs b/tests/perf/should_run/T876.hs
new file mode 100644
index 000000000..398859f86
--- /dev/null
+++ b/tests/perf/should_run/T876.hs
@@ -0,0 +1,11 @@
+-- This test allocates a lot more if length is
+-- not a good consumer
+
+module Main where
+import System.Environment (getArgs)
+
+foo :: Int -> Int
+foo n = sum [ length [i..n] | i <- [1..n] ]
+
+main = do { [arg] <- getArgs
+          ; print (foo (read arg)) }
diff --git a/tests/perf/should_run/T876.stdout b/tests/perf/should_run/T876.stdout
new file mode 100644
index 000000000..b9d569380
--- /dev/null
+++ b/tests/perf/should_run/T876.stdout
@@ -0,0 +1 @@
+50005000
diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T
index a8ea00317..58ffe8f2d 100644
--- a/tests/perf/should_run/all.T
+++ b/tests/perf/should_run/all.T
@@ -49,6 +49,17 @@ test('lazy-bs-alloc',
      compile_and_run,
      ['-O'])
 
+test('T876',
+     [stats_num_field('bytes allocated',
+          [(wordsize(64), 1263712 , 5),
+              # 2013-02-14: 1263712 (x86_64/Linux)
+           (wordsize(32), 663712, 5)]),
+      only_ways(['normal']),
+      extra_run_opts('10000')
+      ],
+     compile_and_run,
+     ['-O'])
+
 # Get reproducible floating-point results on x86
 if config.arch == 'i386':
    sse2_opts = '-msse2'
-- 
GitLab


From 114ff02dba9ae4d3cc1b67dec2a5b773c131b81f Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 14 Feb 2013 10:43:16 +0000
Subject: [PATCH 164/223] Change T3064's peak-megabytes again.  It just bounces
 around

---
 tests/perf/compiler/all.T | 5 ++---
 1 file changed, 2 insertions(+), 3 deletions(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index a7ac4e2d8..556a03bc1 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -161,11 +161,10 @@ test('T3064',
       compiler_stats_num_field('peak_megabytes_allocated',
           [(wordsize(32), 14, 1),
         # expected value: 14 (x86/Linux 28-06-2012):
-           (wordsize(64), 26, 10)]),
+           (wordsize(64), 23, 10)]),
             # (amd64/Linux):            18
             # (amd64/Linux) 2012-02-07: 26
-            # (amd64/Linux) 2013-02-12: 23
-            # (amd64/Linux) 2013-02-13: back to 26; increased range to 10%
+            # (amd64/Linux) 2013-02-12: 23; increased range to 10%
 
       compiler_stats_num_field('bytes allocated',
           [(wordsize(32), 111189536, 10),
-- 
GitLab


From 0dd602b9d81d0c39e566808aed67dd48615b77e6 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 14 Feb 2013 10:43:48 +0000
Subject: [PATCH 165/223] Wibbles because of exprStats change

---
 tests/simplCore/should_compile/T3717.stderr       | 2 +-
 tests/simplCore/should_compile/T3772.stdout       | 2 +-
 tests/simplCore/should_compile/T4908.stderr       | 2 +-
 tests/simplCore/should_compile/T4930.stderr       | 2 +-
 tests/simplCore/should_compile/spec-inline.stderr | 2 +-
 5 files changed, 5 insertions(+), 5 deletions(-)

diff --git a/tests/simplCore/should_compile/T3717.stderr b/tests/simplCore/should_compile/T3717.stderr
index 445e2b819..bafc97436 100644
--- a/tests/simplCore/should_compile/T3717.stderr
+++ b/tests/simplCore/should_compile/T3717.stderr
@@ -1,6 +1,6 @@
 
 ==================== Tidy Core ====================
-Result size of Tidy Core = {terms: 19, types: 10, coercions: 0}
+Result size of Tidy Core = {terms: 22, types: 10, coercions: 0}
 
 Rec {
 T3717.$wfoo [Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int#
diff --git a/tests/simplCore/should_compile/T3772.stdout b/tests/simplCore/should_compile/T3772.stdout
index 4f4d60018..0b21950e9 100644
--- a/tests/simplCore/should_compile/T3772.stdout
+++ b/tests/simplCore/should_compile/T3772.stdout
@@ -1,6 +1,6 @@
 
 ==================== Tidy Core ====================
-Result size of Tidy Core = {terms: 23, types: 10, coercions: 0}
+Result size of Tidy Core = {terms: 27, types: 10, coercions: 0}
 
 Rec {
 xs :: GHC.Prim.Int# -> ()
diff --git a/tests/simplCore/should_compile/T4908.stderr b/tests/simplCore/should_compile/T4908.stderr
index 9af872363..fa5205633 100644
--- a/tests/simplCore/should_compile/T4908.stderr
+++ b/tests/simplCore/should_compile/T4908.stderr
@@ -1,6 +1,6 @@
 
 ==================== Tidy Core ====================
-Result size of Tidy Core = {terms: 47, types: 38, coercions: 0}
+Result size of Tidy Core = {terms: 54, types: 38, coercions: 0}
 
 Rec {
 T4908.f_$s$wf [Occ=LoopBreaker]
diff --git a/tests/simplCore/should_compile/T4930.stderr b/tests/simplCore/should_compile/T4930.stderr
index fd3b72da2..2d7c58213 100644
--- a/tests/simplCore/should_compile/T4930.stderr
+++ b/tests/simplCore/should_compile/T4930.stderr
@@ -1,6 +1,6 @@
 
 ==================== Tidy Core ====================
-Result size of Tidy Core = {terms: 20, types: 10, coercions: 0}
+Result size of Tidy Core = {terms: 22, types: 10, coercions: 0}
 
 lvl :: [GHC.Types.Char]
 [GblId, Str=DmdType]
diff --git a/tests/simplCore/should_compile/spec-inline.stderr b/tests/simplCore/should_compile/spec-inline.stderr
index d3fa84e9e..b604214c0 100644
--- a/tests/simplCore/should_compile/spec-inline.stderr
+++ b/tests/simplCore/should_compile/spec-inline.stderr
@@ -1,6 +1,6 @@
 
 ==================== Tidy Core ====================
-Result size of Tidy Core = {terms: 140, types: 55, coercions: 0}
+Result size of Tidy Core = {terms: 156, types: 55, coercions: 0}
 
 Roman.foo3 :: GHC.Types.Int
 [GblId, Str=DmdType b]
-- 
GitLab


From bb54620903c6c9933e39cd590d93a5b67994c849 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 14 Feb 2013 10:44:22 +0000
Subject: [PATCH 166/223] Wibbles because of length-is-good-consumer change

---
 tests/simplCore/should_compile/T7360.stderr | 41 ++++++++++++++-------
 1 file changed, 27 insertions(+), 14 deletions(-)

diff --git a/tests/simplCore/should_compile/T7360.stderr b/tests/simplCore/should_compile/T7360.stderr
index d48570395..62dc4b83c 100644
--- a/tests/simplCore/should_compile/T7360.stderr
+++ b/tests/simplCore/should_compile/T7360.stderr
@@ -1,6 +1,6 @@
 
 ==================== Tidy Core ====================
-Result size of Tidy Core = {terms: 27, types: 24, coercions: 0}
+Result size of Tidy Core = {terms: 36, types: 28, coercions: 0}
 
 T7360.$WFoo3 [InlPrag=INLINE] :: GHC.Types.Int -> T7360.Foo
 [GblId[DataConWrapper],
@@ -21,13 +21,22 @@ T7360.fun1 [InlPrag=NOINLINE] :: T7360.Foo -> ()
 T7360.fun1 =
   \ (x :: T7360.Foo) -> case x of _ { __DEFAULT -> GHC.Tuple.() }
 
-T7360.fun3 :: ()
+T7360.fun4 :: ()
 [GblId,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=False,
          ConLike=False, WorkFree=False, Expandable=False,
          Guidance=IF_ARGS [] 20 0}]
-T7360.fun3 = T7360.fun1 T7360.Foo1
+T7360.fun4 = T7360.fun1 T7360.Foo1
+
+T7360.fun3 :: GHC.Types.Int
+[GblId,
+ Caf=NoCafRefs,
+ Str=DmdType m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
+         ConLike=True, WorkFree=True, Expandable=True,
+         Guidance=IF_ARGS [] 10 20}]
+T7360.fun3 = GHC.Types.I# 0
 
 T7360.fun2 :: forall a. [a] -> ((), GHC.Types.Int)
 [GblId,
@@ -36,20 +45,24 @@ T7360.fun2 :: forall a. [a] -> ((), GHC.Types.Int)
  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
-         Tmpl= \ (@ a) (x [Occ=Once] :: [a]) ->
-                 (T7360.fun3,
-                  case x of wild { __DEFAULT ->
-                  case GHC.List.$wlen @ a wild 0 of ww { __DEFAULT ->
-                  GHC.Types.I# ww
-                  }
+         Tmpl= \ (@ a) (x [Occ=Once!] :: [a]) ->
+                 (T7360.fun4,
+                  case x of wild {
+                    [] -> T7360.fun3;
+                    : _ _ ->
+                      case GHC.List.$wlenAcc @ a wild 0 of ww { __DEFAULT ->
+                      GHC.Types.I# ww
+                      }
                   })}]
 T7360.fun2 =
   \ (@ a) (x :: [a]) ->
-    (T7360.fun3,
-     case x of wild { __DEFAULT ->
-     case GHC.List.$wlen @ a wild 0 of ww { __DEFAULT ->
-     GHC.Types.I# ww
-     }
+    (T7360.fun4,
+     case x of wild {
+       [] -> T7360.fun3;
+       : ds ds1 ->
+         case GHC.List.$wlenAcc @ a wild 0 of ww { __DEFAULT ->
+         GHC.Types.I# ww
+         }
      })
 
 
-- 
GitLab


From d59796281bc692b0faf614620de1cf3a9f344af4 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Thu, 14 Feb 2013 13:15:30 +0000
Subject: [PATCH 167/223] add a StableName test

---
 tests/rts/all.T                |  4 ++++
 tests/rts/stablename001.hs     | 13 +++++++++++++
 tests/rts/stablename001.stdout |  1 +
 3 files changed, 18 insertions(+)
 create mode 100644 tests/rts/stablename001.hs
 create mode 100644 tests/rts/stablename001.stdout

diff --git a/tests/rts/all.T b/tests/rts/all.T
index 3ccd14297..d96e5476d 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -164,3 +164,7 @@ test('T7227', [ extra_run_opts('+RTS -tT7227.stat --machine-readable -RTS'),
             , compile_and_run, [''] )
 
 test('T7636', [ exit_code(1), extra_run_opts('100000') ], compile_and_run, [''] )
+
+test('stablename001', expect_fail_for(['hpc']), compile_and_run, [''])
+# hpc should fail this, because it tags every variable occurrence with
+# a different tick.  It's probably a bug if it works, hence expect_fail.
diff --git a/tests/rts/stablename001.hs b/tests/rts/stablename001.hs
new file mode 100644
index 000000000..f046f7c7f
--- /dev/null
+++ b/tests/rts/stablename001.hs
@@ -0,0 +1,13 @@
+import System.Mem.StableName
+import System.Mem
+
+-- Test that we get the same StableName even after a GC.  This is easy
+-- to get wrong, by not following indirections properly.
+
+main = do
+  let x = [1..10]
+  seq x (return ())
+  n1 <- makeStableName x
+  performGC
+  n2 <- makeStableName x
+  print (n1 == n2)
diff --git a/tests/rts/stablename001.stdout b/tests/rts/stablename001.stdout
new file mode 100644
index 000000000..0ca95142b
--- /dev/null
+++ b/tests/rts/stablename001.stdout
@@ -0,0 +1 @@
+True
-- 
GitLab


From 779c4fe11ffd64979206ac43314888c1416979f4 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Thu, 14 Feb 2013 13:35:30 +0000
Subject: [PATCH 168/223] fix T3064 bounds

---
 tests/perf/compiler/all.T | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index 556a03bc1..fee07dd52 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -177,9 +177,10 @@ test('T3064',
       compiler_stats_num_field('max_bytes_used',
           [(wordsize(32), 5511604, 20),
         # expected value: 2247016 (x86/Linux) (28/6/2011):
-           (wordsize(64), 9819288, 5)]),
+           (wordsize(64), 8687360, 5)]),
             # (amd64/Linux, intree) (28/06/2011):  4032024
             # (amd64/Linux, intree) (07/02/2013):  9819288
+            # (amd64/Linux)         (14/02/2013):  8687360
        only_ways(['normal'])
       ],
      compile,
-- 
GitLab


From 91798755dde75d037af8e744f459893433481679 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 14 Feb 2013 14:46:13 +0000
Subject: [PATCH 169/223] Error message wibbles when adding overloaded lists

---
 tests/codeGen/should_run/cgrun064.hs         |  2 +-
 tests/codeGen/should_run/cgrun068.hs         |  2 +-
 tests/codeGen/should_run/cgrun070.hs         |  2 +-
 tests/driver/T4437.hs                        |  1 +
 tests/driver/werror.stderr                   | 28 ++++++++++----------
 tests/ghci.debugger/scripts/break003.stderr  |  2 +-
 tests/ghci.debugger/scripts/break003.stdout  |  4 +--
 tests/ghci.debugger/scripts/break005.stdout  |  2 +-
 tests/ghci.debugger/scripts/break006.stderr  | 12 ++++-----
 tests/ghci.debugger/scripts/break006.stdout  | 12 ++++-----
 tests/ghci.debugger/scripts/break027.stdout  |  2 +-
 tests/ghci.debugger/scripts/hist001.stdout   | 18 ++++++-------
 tests/rename/should_fail/T5892a.stderr       | 20 +++++++-------
 tests/th/TH_exn1.stderr                      |  2 +-
 tests/typecheck/should_fail/T2534.stderr     |  2 +-
 tests/typecheck/should_fail/T5858.stderr     | 20 +++++++-------
 tests/typecheck/should_fail/tcfail001.stderr |  2 +-
 tests/typecheck/should_fail/tcfail012.stderr |  2 +-
 18 files changed, 68 insertions(+), 67 deletions(-)

diff --git a/tests/codeGen/should_run/cgrun064.hs b/tests/codeGen/should_run/cgrun064.hs
index aa037e878..24544c438 100644
--- a/tests/codeGen/should_run/cgrun064.hs
+++ b/tests/codeGen/should_run/cgrun064.hs
@@ -5,7 +5,7 @@
 
 module Main ( main ) where
 
-import GHC.Exts
+import GHC.Exts hiding (IsList(..))
 import GHC.Prim
 import GHC.ST
 
diff --git a/tests/codeGen/should_run/cgrun068.hs b/tests/codeGen/should_run/cgrun068.hs
index 9d9a0f954..69a8b279f 100644
--- a/tests/codeGen/should_run/cgrun068.hs
+++ b/tests/codeGen/should_run/cgrun068.hs
@@ -33,7 +33,7 @@ import Control.Exception (assert)
 import Control.Monad
 import Control.Monad.Trans.State.Strict
 import Control.Monad.Trans.Class
-import GHC.Exts
+import GHC.Exts hiding (IsList(..))
 import GHC.ST hiding (liftST)
 import Prelude hiding (length, read)
 import qualified Prelude as P
diff --git a/tests/codeGen/should_run/cgrun070.hs b/tests/codeGen/should_run/cgrun070.hs
index 1f6b5622b..3187af6f6 100644
--- a/tests/codeGen/should_run/cgrun070.hs
+++ b/tests/codeGen/should_run/cgrun070.hs
@@ -6,7 +6,7 @@
 module Main ( main ) where
 
 import GHC.Word
-import GHC.Exts
+import GHC.Exts hiding (IsList(..))
 import GHC.Prim
 import GHC.ST
 
diff --git a/tests/driver/T4437.hs b/tests/driver/T4437.hs
index 23be89bfc..617484c6c 100644
--- a/tests/driver/T4437.hs
+++ b/tests/driver/T4437.hs
@@ -37,6 +37,7 @@ expectedGhcOnlyExtensions = [
                              "AlternativeLayoutRuleTransitional",
                              "ExplicitNamespaces",
                              "TypeHoles",
+                             "OverloadedLists",
                              "EmptyCase",
                              "AutoDeriveTypeable"]
 
diff --git a/tests/driver/werror.stderr b/tests/driver/werror.stderr
index c8e789408..4bad5e6b4 100644
--- a/tests/driver/werror.stderr
+++ b/tests/driver/werror.stderr
@@ -1,10 +1,10 @@
 
-werror.hs:6:1:
-    Warning: Top-level binding with no type signature: main :: IO ()
+werror.hs:6:1: Warning:
+    Top-level binding with no type signature: main :: IO ()
 
-werror.hs:7:13:
-    Warning: This binding for `main' shadows the existing binding
-               defined at werror.hs:6:1
+werror.hs:7:13: Warning:
+    This binding for `main' shadows the existing binding
+      defined at werror.hs:6:1
 
 werror.hs:7:13: Warning: Defined but not used: `main'
 
@@ -12,17 +12,17 @@ werror.hs:8:1: Warning: Tab character
 
 werror.hs:10:1: Warning: Defined but not used: `f'
 
-werror.hs:10:1:
-    Warning: Top-level binding with no type signature:
-               f :: forall t a. [t] -> [a]
+werror.hs:10:1: Warning:
+    Top-level binding with no type signature:
+      f :: forall t t1. [t] -> [t1]
 
-werror.hs:10:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `f': f [] = ...
+werror.hs:10:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for `f': f [] = ...
 
-werror.hs:10:1:
-    Warning: Pattern match(es) are non-exhaustive
-             In an equation for `f': Patterns not matched: _ : _
+werror.hs:10:1: Warning:
+    Pattern match(es) are non-exhaustive
+    In an equation for `f': Patterns not matched: _ : _
 
 <no location info>: 
 Failing due to -Werror.
diff --git a/tests/ghci.debugger/scripts/break003.stderr b/tests/ghci.debugger/scripts/break003.stderr
index 03dc88bfd..fc7bb337d 100644
--- a/tests/ghci.debugger/scripts/break003.stderr
+++ b/tests/ghci.debugger/scripts/break003.stderr
@@ -1,4 +1,4 @@
 
 <interactive>:5:1:
-    No instance for (Show (t -> a)) arising from a use of `print'
+    No instance for (Show (t -> t1)) arising from a use of `print'
     In a stmt of an interactive GHCi command: print it
diff --git a/tests/ghci.debugger/scripts/break003.stdout b/tests/ghci.debugger/scripts/break003.stdout
index ed418836c..a48f74c4c 100644
--- a/tests/ghci.debugger/scripts/break003.stdout
+++ b/tests/ghci.debugger/scripts/break003.stdout
@@ -1,6 +1,6 @@
 Breakpoint 0 activated at ../Test3.hs:2:18-31
 Stopped at ../Test3.hs:2:18-31
-_result :: [a] = _
-f :: t -> a = _
+_result :: [t1] = _
+f :: t -> t1 = _
 x :: t = _
 xs :: [t] = [_]
diff --git a/tests/ghci.debugger/scripts/break005.stdout b/tests/ghci.debugger/scripts/break005.stdout
index 82fc68110..65eeb56cf 100644
--- a/tests/ghci.debugger/scripts/break005.stdout
+++ b/tests/ghci.debugger/scripts/break005.stdout
@@ -1,5 +1,5 @@
 Stopped at ../QSort.hs:(4,1)-(6,55)
-_result :: [a] = _
+_result :: [t] = _
 Stopped at ../QSort.hs:5:16-51
 _result :: [Integer] = _
 a :: Integer = 1
diff --git a/tests/ghci.debugger/scripts/break006.stderr b/tests/ghci.debugger/scripts/break006.stderr
index 45f6f8343..9543d675e 100644
--- a/tests/ghci.debugger/scripts/break006.stderr
+++ b/tests/ghci.debugger/scripts/break006.stderr
@@ -1,9 +1,9 @@
 
 <interactive>:6:1:
-    No instance for (Show a) arising from a use of `print'
-    Cannot resolve unknown runtime type `a'
+    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 :: a (bound at <interactive>:6:1)
+    Relevant bindings include it :: t1 (bound at <interactive>:6:1)
     Note: there are several potential instances:
       instance Show Double -- Defined in `GHC.Float'
       instance Show Float -- Defined in `GHC.Float'
@@ -13,10 +13,10 @@
     In a stmt of an interactive GHCi command: print it
 
 <interactive>:8:1:
-    No instance for (Show a) arising from a use of `print'
-    Cannot resolve unknown runtime type `a'
+    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 :: a (bound at <interactive>:8:1)
+    Relevant bindings include it :: t1 (bound at <interactive>:8:1)
     Note: there are several potential instances:
       instance Show Double -- Defined in `GHC.Float'
       instance Show Float -- Defined in `GHC.Float'
diff --git a/tests/ghci.debugger/scripts/break006.stdout b/tests/ghci.debugger/scripts/break006.stdout
index b78f4f365..7e5edbf9d 100644
--- a/tests/ghci.debugger/scripts/break006.stdout
+++ b/tests/ghci.debugger/scripts/break006.stdout
@@ -1,15 +1,15 @@
 Stopped at ../Test3.hs:(1,1)-(2,31)
-_result :: [a] = _
+_result :: [t1] = _
 Stopped at ../Test3.hs:2:18-31
-_result :: [a] = _
-f :: Integer -> a = _
+_result :: [t1] = _
+f :: Integer -> t1 = _
 x :: Integer = 1
 xs :: [Integer] = [2,3]
 xs :: [Integer] = [2,3]
 x :: Integer = 1
-f :: Integer -> a = _
-_result :: [a] = _
-y = (_t1::a)
+f :: Integer -> t1 = _
+_result :: [t1] = _
+y = (_t1::t1)
 y = 2
 xs :: [Integer] = [2,3]
 x :: Integer = 1
diff --git a/tests/ghci.debugger/scripts/break027.stdout b/tests/ghci.debugger/scripts/break027.stdout
index fdacda8d8..bac674b94 100644
--- a/tests/ghci.debugger/scripts/break027.stdout
+++ b/tests/ghci.debugger/scripts/break027.stdout
@@ -1,6 +1,6 @@
 Breakpoint 0 activated at ../QSort.hs:(4,1)-(6,55)
 Stopped at ../QSort.hs:(4,1)-(6,55)
-_result :: [a] = _
+_result :: [t] = _
 Stopped at ../QSort.hs:5:16-51
 _result :: [Integer] = _
 a :: Integer = 3
diff --git a/tests/ghci.debugger/scripts/hist001.stdout b/tests/ghci.debugger/scripts/hist001.stdout
index 74cb48399..0b58b8fcb 100644
--- a/tests/ghci.debugger/scripts/hist001.stdout
+++ b/tests/ghci.debugger/scripts/hist001.stdout
@@ -12,20 +12,20 @@ _result :: [a] = _
 -9  : mymap (../Test3.hs:(1,1)-(2,31))
 <end of history>
 Logged breakpoint at ../Test3.hs:(1,1)-(2,31)
-_result :: [a]
-_result :: [a] = _
+_result :: [t1]
+_result :: [t1] = _
 Logged breakpoint at ../Test3.hs:2:22-31
-_result :: [a]
-f :: t -> a
+_result :: [t1]
+f :: t -> t1
 xs :: [t]
 xs :: [t] = []
-f :: t -> a = _
-_result :: [a] = _
+f :: t -> t1 = _
+_result :: [t1] = _
 *** Ignoring breakpoint
 _result = []
 Logged breakpoint at ../Test3.hs:2:18-20
-_result :: a
-f :: Integer -> a
+_result :: t1
+f :: Integer -> t1
 x :: Integer
 Logged breakpoint at ../Test3.hs:2:22-31
-_result :: [a]
+_result :: [t1]
diff --git a/tests/rename/should_fail/T5892a.stderr b/tests/rename/should_fail/T5892a.stderr
index 9eecad61b..1047599b8 100644
--- a/tests/rename/should_fail/T5892a.stderr
+++ b/tests/rename/should_fail/T5892a.stderr
@@ -1,10 +1,10 @@
-
-T5892a.hs:12:8: Warning:
-    Fields of `Version' not initialised: Data.Version.versionTags
-    In the expression: Version {..}
-    In the expression: let versionBranch = [] in Version {..}
-    In an equation for `foo':
-        foo (Version {..}) = let versionBranch = [] in Version {..}
-
-<no location info>: 
-Failing due to -Werror.
+
+T5892a.hs:12:8: Warning:
+    Fields of `Version' not initialised: Data.Version.versionTags
+    In the expression: Version {..}
+    In the expression: let versionBranch = [] in Version {..}
+    In an equation for `foo':
+        foo (Version {..}) = let versionBranch = ... in Version {..}
+
+<no location info>: 
+Failing due to -Werror.
diff --git a/tests/th/TH_exn1.stderr b/tests/th/TH_exn1.stderr
index f54448524..63548613d 100644
--- a/tests/th/TH_exn1.stderr
+++ b/tests/th/TH_exn1.stderr
@@ -3,4 +3,4 @@ TH_exn1.hs:1:1:
     Exception when trying to run compile-time code:
       TH_exn1.hs:(9,4)-(10,23): Non-exhaustive patterns in case
 
-      Code: case reverse "no" of { [] -> return (GHC.Types.[]) }
+    Code: case reverse "no" of { [] -> return [] }
diff --git a/tests/typecheck/should_fail/T2534.stderr b/tests/typecheck/should_fail/T2534.stderr
index 8943b979a..02ad7821f 100644
--- a/tests/typecheck/should_fail/T2534.stderr
+++ b/tests/typecheck/should_fail/T2534.stderr
@@ -1,6 +1,6 @@
 
 T2534.hs:3:19:
-    Couldn't match expected type `a -> a -> b' with actual type `[a0]'
+    Couldn't match expected type `a -> a -> b' with actual type `[t0]'
     Relevant bindings include
       foo :: a -> a -> b (bound at T2534.hs:3:1)
     In the second argument of `foldr', namely `[]'
diff --git a/tests/typecheck/should_fail/T5858.stderr b/tests/typecheck/should_fail/T5858.stderr
index 0ecd766ec..437b5baca 100644
--- a/tests/typecheck/should_fail/T5858.stderr
+++ b/tests/typecheck/should_fail/T5858.stderr
@@ -1,10 +1,10 @@
-
-T5858.hs:11:7:
-    No instance for (InferOverloaded ([a0], [a1]))
-      arising from a use of `infer'
-    The type variables `a0', `a1' are ambiguous
-    Note: there is a potential instance available:
-      instance t1 ~ String => InferOverloaded (t1, t1)
-        -- Defined at T5858.hs:8:10
-    In the expression: infer ([], [])
-    In an equation for `foo': foo = infer ([], [])
+
+T5858.hs:11:7:
+    No instance for (InferOverloaded ([t0], [t1]))
+      arising from a use of `infer'
+    The type variables `t0', `t1' are ambiguous
+    Note: there is a potential instance available:
+      instance t1 ~ String => InferOverloaded (t1, t1)
+        -- Defined at T5858.hs:8:10
+    In the expression: infer ([], [])
+    In an equation for `foo': foo = infer ([], [])
diff --git a/tests/typecheck/should_fail/tcfail001.stderr b/tests/typecheck/should_fail/tcfail001.stderr
index 85b6788a7..8734ee32b 100644
--- a/tests/typecheck/should_fail/tcfail001.stderr
+++ b/tests/typecheck/should_fail/tcfail001.stderr
@@ -1,6 +1,6 @@
 
 tcfail001.hs:9:2:
-    Couldn't match expected type `[t0] -> [a0]' with actual type `[a]'
+    Couldn't match expected type `[t0] -> [t1]' with actual type `[a]'
     Relevant bindings include op :: [a] (bound at tcfail001.hs:9:2)
     The equation(s) for `op' have one argument,
     but its type `[a]' has none
diff --git a/tests/typecheck/should_fail/tcfail012.stderr b/tests/typecheck/should_fail/tcfail012.stderr
index 7fe9b18d4..7d99a18a3 100644
--- a/tests/typecheck/should_fail/tcfail012.stderr
+++ b/tests/typecheck/should_fail/tcfail012.stderr
@@ -1,5 +1,5 @@
 
 tcfail012.hs:3:8:
-    Couldn't match expected type `Bool' with actual type `[a0]'
+    Couldn't match expected type `Bool' with actual type `[t0]'
     In the expression: []
     In a pattern binding: True = []
-- 
GitLab


From 9426754eaf68b854b7ad4dd30411df3e4207e982 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 14 Feb 2013 14:52:43 +0000
Subject: [PATCH 170/223] Add tests for OverloadedLists

---
 tests/overloadedlists/Makefile                |  3 ++
 tests/overloadedlists/should_fail/Makefile    |  3 ++
 tests/overloadedlists/should_fail/all.T       |  6 ++++
 .../should_fail/overloadedlistsfail01.hs      |  5 +++
 .../should_fail/overloadedlistsfail01.stderr  | 36 +++++++++++++++++++
 .../should_fail/overloadedlistsfail02.hs      |  8 +++++
 .../should_fail/overloadedlistsfail02.stderr  | 13 +++++++
 .../should_fail/overloadedlistsfail03.hs      |  3 ++
 .../should_fail/overloadedlistsfail03.stderr  |  9 +++++
 .../should_fail/overloadedlistsfail04.hs      |  3 ++
 .../should_fail/overloadedlistsfail04.stderr  | 12 +++++++
 .../should_fail/overloadedlistsfail05.hs      |  3 ++
 .../should_fail/overloadedlistsfail05.stderr  |  7 ++++
 .../should_fail/overloadedlistsfail06.hs      |  4 +++
 .../should_fail/overloadedlistsfail06.stderr  |  7 ++++
 tests/overloadedlists/should_run/Makefile     |  3 ++
 tests/overloadedlists/should_run/all.T        |  5 +++
 .../should_run/overloadedlistsrun01.hs        |  6 ++++
 .../should_run/overloadedlistsrun01.stdout    |  4 +++
 .../should_run/overloadedlistsrun02.hs        | 13 +++++++
 .../should_run/overloadedlistsrun02.stdout    |  3 ++
 .../should_run/overloadedlistsrun03.hs        | 18 ++++++++++
 .../should_run/overloadedlistsrun03.stdout    |  5 +++
 .../should_run/overloadedlistsrun04.hs        | 28 +++++++++++++++
 .../should_run/overloadedlistsrun04.stdout    |  7 ++++
 .../should_run/overloadedlistsrun05.hs        | 16 +++++++++
 .../should_run/overloadedlistsrun05.stdout    |  6 ++++
 27 files changed, 236 insertions(+)
 create mode 100644 tests/overloadedlists/Makefile
 create mode 100644 tests/overloadedlists/should_fail/Makefile
 create mode 100644 tests/overloadedlists/should_fail/all.T
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail01.hs
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail01.stderr
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail02.hs
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail02.stderr
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail03.hs
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail03.stderr
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail04.hs
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail04.stderr
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail05.hs
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail05.stderr
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail06.hs
 create mode 100644 tests/overloadedlists/should_fail/overloadedlistsfail06.stderr
 create mode 100644 tests/overloadedlists/should_run/Makefile
 create mode 100644 tests/overloadedlists/should_run/all.T
 create mode 100644 tests/overloadedlists/should_run/overloadedlistsrun01.hs
 create mode 100644 tests/overloadedlists/should_run/overloadedlistsrun01.stdout
 create mode 100644 tests/overloadedlists/should_run/overloadedlistsrun02.hs
 create mode 100644 tests/overloadedlists/should_run/overloadedlistsrun02.stdout
 create mode 100644 tests/overloadedlists/should_run/overloadedlistsrun03.hs
 create mode 100644 tests/overloadedlists/should_run/overloadedlistsrun03.stdout
 create mode 100644 tests/overloadedlists/should_run/overloadedlistsrun04.hs
 create mode 100644 tests/overloadedlists/should_run/overloadedlistsrun04.stdout
 create mode 100644 tests/overloadedlists/should_run/overloadedlistsrun05.hs
 create mode 100644 tests/overloadedlists/should_run/overloadedlistsrun05.stdout

diff --git a/tests/overloadedlists/Makefile b/tests/overloadedlists/Makefile
new file mode 100644
index 000000000..9a36a1c5f
--- /dev/null
+++ b/tests/overloadedlists/Makefile
@@ -0,0 +1,3 @@
+TOP=../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
diff --git a/tests/overloadedlists/should_fail/Makefile b/tests/overloadedlists/should_fail/Makefile
new file mode 100644
index 000000000..9101fbd40
--- /dev/null
+++ b/tests/overloadedlists/should_fail/Makefile
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
diff --git a/tests/overloadedlists/should_fail/all.T b/tests/overloadedlists/should_fail/all.T
new file mode 100644
index 000000000..771035d07
--- /dev/null
+++ b/tests/overloadedlists/should_fail/all.T
@@ -0,0 +1,6 @@
+test('overloadedlistsfail01', normal, compile_fail, [''])
+test('overloadedlistsfail02', normal, compile_fail, [''])
+test('overloadedlistsfail03', normal, compile_fail, [''])
+test('overloadedlistsfail04', normal, compile_fail, [''])
+test('overloadedlistsfail05', normal, compile_fail, [''])
+test('overloadedlistsfail06', normal, compile_fail, [''])
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail01.hs b/tests/overloadedlists/should_fail/overloadedlistsfail01.hs
new file mode 100644
index 000000000..ec49accf1
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail01.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE OverloadedLists #-}
+
+-- This will fail because there is no type defaulting implemented as of yet.
+
+main = print [1]
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr
new file mode 100644
index 000000000..a08985f88
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr
@@ -0,0 +1,36 @@
+
+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 Show Double -- Defined in `GHC.Float'
+      instance Show Float -- Defined in `GHC.Float'
+      instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
+        -- Defined in `GHC.Real'
+      ...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 is a potential instance available:
+      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 Double -- Defined in `GHC.Float'
+      instance Num Float -- Defined in `GHC.Float'
+      instance Integral a => Num (GHC.Real.Ratio a)
+        -- Defined in `GHC.Real'
+      ...plus three others
+    In the expression: 1
+    In the first argument of `print', namely `[1]'
+    In the expression: print [1]
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail02.hs b/tests/overloadedlists/should_fail/overloadedlistsfail02.hs
new file mode 100644
index 000000000..54ca2db9f
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail02.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE OverloadedLists #-}
+
+data Foo = Foo
+
+test :: Foo
+test = [7]
+
+main = return ()
\ No newline at end of file
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr
new file mode 100644
index 000000000..49e6b9ee9
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr
@@ -0,0 +1,13 @@
+
+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]
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail03.hs b/tests/overloadedlists/should_fail/overloadedlistsfail03.hs
new file mode 100644
index 000000000..d1981846d
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail03.hs
@@ -0,0 +1,3 @@
+{-# LANGUAGE OverloadedLists #-}
+
+main = print (length ['a',"b"])
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail03.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail03.stderr
new file mode 100644
index 000000000..099d79f23
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail03.stderr
@@ -0,0 +1,9 @@
+
+overloadedlistsfail03.hs:3:27:
+    Couldn't match expected type `Char' with actual type `[Char]'
+    In the expression: "b"
+    In the first argument of `length', namely `['a', "b"]'
+    In the first argument of `print', namely `(length ['a', "b"])'
+
+
+
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail04.hs b/tests/overloadedlists/should_fail/overloadedlistsfail04.hs
new file mode 100644
index 000000000..811c0511f
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail04.hs
@@ -0,0 +1,3 @@
+{-# LANGUAGE OverloadedLists #-}
+
+main = print (["a".."b"] :: [String])
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail04.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail04.stderr
new file mode 100644
index 000000000..cfa051997
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail04.stderr
@@ -0,0 +1,12 @@
+
+overloadedlistsfail04.hs:3:15:
+    No instance for (Enum [Char])
+      arising from the arithmetic sequence `"a" .. "b"'
+    In the first argument of `print', namely
+      `(["a" .. "b"] :: [String])'
+    In the expression: print (["a" .. "b"] :: [String])
+    In an equation for `main': main = print (["a" .. "b"] :: [String])
+
+
+
+
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail05.hs b/tests/overloadedlists/should_fail/overloadedlistsfail05.hs
new file mode 100644
index 000000000..3601c6e2f
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail05.hs
@@ -0,0 +1,3 @@
+{-# LANGUAGE OverloadedLists #-}
+
+main = print (length ['a'..(10 :: Int)])
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail05.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail05.stderr
new file mode 100644
index 000000000..6e4d3dbd0
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail05.stderr
@@ -0,0 +1,7 @@
+
+overloadedlistsfail05.hs:3:29:
+    Couldn't match expected type `Char' with actual type `Int'
+    In the expression: (10 :: Int)
+    In the first argument of `length', namely `['a' .. (10 :: Int)]'
+    In the first argument of `print', namely
+      `(length ['a' .. (10 :: Int)])'
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail06.hs b/tests/overloadedlists/should_fail/overloadedlistsfail06.hs
new file mode 100644
index 000000000..c8cf5aea2
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail06.hs
@@ -0,0 +1,4 @@
+{-# LANGUAGE OverloadedLists, RebindableSyntax #-}
+
+f [] = []
+f x = x
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail06.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail06.stderr
new file mode 100644
index 000000000..2cd0c3fa1
--- /dev/null
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail06.stderr
@@ -0,0 +1,7 @@
+
+overloadedlistsfail06.hs:3:3:
+    Not in scope: `toList'
+
+overloadedlistsfail06.hs:3:8:
+    Not in scope: `fromListN'
+
diff --git a/tests/overloadedlists/should_run/Makefile b/tests/overloadedlists/should_run/Makefile
new file mode 100644
index 000000000..9101fbd40
--- /dev/null
+++ b/tests/overloadedlists/should_run/Makefile
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
diff --git a/tests/overloadedlists/should_run/all.T b/tests/overloadedlists/should_run/all.T
new file mode 100644
index 000000000..be654e3ca
--- /dev/null
+++ b/tests/overloadedlists/should_run/all.T
@@ -0,0 +1,5 @@
+test('overloadedlistsrun01', normal, compile_and_run, [''])
+test('overloadedlistsrun02', normal, compile_and_run, [''])
+test('overloadedlistsrun03', normal, compile_and_run, [''])
+test('overloadedlistsrun04', normal, compile_and_run, [''])
+test('overloadedlistsrun05', normal, compile_and_run, [''])
diff --git a/tests/overloadedlists/should_run/overloadedlistsrun01.hs b/tests/overloadedlists/should_run/overloadedlistsrun01.hs
new file mode 100644
index 000000000..00852b92c
--- /dev/null
+++ b/tests/overloadedlists/should_run/overloadedlistsrun01.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE OverloadedLists #-}
+
+main = do print ([] :: [Int])
+          print ([1,2,3] :: [Int])
+          print ((take 10 [1..]) :: [Int])
+          print (['a'..'e'] :: [Char])
diff --git a/tests/overloadedlists/should_run/overloadedlistsrun01.stdout b/tests/overloadedlists/should_run/overloadedlistsrun01.stdout
new file mode 100644
index 000000000..4a75bae7d
--- /dev/null
+++ b/tests/overloadedlists/should_run/overloadedlistsrun01.stdout
@@ -0,0 +1,4 @@
+[]
+[1,2,3]
+[1,2,3,4,5,6,7,8,9,10]
+"abcde"
diff --git a/tests/overloadedlists/should_run/overloadedlistsrun02.hs b/tests/overloadedlists/should_run/overloadedlistsrun02.hs
new file mode 100644
index 000000000..8567db356
--- /dev/null
+++ b/tests/overloadedlists/should_run/overloadedlistsrun02.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE OverloadedLists, TypeFamilies #-}
+
+import qualified Data.Set as S
+import GHC.Exts
+
+main = do print ([] :: (S.Set Int))
+          print (['a','b','c'] :: (S.Set Char))
+          print (['a','c'..'g'] :: (S.Set Char))
+          
+instance Ord a => IsList (S.Set a) where
+ type (Item (S.Set a)) = a
+ fromList = S.fromList
+ toList = S.toList
diff --git a/tests/overloadedlists/should_run/overloadedlistsrun02.stdout b/tests/overloadedlists/should_run/overloadedlistsrun02.stdout
new file mode 100644
index 000000000..08fffbfc1
--- /dev/null
+++ b/tests/overloadedlists/should_run/overloadedlistsrun02.stdout
@@ -0,0 +1,3 @@
+fromList []
+fromList "abc"
+fromList "aceg"
diff --git a/tests/overloadedlists/should_run/overloadedlistsrun03.hs b/tests/overloadedlists/should_run/overloadedlistsrun03.hs
new file mode 100644
index 000000000..7d5b7d945
--- /dev/null
+++ b/tests/overloadedlists/should_run/overloadedlistsrun03.hs
@@ -0,0 +1,18 @@
+{-# LANGUAGE OverloadedLists, TypeFamilies #-}
+
+import GHC.Exts
+
+-- This nonsensical instance is used to test if fromListN is used properly in
+-- desugaring of explicit lists.
+
+instance IsList Int where
+ type Item Int = Int
+ fromList _ = 0
+ toList _ = []
+ fromListN n _ = n
+ 
+main = do print ([] :: Int)
+          print ([1,2,3,4,5] :: Int)
+          print ([1..3] :: Int)
+          print ([7] :: Int)
+          print ([1,3..] :: Int)
diff --git a/tests/overloadedlists/should_run/overloadedlistsrun03.stdout b/tests/overloadedlists/should_run/overloadedlistsrun03.stdout
new file mode 100644
index 000000000..ff973f8f1
--- /dev/null
+++ b/tests/overloadedlists/should_run/overloadedlistsrun03.stdout
@@ -0,0 +1,5 @@
+0
+5
+0
+1
+0
diff --git a/tests/overloadedlists/should_run/overloadedlistsrun04.hs b/tests/overloadedlists/should_run/overloadedlistsrun04.hs
new file mode 100644
index 000000000..478d8d2c2
--- /dev/null
+++ b/tests/overloadedlists/should_run/overloadedlistsrun04.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE OverloadedLists, TypeFamilies #-}
+
+import qualified Data.Set as S
+import GHC.Exts
+
+main = do putStrLn (f [])       
+          putStrLn (f [1,2])    
+          putStrLn (f [2,0])    
+          putStrLn (f [3,2])     
+          putStrLn (f [2,7])
+          putStrLn (f [2,2])
+          putStrLn (f [1..7])
+
+
+f :: S.Set Int -> String
+f [] = "empty"
+f [_] = "one element"
+f [2,_] = "two elements, the smaller one is 2"
+f [_,2] = "two elements, the bigger one is 2"
+f _ = "else"
+
+          
+instance Ord a => IsList (S.Set a) where
+ type (Item (S.Set a)) = a
+ fromList = S.fromList
+ toList = S.toList
+          
+
diff --git a/tests/overloadedlists/should_run/overloadedlistsrun04.stdout b/tests/overloadedlists/should_run/overloadedlistsrun04.stdout
new file mode 100644
index 000000000..0f50db555
--- /dev/null
+++ b/tests/overloadedlists/should_run/overloadedlistsrun04.stdout
@@ -0,0 +1,7 @@
+empty
+two elements, the bigger one is 2
+two elements, the bigger one is 2
+two elements, the smaller one is 2
+two elements, the smaller one is 2
+one element
+else
diff --git a/tests/overloadedlists/should_run/overloadedlistsrun05.hs b/tests/overloadedlists/should_run/overloadedlistsrun05.hs
new file mode 100644
index 000000000..18d8cc1d0
--- /dev/null
+++ b/tests/overloadedlists/should_run/overloadedlistsrun05.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE OverloadedLists, TypeFamilies, RebindableSyntax #-}
+
+import Prelude
+import Data.List
+
+main = do print []       
+          print [0,3..20]    
+          print [3]     
+          print [2..7]
+          print [20,2]
+          print [1,2,37]
+
+fromListN _ = length 
+fromList = length
+          
+
diff --git a/tests/overloadedlists/should_run/overloadedlistsrun05.stdout b/tests/overloadedlists/should_run/overloadedlistsrun05.stdout
new file mode 100644
index 000000000..e0777cd8e
--- /dev/null
+++ b/tests/overloadedlists/should_run/overloadedlistsrun05.stdout
@@ -0,0 +1,6 @@
+0
+7
+1
+6
+2
+3
-- 
GitLab


From 5a58fc0f8c3ebae024191a258cb6ecd47ada8e77 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 14 Feb 2013 14:04:42 +0000
Subject: [PATCH 171/223] Improve a comment

---
 tests/Makefile | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/tests/Makefile b/tests/Makefile
index d0fc4ee65..9234bcc68 100644
--- a/tests/Makefile
+++ b/tests/Makefile
@@ -3,7 +3,8 @@ include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk
 
 # The libraries that we actually know about. We don't want to test
-# extralibs that are in our tree but which we haven't built.
+# extralibs that are in our tree but which we haven't built, and
+# we don't want to test unix on Windows or Win32 on non-Windows.
 LIBRARIES := $(shell '$(GHC_PKG)' list --simple-output --names-only)
 
 ifeq "$(findstring base,$(LIBRARIES))" ""
-- 
GitLab


From 6956cc199b50fb760496c2ee7c351719a4277755 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Thu, 14 Feb 2013 14:48:09 +0000
Subject: [PATCH 172/223] Remove uses of compose(s) in tests, and change how
 composition is handled

The driver now also supports nested lists of setup functions
---
 driver/testlib.py                    | 23 +++++------
 tests/array/should_run/all.T         |  8 ++--
 tests/codeGen/should_run/all.T       |  8 ++--
 tests/concurrent/should_run/all.T    | 37 +++++++++---------
 tests/deriving/should_run/all.T      |  2 +-
 tests/ffi/should_run/all.T           | 17 +++++----
 tests/ghci.debugger/scripts/all.T    |  6 +--
 tests/numeric/should_run/all.T       |  4 +-
 tests/profiling/should_compile/all.T |  6 +--
 tests/profiling/should_run/all.T     |  8 ++--
 tests/rts/all.T                      | 57 +++++++++++++---------------
 tests/simplCore/should_run/all.T     |  4 +-
 tests/typecheck/should_run/all.T     | 24 ++++++++----
 13 files changed, 104 insertions(+), 100 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index de8ab9012..355392656 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -62,7 +62,7 @@ def setLocalTestOpts(opts):
 # for the following tests.
 def setTestOpts( f ):
     global thisdir_settings
-    thisdir_settings = compose(thisdir_settings, f)
+    thisdir_settings = [thisdir_settings, f]
 
 # -----------------------------------------------------------------------------
 # Canned setup functions for common cases.  eg. for a test you might say
@@ -475,15 +475,16 @@ def two_normalisers(f, g):
 # ----
 # Function for composing two opt-fns together
 
-def composes( fs ):
-    return reduce(lambda f, g: compose(f, g), fs)
+def executeSetups(fs, name, opts):
+    if type(fs) is types.ListType:
+        # If we have a list of setups, then execute each one
+        map (lambda f : executeSetups(f, name, opts), fs)
+    else:
+        # fs is a single function, so just apply it
+        fs(name, opts)
 
 def compose( f, g ):
-    return lambda name, opts, f=f, g=g: _compose(name, opts, f, g)
-
-def _compose( name, opts, f, g ):
-    f(name, opts)
-    g(name, opts)
+    return [f, g]
 
 # -----------------------------------------------------------------------------
 # The current directory of tests
@@ -539,11 +540,7 @@ def test (name, setup, func, args):
     # them, all tests will see the modified version!
     myTestOpts = copy.deepcopy(default_testopts)
 
-    if type(setup) is types.ListType:
-       setup = composes(setup)
-
-    setup = compose(thisdir_settings, setup)
-    setup(name, myTestOpts)
+    executeSetups([thisdir_settings, setup], name, myTestOpts)
 
     thisTest = lambda : runTest(myTestOpts, name, func, args)
     if myTestOpts.alone:
diff --git a/tests/array/should_run/all.T b/tests/array/should_run/all.T
index a0cfc6be3..6b5500700 100644
--- a/tests/array/should_run/all.T
+++ b/tests/array/should_run/all.T
@@ -6,12 +6,12 @@
 
 test('arr001', when(fast(), skip), compile_and_run, [''])
 test('arr002', when(fast(), skip), compile_and_run, [''])
-test('arr003', compose(when(fast(), skip),exit_code(1)), compile_and_run, [''])
-test('arr004', compose(when(fast(), skip),exit_code(1)), compile_and_run, [''])
+test('arr003', [when(fast(), skip),exit_code(1)], compile_and_run, [''])
+test('arr004', [when(fast(), skip),exit_code(1)], compile_and_run, [''])
 test('arr005', when(fast(), skip), compile_and_run, [''])
 test('arr006', when(fast(), skip), compile_and_run, [''])
-test('arr007', compose(when(fast(), skip),exit_code(1)), compile_and_run, [''])
-test('arr008', compose(when(fast(), skip),exit_code(1)), compile_and_run, [''])
+test('arr007', [when(fast(), skip),exit_code(1)], compile_and_run, [''])
+test('arr008', [when(fast(), skip),exit_code(1)], compile_and_run, [''])
 test('arr009', when(fast(), skip), compile_and_run, [''])
 test('arr010', when(fast(), skip), compile_and_run, [''])
 test('arr011', when(fast(), skip), compile_and_run, [''])
diff --git a/tests/codeGen/should_run/all.T b/tests/codeGen/should_run/all.T
index d470d7b4a..958d33864 100644
--- a/tests/codeGen/should_run/all.T
+++ b/tests/codeGen/should_run/all.T
@@ -24,8 +24,9 @@ test('cgrun020', normal, compile_and_run, [''])
 test('cgrun021', normal, compile_and_run, [''])
 test('cgrun022', normal, compile_and_run, [''])
 test('cgrun024', normal, compile_and_run, [''])
-test('cgrun025', compose(reqlib('regex-compat'), compose(extra_run_opts('cg025.hs'),exit_code(1))),
-                      compile_and_run, ['-package regex-compat'])
+test('cgrun025',
+     [reqlib('regex-compat'), extra_run_opts('cg025.hs'), exit_code(1)],
+     compile_and_run, ['-package regex-compat'])
 test('cgrun026', only_compiler_types(['ghc']), compile_and_run, [''])
 test('cgrun027', normal, compile_and_run, [''])
 test('cgrun028', normal, compile_and_run, [''])
@@ -48,7 +49,8 @@ test('cgrun048', normal, compile_and_run, [''])
 test('cgrun049', normal, compile_and_run, ['-funbox-strict-fields'])
 test('cgrun050', normal, compile_and_run, [''])
 # Doesn't work with External Core due to datatype declaration with no constructors
-test('cgrun051', (compose (expect_fail_for(['extcore','optextcore']),exit_code(1))), compile_and_run, [''])
+test('cgrun051', [expect_fail_for(['extcore','optextcore']), exit_code(1)],
+     compile_and_run, [''])
 test('cgrun052', only_ways(['optasm']), compile_and_run, ['-funbox-strict-fields'])
 test('cgrun053', normal, compile_and_run, [''])
 test('cgrun054', normal, compile_and_run, [''])
diff --git a/tests/concurrent/should_run/all.T b/tests/concurrent/should_run/all.T
index 0a0778b6b..bb2bcd383 100644
--- a/tests/concurrent/should_run/all.T
+++ b/tests/concurrent/should_run/all.T
@@ -22,8 +22,8 @@ test('conc072', only_ways(['threaded2']), compile_and_run, [''])
 test('conc073', normal, compile_and_run, [''])
 
 # vector code must get inlined to become non-allocating
-test('T367', composes([reqlib('vector'), timeout_multiplier(0.001)]), compile_and_run, ['-O2 -fno-omit-yields'])
-test('T367_letnoescape', composes([timeout_multiplier(0.001)]), compile_and_run, ['-fno-omit-yields'])
+test('T367', [reqlib('vector'), timeout_multiplier(0.001)], compile_and_run, ['-O2 -fno-omit-yields'])
+test('T367_letnoescape', [timeout_multiplier(0.001)], compile_and_run, ['-fno-omit-yields'])
 
 test('T1980', normal, compile_and_run, [''])
 test('T2910', normal, compile_and_run, [''])
@@ -89,11 +89,11 @@ test('conc002', normal, compile_and_run, [''])
 # Omit GHCi way - it blows up to 0.5G.  Something to do with the threaded RTS?
 test('conc004', omit_ways(['ghci']), compile_and_run, [''])
 
-test('conc007', compose(only_compiler_types(['ghc']),
-			extra_run_opts('+RTS -H128M -RTS')),
+test('conc007', [only_compiler_types(['ghc']),
+                 extra_run_opts('+RTS -H128M -RTS')],
 		compile_and_run, [''])
 test('conc008', only_compiler_types(['ghc']), compile_and_run, [''])
-test('conc009', compose(only_compiler_types(['ghc']), exit_code(1)),
+test('conc009', [only_compiler_types(['ghc']), exit_code(1)],
 		compile_and_run, [''])
 test('conc010', only_compiler_types(['ghc']), compile_and_run, [''])
 
@@ -110,8 +110,8 @@ test('conc016', [ omit_ways(['threaded2']), # see comment in conc016.hs
 test('conc017', only_compiler_types(['ghc']), compile_and_run, [''])
 test('conc017a', only_compiler_types(['ghc']), compile_and_run, [''])
 test('conc018', only_compiler_types(['ghc']), compile_and_run, [''])
-test('conc019', compose(only_compiler_types(['ghc']),
-			extra_run_opts('+RTS -K16m -RTS')),
+test('conc019', [only_compiler_types(['ghc']),
+                 extra_run_opts('+RTS -K16m -RTS')],
 		compile_and_run, [''])
 test('conc020', only_compiler_types(['ghc']), compile_and_run, [''])
 test('conc021', [ omit_ways(['ghci']), exit_code(1) ], compile_and_run, [''])
@@ -127,18 +127,18 @@ if config.platform == 'i386-unknown-mingw32':
 else:
    conc023_ways = normal
 
-test('conc023', composes([when(fast(), skip),
-                          only_compiler_types(['ghc']),
-                          reqlib('random'),
-                          conc023_ways]), compile_and_run, [''])
+test('conc023', [when(fast(), skip),
+                 only_compiler_types(['ghc']),
+                 reqlib('random'),
+                 conc023_ways], compile_and_run, [''])
 
 test('conc024', only_compiler_types(['ghc']), compile_and_run, [''])
 test('conc025', normal, compile_and_run, [''])
 test('conc026', only_compiler_types(['ghc']), compile_and_run, [''])
 test('conc028', normal, compile_and_run, [''])
 test('conc029', normal, compile_and_run, [''])
-test('conc030', compose(only_compiler_types(['ghc']),
-			extra_run_opts('+RTS -K4M -RTS')),
+test('conc030',
+     [only_compiler_types(['ghc']), extra_run_opts('+RTS -K4M -RTS')],
 		compile_and_run, [''])
 
 test('conc031', normal, compile_and_run, [''])
@@ -147,9 +147,9 @@ test('conc032', only_compiler_types(['ghc']), compile_and_run, [''])
 test('conc033', normal, compile_and_run, [''])
 
 # Omit for GHCi, because it just sits there waiting for you to press ^C
-test('conc034', compose(only_compiler_types(['ghc']),
-			compose(omit_ways(['ghci']), 
-			extra_run_opts('+RTS -C0 -RTS'))),
+test('conc034', [only_compiler_types(['ghc']),
+                 omit_ways(['ghci']), 
+                 extra_run_opts('+RTS -C0 -RTS')],
 		compile_and_run, [''])
 
 test('conc035', only_compiler_types(['ghc']), compile_and_run, [''])
@@ -187,9 +187,8 @@ test('conc038', only_ways(['threaded1','threaded2']), compile_and_run, [''])
 test('conc039', omit_ways(['ghci','threaded1','threaded2','profthreaded']), compile_and_run, [''])
 
 # Omit for GHCi, uses foreign export
-test('conc040', compose(only_compiler_types(['ghc']),
-			compose(exit_code(1),
-			omit_ways(['ghci']))),
+test('conc040',
+     [only_compiler_types(['ghc']), exit_code(1), omit_ways(['ghci'])],
 		compile_and_run, [''])
 
 # STM-related tests.
diff --git a/tests/deriving/should_run/all.T b/tests/deriving/should_run/all.T
index eeda9aa72..af4bd720c 100644
--- a/tests/deriving/should_run/all.T
+++ b/tests/deriving/should_run/all.T
@@ -19,7 +19,7 @@ test('drvrun013', when(fast(), skip), compile_and_run, [''])
 test('drvrun014', when(fast(), skip), compile_and_run, [''])
 test('drvrun015', when(fast(), skip), compile_and_run, [''])
 test('drvrun016', when(fast(), skip), compile_and_run, ['-funbox-strict-fields'])
-test('drvrun017', compose(when(fast(), skip), only_compiler_types(['ghc'])), compile_and_run, [''])
+test('drvrun017', [when(fast(), skip), only_compiler_types(['ghc'])], compile_and_run, [''])
 test('drvrun018', when(fast(), skip), compile_and_run, [''])
 test('drvrun019', normal, compile_and_run, [''])
 test('drvrun020', normal, compile_and_run, [''])
diff --git a/tests/ffi/should_run/all.T b/tests/ffi/should_run/all.T
index 01c60112b..89bb0fb83 100644
--- a/tests/ffi/should_run/all.T
+++ b/tests/ffi/should_run/all.T
@@ -5,8 +5,8 @@
 #	expected process return value, if not zero
 
 # Doesn't work with External Core due to __labels
-test('fed001', compose(only_compiler_types(['ghc']),
-			expect_fail_for(['extcore','optextcore'])),
+test('fed001', [only_compiler_types(['ghc']),
+                expect_fail_for(['extcore','optextcore'])],
 		compile_and_run, [''])
 
 # Omit GHCi for these two, as they use foreign export
@@ -48,13 +48,14 @@ test('ffi006', expect_fail_for(['extcore','optextcore']), compile_and_run, [''])
 # Sometimes we end up with the wrong exit code, or get an extra
 # 'interrupted' message from the GHCi thread shutting down.
 
-test('ffi007', compose( omit_ways(['ghci']),
-		        expect_fail_for(['extcore','optextcore']) ), 
+test('ffi007',
+     [omit_ways(['ghci']), expect_fail_for(['extcore','optextcore'])], 
 	       compile_and_run, [''])
 
-test('ffi008', compose(expect_fail_for(['extcore','optextcore']), 
-		       compose(exit_code(1),
-			       omit_ways(['ghci']))), 
+test('ffi008',
+     [expect_fail_for(['extcore','optextcore']),
+      exit_code(1),
+      omit_ways(['ghci'])],
 	       compile_and_run, [''])
 
 # On i386, we need -msse2 to get reliable floating point results
@@ -145,7 +146,7 @@ test('fptr01', [ omit_ways(['ghci']), extra_clean(['fptr01_c.o']) ],
                compile_and_run, ['fptr01_c.c'])
 test('fptr02', normal, compile_and_run, [''])
 
-test('fptrfail01', [ compose(omit_ways(['ghci']), exit_code(1)),
+test('fptrfail01', [ omit_ways(['ghci']), exit_code(1),
                      extra_clean(['fptrfail01_c.o']) ],
                    compile_and_run, ['fptrfail01_c.c'])
 
diff --git a/tests/ghci.debugger/scripts/all.T b/tests/ghci.debugger/scripts/all.T
index e2d545876..c5ea2fb63 100644
--- a/tests/ghci.debugger/scripts/all.T
+++ b/tests/ghci.debugger/scripts/all.T
@@ -1,6 +1,6 @@
-setTestOpts(composes([extra_run_opts('-ignore-dot-ghci'),
-                     when(compiler_profiled(), skip),
-                     normalise_slashes]))
+setTestOpts([extra_run_opts('-ignore-dot-ghci'),
+             when(compiler_profiled(), skip),
+             normalise_slashes])
 
 test('print001', normal, ghci_script, ['print001.script'])
 test('print002', normal, ghci_script, ['print002.script'])
diff --git a/tests/numeric/should_run/all.T b/tests/numeric/should_run/all.T
index d2f017a1f..70bd59150 100644
--- a/tests/numeric/should_run/all.T
+++ b/tests/numeric/should_run/all.T
@@ -29,7 +29,7 @@ test('arith011', normal, compile_and_run, [''])
 
 test('arith012', ways, compile_and_run, [opts])
 
-test('arith013', compose(normal,only_compiler_types(['ghc'])), compile_and_run, [''])
+test('arith013', only_compiler_types(['ghc']), compile_and_run, [''])
 test('arith014', normal, compile_and_run, [''])
 test('arith015', normal, compile_and_run, [''])
 test('numrun009', normal, compile_and_run, [''])
@@ -38,7 +38,7 @@ test('numrun011', normal, compile_and_run, [''])
 test('numrun012', normal, compile_and_run, [''])
 test('numrun013', normal, compile_and_run, [''])
 test('numrun014', normal, compile_and_run, [''])
-test('arith016', compose(normal,only_compiler_types(['ghc'])), compile_and_run, [''])
+test('arith016', [normal,only_compiler_types(['ghc'])], compile_and_run, [''])
 test('arith017', normal, compile_and_run, [''])
 test('arith018', normal, compile_and_run, [''])
 test('arith019', normal, compile_and_run, [''])
diff --git a/tests/profiling/should_compile/all.T b/tests/profiling/should_compile/all.T
index cf7d48dad..ca3cc9300 100644
--- a/tests/profiling/should_compile/all.T
+++ b/tests/profiling/should_compile/all.T
@@ -1,8 +1,8 @@
 
 # We need to run prof001 and prof002 the normal way, as the extra flags
 # added for the profiling ways makes it pass
-test('prof001', compose(only_ways(['normal']), req_profiling), compile_and_run, ['-prof -caf-all'])
-test('prof002', compose(only_ways(['normal']), req_profiling), compile_and_run, ['-prof -caf-all'])
+test('prof001', [only_ways(['normal']), req_profiling], compile_and_run, ['-prof -caf-all'])
+test('prof002', [only_ways(['normal']), req_profiling], compile_and_run, ['-prof -caf-all'])
 
-test('T2410', compose(only_ways(['normal']), req_profiling), compile, ['-O2 -prof -caf-all'])
+test('T2410', [only_ways(['normal']), req_profiling], compile, ['-O2 -prof -caf-all'])
 
diff --git a/tests/profiling/should_run/all.T b/tests/profiling/should_run/all.T
index 3722209d9..493c846bc 100644
--- a/tests/profiling/should_run/all.T
+++ b/tests/profiling/should_run/all.T
@@ -3,10 +3,10 @@
 extra_prof_ways = ['prof', 'prof_hc_hb', 'prof_hb', 'prof_hd', 'prof_hy', 'prof_hr']
 
 test('heapprof001',
-     composes([only_ways(prof_ways),
-               extra_ways(extra_prof_ways),
-               req_profiling,
-               extra_run_opts('7')]),
+     [only_ways(prof_ways),
+      extra_ways(extra_prof_ways),
+      req_profiling,
+      extra_run_opts('7')],
      compile_and_run, [''])
 
 test('T2592',
diff --git a/tests/rts/all.T b/tests/rts/all.T
index d96e5476d..3a73054ba 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -1,40 +1,37 @@
-test('testblockalloc', compose(c_src, 
-                       compose(only_ways(['normal','threaded1']),
-                               extra_run_opts('+RTS -I0'))), 
-                       compile_and_run, [''])
+test('testblockalloc',
+     [c_src, only_ways(['normal','threaded1']), extra_run_opts('+RTS -I0')], 
+     compile_and_run, [''])
 
 
 # See bug #101, test requires +RTS -c (or equivalently +RTS -M<something>)
 # only GHCi triggers the bug, but we run the test all ways for completeness.
 test('bug1010', normal, compile_and_run, ['+RTS -c -RTS'])
 test('derefnull',
-     composes([
-             when(platform('x86_64-unknown-mingw32'), expect_broken(6079)),
-             # LLVM Optimiser considers dereference of a null pointer
-             # undefined and marks the code as unreachable which means
-             # that later optimisations remove it altogether.
-             omit_ways(['optllvm']),
-             # SIGSEGV on Linux (which we make the default)
-             exit_code(139),
-             # Apparently the output can be different on different
-             # Linux setups, so just ignore it. As long as we get
-             # the right exit code we're OK.
-             when(opsys('linux'), ignore_output),
-             # SIGBUS on OX X (PPC and x86 only; amd64 gives SEGV)
-             when(platform('i386-apple-darwin'), exit_code(138)),
-             when(platform('powerpc-apple-darwin'), exit_code(138)),
-             when(opsys('mingw32'), exit_code(1))]),
+     [when(platform('x86_64-unknown-mingw32'), expect_broken(6079)),
+      # LLVM Optimiser considers dereference of a null pointer
+      # undefined and marks the code as unreachable which means
+      # that later optimisations remove it altogether.
+      omit_ways(['optllvm']),
+      # SIGSEGV on Linux (which we make the default)
+      exit_code(139),
+      # Apparently the output can be different on different
+      # Linux setups, so just ignore it. As long as we get
+      # the right exit code we're OK.
+      when(opsys('linux'), ignore_output),
+      # SIGBUS on OX X (PPC and x86 only; amd64 gives SEGV)
+      when(platform('i386-apple-darwin'), exit_code(138)),
+      when(platform('powerpc-apple-darwin'), exit_code(138)),
+      when(opsys('mingw32'), exit_code(1))],
      compile_and_run, [''])
 test('divbyzero',
-     composes([
-             when(platform('x86_64-unknown-mingw32'), expect_broken(6079)),
-             # SIGFPE on Linux
-             exit_code(136),
-             # Apparently the output can be different on different
-             # Linux setups, so just ignore it. As long as we get
-             # the right exit code we're OK.
-             when(opsys('linux'), ignore_output),
-             when(opsys('mingw32'), exit_code(1))]),
+     [when(platform('x86_64-unknown-mingw32'), expect_broken(6079)),
+      # SIGFPE on Linux
+      exit_code(136),
+      # Apparently the output can be different on different
+      # Linux setups, so just ignore it. As long as we get
+      # the right exit code we're OK.
+      when(opsys('linux'), ignore_output),
+      when(opsys('mingw32'), exit_code(1))],
      compile_and_run, [''])
 
 test('outofmem', when(opsys('darwin'), skip), 
@@ -42,7 +39,7 @@ test('outofmem', when(opsys('darwin'), skip),
 test('outofmem2', extra_run_opts('+RTS -M5m -RTS'),
                   run_command, ['$MAKE -s --no-print-directory outofmem2'])
 
-test('T2047', compose(ignore_output, extra_run_opts('+RTS -c -RTS')),
+test('T2047', [ignore_output, extra_run_opts('+RTS -c -RTS')],
               compile_and_run, ['-package containers'])
 
 # Blackhole-detection test.
diff --git a/tests/simplCore/should_run/all.T b/tests/simplCore/should_run/all.T
index 545dadbf6..fa1dddd7d 100644
--- a/tests/simplCore/should_run/all.T
+++ b/tests/simplCore/should_run/all.T
@@ -18,8 +18,8 @@ test('simplrun005', normal, compile_and_run, [''])
 test('simplrun007', normal, compile_and_run, [''])
 test('simplrun008', normal, compile_and_run, [''])
 test('simplrun009', normal, compile_and_run, [''])
-test('simplrun010', composes([extra_run_opts('24 16 8 +RTS -M10m -RTS'),
-                              exit_code(251)])
+test('simplrun010', [extra_run_opts('24 16 8 +RTS -M10m -RTS'),
+                     exit_code(251)]
                   , compile_and_run, [''])
 
 # Really we'd like to run T2486 too, to check that its
diff --git a/tests/typecheck/should_run/all.T b/tests/typecheck/should_run/all.T
index 17b7b0e83..b5ffa8c0e 100755
--- a/tests/typecheck/should_run/all.T
+++ b/tests/typecheck/should_run/all.T
@@ -38,7 +38,8 @@ test('tcrun020', normal, compile_and_run, [''])
 # Doesn't work with External Core due to datatype with no constructors
 test('tcrun021', expect_fail_for(['extcore','optextcore']),
      compile_and_run, ['-package containers'])
-test('tcrun022', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compile_and_run, ['-O'])
+test('tcrun022', [omit_ways(['ghci']),only_compiler_types(['ghc'])],
+     compile_and_run, ['-O'])
 test('tcrun023', normal, compile_and_run, ['-O'])
 test('tcrun024', normal, compile_and_run, ['-O'])
 test('tcrun025', extra_clean(['TcRun025_B.hi', 'TcRun025_B.o']),
@@ -70,11 +71,16 @@ test('tcrun043', normal, compile_and_run, [''])
 test('tcrun044', normal, compile_and_run, [''])
 test('tcrun045', normal, compile_and_run, [''])
 test('tcrun046', normal, compile_and_run, [''])
-test('tcrun047', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compile_and_run, [''])
-test('tcrun048', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compile_and_run, [''])
-test('tcrun049', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compile_and_run, [''])
-test('tcrun050', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compile_and_run, [''])
-test('tcrun051', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compile_and_run, [''])
+test('tcrun047', [omit_ways(['ghci']), only_compiler_types(['ghc'])],
+     compile_and_run, [''])
+test('tcrun048', [omit_ways(['ghci']), only_compiler_types(['ghc'])],
+     compile_and_run, [''])
+test('tcrun049', [omit_ways(['ghci']), only_compiler_types(['ghc'])],
+     compile_and_run, [''])
+test('tcrun050', [omit_ways(['ghci']), only_compiler_types(['ghc'])],
+     compile_and_run, [''])
+test('tcrun051', [omit_ways(['ghci']), only_compiler_types(['ghc'])],
+     compile_and_run, [''])
 
 test('church', normal, compile_and_run, [''])
 test('testeq2', normal, compile_and_run, [''])
@@ -92,8 +98,10 @@ test('T4809', reqlib('mtl'), compile_and_run, [''])
 test('T2722', normal, compile_and_run, [''])
 test('mc17', normal, compile_and_run, [''])
 test('T5759', normal, compile_and_run, [''])
-test('T5573a', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compile_and_run, [''])
-test('T5573b', compose(omit_ways(['ghci']),only_compiler_types(['ghc'])), compile_and_run, [''])
+test('T5573a', [omit_ways(['ghci']), only_compiler_types(['ghc'])],
+     compile_and_run, [''])
+test('T5573b', [omit_ways(['ghci']), only_compiler_types(['ghc'])],
+     compile_and_run, [''])
 test('T7023', normal, compile_and_run, [''])
 test('T7126', normal, compile_and_run, [''])
 test('T6117', normal, compile_and_run, [''])
-- 
GitLab


From bb1f5b39e4c04f1712b1519b776064d2ddc72b84 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu, 14 Feb 2013 17:42:28 +0000
Subject: [PATCH 173/223] Test Trac #7645

---
 tests/typecheck/should_fail/T7645.hs     | 8 ++++++++
 tests/typecheck/should_fail/T7645.stderr | 6 ++++++
 tests/typecheck/should_fail/all.T        | 1 +
 3 files changed, 15 insertions(+)
 create mode 100644 tests/typecheck/should_fail/T7645.hs
 create mode 100644 tests/typecheck/should_fail/T7645.stderr

diff --git a/tests/typecheck/should_fail/T7645.hs b/tests/typecheck/should_fail/T7645.hs
new file mode 100644
index 000000000..db086c8e6
--- /dev/null
+++ b/tests/typecheck/should_fail/T7645.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE TypeOperators, KindSignatures #-}
+module T7645 where
+
+data (+) a b = P
+
+f :: ((+) a (a :: *), Maybe)
+f = undefined
+
diff --git a/tests/typecheck/should_fail/T7645.stderr b/tests/typecheck/should_fail/T7645.stderr
new file mode 100644
index 000000000..96bd2e47c
--- /dev/null
+++ b/tests/typecheck/should_fail/T7645.stderr
@@ -0,0 +1,6 @@
+
+T7645.hs:6:23:
+    Expecting one more argument to `Maybe'
+    The second argument of a tuple should have kind `*',
+      but `Maybe' has kind `* -> *'
+    In the type signature for `f': f :: ((+) a (a :: *), Maybe)
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index 9cffd3d98..de9cbb8c9 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -295,3 +295,4 @@ test('T7545', normal, compile_fail, [''])
 test('T7279', normal, compile_fail, [''])
 test('T2247', normal, compile_fail, [''])
 test('T7609', normal, compile_fail, [''])
+test('T7645', normal, compile_fail, [''])
-- 
GitLab


From 0a9a65ebbd17a23a496548428b31cf2a7c1e975e Mon Sep 17 00:00:00 2001
From: Manuel M T Chakravarty <chak@cse.unsw.edu.au>
Date: Fri, 15 Feb 2013 12:08:21 +1100
Subject: [PATCH 174/223] DPH: test tidying when unvectorised version of an
 exported variable disappears

---
 tests/dph/modules/ExportList.hs               | 33 +++++++++++++++++++
 tests/dph/modules/Makefile                    |  3 ++
 .../modules/dph-ExportList-vseg-fast.stderr   |  6 ++++
 tests/dph/modules/dph-modules.T               |  8 +++++
 4 files changed, 50 insertions(+)
 create mode 100644 tests/dph/modules/ExportList.hs
 create mode 100644 tests/dph/modules/Makefile
 create mode 100644 tests/dph/modules/dph-ExportList-vseg-fast.stderr
 create mode 100644 tests/dph/modules/dph-modules.T

diff --git a/tests/dph/modules/ExportList.hs b/tests/dph/modules/ExportList.hs
new file mode 100644
index 000000000..99011e1a9
--- /dev/null
+++ b/tests/dph/modules/ExportList.hs
@@ -0,0 +1,33 @@
+-- Explicit export list
+-- Produces error
+-- > ghc-stage2: panic! (the 'impossible' happened)
+-- >   (GHC version 7.7.20130109 for x86_64-unknown-linux):
+-- >      nameModule solveV{v r3Ep}
+-- It is something about internal vs external names.
+
+{-# LANGUAGE ParallelArrays, ParallelListComp #-}
+{-# OPTIONS -fvectorise #-}
+module ExportList (solvePA) where
+
+import Data.Array.Parallel hiding ((+), (-), (*), (/))
+import Data.Array.Parallel.PArray
+import Data.Array.Parallel.Prelude.Bool          as B
+import Data.Array.Parallel.Prelude.Double        as D
+import qualified Data.Array.Parallel.Prelude.Int as I
+import qualified Data.Vector                     as V
+import qualified Prelude                         as P
+
+data NodeV = NodeV Double Double Double [:NodeV:]
+
+{-# NOINLINE solvePA #-}
+solvePA
+    :: NodeV    -- ^ nodes
+    -> Double   -- ^ time
+    -> PArray Double
+solvePA nodes t = toPArrayP (solveV t)
+
+
+solveV :: Double -> [:Double:]
+solveV t
+ = concatP (mapP solveV [: :])
+
diff --git a/tests/dph/modules/Makefile b/tests/dph/modules/Makefile
new file mode 100644
index 000000000..9101fbd40
--- /dev/null
+++ b/tests/dph/modules/Makefile
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
diff --git a/tests/dph/modules/dph-ExportList-vseg-fast.stderr b/tests/dph/modules/dph-ExportList-vseg-fast.stderr
new file mode 100644
index 000000000..749c3cdfe
--- /dev/null
+++ b/tests/dph/modules/dph-ExportList-vseg-fast.stderr
@@ -0,0 +1,6 @@
+[1 of 1] Compiling ExportList       ( ExportList.hs, ExportList.o )
+Warning: vectorisation failure: identityConvTyCon: type constructor contains parallel arrays [::]
+  Could NOT call vectorised from original version ExportList.solveV
+Warning: vectorisation failure: identityConvTyCon: type constructor contains parallel arrays NodeV
+  Could NOT call vectorised from original version
+  ExportList.solvePA
diff --git a/tests/dph/modules/dph-modules.T b/tests/dph/modules/dph-modules.T
new file mode 100644
index 000000000..77db0cdf1
--- /dev/null
+++ b/tests/dph/modules/dph-modules.T
@@ -0,0 +1,8 @@
+test    ('dph-ExportList-vseg-fast' 
+        , [ extra_clean(['ExportList.o', 'ExportList.hi'])
+          , reqlib('dph-lifted-vseg')
+          , reqlib('dph-prim-par')
+          , only_ways(['normal', 'threaded1', 'threaded2']) ] 
+        , multimod_compile
+        , [ 'ExportList'
+          , '-O -fno-enable-rewrite-rules -package dph-lifted-vseg'])
-- 
GitLab


From 2a4da7313f5f16bb0de00df290e1246ae03f0966 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Fri, 15 Feb 2013 15:16:49 +0000
Subject: [PATCH 175/223] Test Trac #2354

---
 tests/typecheck/should_fail/T2354.hs     | 7 +++++++
 tests/typecheck/should_fail/T2354.stderr | 6 ++++++
 tests/typecheck/should_fail/all.T        | 1 +
 3 files changed, 14 insertions(+)
 create mode 100644 tests/typecheck/should_fail/T2354.hs
 create mode 100644 tests/typecheck/should_fail/T2354.stderr

diff --git a/tests/typecheck/should_fail/T2354.hs b/tests/typecheck/should_fail/T2354.hs
new file mode 100644
index 000000000..7bc1d40b7
--- /dev/null
+++ b/tests/typecheck/should_fail/T2354.hs
@@ -0,0 +1,7 @@
+module T2354(test) where 
+ 
+class AsInt a where 
+  {-# NOINLINE toInt #-} 
+  toInt   :: a -> Int 
+  {-# NOINLINE fromInt #-} 
+  fromInt :: Int -> a 
diff --git a/tests/typecheck/should_fail/T2354.stderr b/tests/typecheck/should_fail/T2354.stderr
new file mode 100644
index 000000000..da21f7929
--- /dev/null
+++ b/tests/typecheck/should_fail/T2354.stderr
@@ -0,0 +1,6 @@
+
+T2354.hs:4:3:
+    The INLINE pragma for default method `toInt' lacks an accompanying binding
+
+T2354.hs:6:3:
+    The INLINE pragma for default method `fromInt' lacks an accompanying binding
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index de9cbb8c9..0750c57a8 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -296,3 +296,4 @@ test('T7279', normal, compile_fail, [''])
 test('T2247', normal, compile_fail, [''])
 test('T7609', normal, compile_fail, [''])
 test('T7645', normal, compile_fail, [''])
+test('T2354', normal, compile_fail, ['-O'])
-- 
GitLab


From 82bd399be01b931d5b0b24bdf8ea61efd3c98bbc Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Fri, 15 Feb 2013 17:13:33 +0000
Subject: [PATCH 176/223] Test Trac #7688

---
 tests/ghci/scripts/T7688.hs     | 5 +++++
 tests/ghci/scripts/T7688.script | 4 ++++
 tests/ghci/scripts/T7688.stdout | 1 +
 tests/ghci/scripts/all.T        | 1 +
 4 files changed, 11 insertions(+)
 create mode 100644 tests/ghci/scripts/T7688.hs
 create mode 100644 tests/ghci/scripts/T7688.script
 create mode 100644 tests/ghci/scripts/T7688.stdout

diff --git a/tests/ghci/scripts/T7688.hs b/tests/ghci/scripts/T7688.hs
new file mode 100644
index 000000000..7538f2e9a
--- /dev/null
+++ b/tests/ghci/scripts/T7688.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE PolyKinds #-}
+
+module Tim where
+
+data Proxy (t:: k) = Proxy
diff --git a/tests/ghci/scripts/T7688.script b/tests/ghci/scripts/T7688.script
new file mode 100644
index 000000000..45fcb9068
--- /dev/null
+++ b/tests/ghci/scripts/T7688.script
@@ -0,0 +1,4 @@
+:l T7688
+:k Proxy
+# I'm expecting to see a kind-polymorphic answer,
+# even though -XPolyKinds is not set in GHCi
diff --git a/tests/ghci/scripts/T7688.stdout b/tests/ghci/scripts/T7688.stdout
new file mode 100644
index 000000000..3e387ebd1
--- /dev/null
+++ b/tests/ghci/scripts/T7688.stdout
@@ -0,0 +1 @@
+Proxy :: k -> *
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index 398efb4f0..e02a9783c 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -141,4 +141,5 @@ test('ghci058',
      ghci_script,
      ['ghci058.script'])
 test('T7587', normal, ghci_script, ['T7587.script'])
+test('T7688', normal, ghci_script, ['T7688.script'])
 
-- 
GitLab


From cb38f78be13f193f6bf8e857a1b7a803f6c034f1 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 15 Feb 2013 22:34:04 +0000
Subject: [PATCH 177/223] unixify line endings

---
 tests/ghci/shell.hs | 18 +++++++++---------
 1 file changed, 9 insertions(+), 9 deletions(-)

diff --git a/tests/ghci/shell.hs b/tests/ghci/shell.hs
index 75f78342a..5b4fdd1ab 100644
--- a/tests/ghci/shell.hs
+++ b/tests/ghci/shell.hs
@@ -1,9 +1,9 @@
--- Used to present a consistent shell view for :! commands in GHCi
--- scripts.  We're assuming that sh is in the path and that it
--- is a Bourne-compatible shell.
-
-import System.Cmd
-import System.Exit
-
-shell :: String -> IO ExitCode
-shell s = rawSystem "sh" ["-c", s]
+-- Used to present a consistent shell view for :! commands in GHCi
+-- scripts.  We're assuming that sh is in the path and that it
+-- is a Bourne-compatible shell.
+
+import System.Cmd
+import System.Exit
+
+shell :: String -> IO ExitCode
+shell s = rawSystem "sh" ["-c", s]
-- 
GitLab


From b370622746f1769181191e223d80f05c882feb18 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 15 Feb 2013 22:34:35 +0000
Subject: [PATCH 178/223] Don't use deprecated System.Cmd

---
 tests/ghci/shell.hs | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/ghci/shell.hs b/tests/ghci/shell.hs
index 5b4fdd1ab..4c08a8f34 100644
--- a/tests/ghci/shell.hs
+++ b/tests/ghci/shell.hs
@@ -2,8 +2,8 @@
 -- scripts.  We're assuming that sh is in the path and that it
 -- is a Bourne-compatible shell.
 
-import System.Cmd
 import System.Exit
+import System.Process (rawSystem)
 
 shell :: String -> IO ExitCode
 shell s = rawSystem "sh" ["-c", s]
-- 
GitLab


From 0732bd4d6fa5e1adfb286041e8910744fb0c9a2a Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 15 Feb 2013 22:39:57 +0000
Subject: [PATCH 179/223] Fix T7688

We need to use Haskell "--" comments in ghci scripts, not '#' comments.
---
 tests/ghci/scripts/T7688.script | 4 ++--
 1 file changed, 2 insertions(+), 2 deletions(-)

diff --git a/tests/ghci/scripts/T7688.script b/tests/ghci/scripts/T7688.script
index 45fcb9068..ee7037283 100644
--- a/tests/ghci/scripts/T7688.script
+++ b/tests/ghci/scripts/T7688.script
@@ -1,4 +1,4 @@
 :l T7688
 :k Proxy
-# I'm expecting to see a kind-polymorphic answer,
-# even though -XPolyKinds is not set in GHCi
+-- I'm expecting to see a kind-polymorphic answer,
+-- even though -XPolyKinds is not set in GHCi
-- 
GitLab


From 2e679d7d809642da451ad98a1bdf4316dc0eb7d0 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 16 Feb 2013 14:01:13 +0000
Subject: [PATCH 180/223] mask002: Follow changes in base

---
 tests/concurrent/should_run/mask002.hs | 8 +++++---
 1 file changed, 5 insertions(+), 3 deletions(-)

diff --git a/tests/concurrent/should_run/mask002.hs b/tests/concurrent/should_run/mask002.hs
index 264ac1fb7..069af8f2f 100644
--- a/tests/concurrent/should_run/mask002.hs
+++ b/tests/concurrent/should_run/mask002.hs
@@ -3,7 +3,7 @@ import Control.Concurrent
 import Text.Printf
 
 -- Test combinations of nesting mask/uninterruptibleMask with
--- forkIO/forkIOUnmask
+-- forkIO/forkIOWithUnmask
 
 main = do
   m <- newEmptyMVar
@@ -17,9 +17,11 @@ main = do
                                       print (e::SomeException)
                                       throwIO e
   killThread t2
-  t3 <- mask_ $ forkIOUnmasked $ do stat 3 Unmasked; putMVar m ()
+  t3 <- mask_ $ forkIOWithUnmask $ \unmask ->
+            unmask $ do stat 3 Unmasked; putMVar m ()
   takeMVar m
-  t4 <- uninterruptibleMask_ $ forkIOUnmasked $ do stat 4 Unmasked; putMVar m ()
+  t4 <- uninterruptibleMask_ $ forkIOWithUnmask $ \unmask ->
+            unmask $ do stat 4 Unmasked; putMVar m ()
   takeMVar m
 
 stat :: Int -> MaskingState -> IO ()
-- 
GitLab


From 9ef15f7672dc3e874a36b4367e355f6c4c232e5f Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 16 Feb 2013 14:06:01 +0000
Subject: [PATCH 181/223] T4978: Follow changes in base

---
 tests/perf/should_run/T4978.hs | 1 +
 1 file changed, 1 insertion(+)

diff --git a/tests/perf/should_run/T4978.hs b/tests/perf/should_run/T4978.hs
index 6413b01fd..b661edc48 100644
--- a/tests/perf/should_run/T4978.hs
+++ b/tests/perf/should_run/T4978.hs
@@ -6,6 +6,7 @@ import Data.ByteString.Internal (inlinePerformIO)
 import qualified Data.ByteString.Internal as S
 import Data.Monoid
 import Foreign
+import System.IO.Unsafe
 
 newtype Builder = Builder {
         runBuilder :: (Buffer -> [S.ByteString]) -> Buffer -> [S.ByteString]
-- 
GitLab


From 21a204ac56b42db6beffc9d60510f991eba4c2b5 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 16 Feb 2013 14:07:21 +0000
Subject: [PATCH 182/223] BadImport04: Follow changes in base

---
 tests/safeHaskell/unsafeLibs/BadImport04.hs     | 4 ++--
 tests/safeHaskell/unsafeLibs/BadImport04.stderr | 2 +-
 2 files changed, 3 insertions(+), 3 deletions(-)

diff --git a/tests/safeHaskell/unsafeLibs/BadImport04.hs b/tests/safeHaskell/unsafeLibs/BadImport04.hs
index c22b0362f..df369f3bb 100644
--- a/tests/safeHaskell/unsafeLibs/BadImport04.hs
+++ b/tests/safeHaskell/unsafeLibs/BadImport04.hs
@@ -1,8 +1,8 @@
 {-# LANGUAGE Safe #-}
--- | Import unsafe module Foreign to make sure it fails
+-- | Import unsafe module System.IO.Unsafe to make sure it fails
 module Main where
 
-import Foreign (unsafePerformIO)
+import System.IO.Unsafe (unsafePerformIO)
 
 f :: Int
 f = unsafePerformIO $ putStrLn "What kind of swallow?" >> return 2
diff --git a/tests/safeHaskell/unsafeLibs/BadImport04.stderr b/tests/safeHaskell/unsafeLibs/BadImport04.stderr
index 2c2f3befb..e0fa256c3 100644
--- a/tests/safeHaskell/unsafeLibs/BadImport04.stderr
+++ b/tests/safeHaskell/unsafeLibs/BadImport04.stderr
@@ -1,3 +1,3 @@
 
 BadImport04.hs:5:1:
-    Foreign: Can't be safely imported! The module itself isn't safe.
+    System.IO.Unsafe: Can't be safely imported! The module itself isn't safe.
-- 
GitLab


From 42686031e0cf7759f78984b3518237afe0842d02 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 16 Feb 2013 14:09:05 +0000
Subject: [PATCH 183/223] Remove BadImport04 and BadImport09

They are now redundant
---
 tests/safeHaskell/unsafeLibs/BadImport04.hs     | 12 ------------
 tests/safeHaskell/unsafeLibs/BadImport04.stderr |  3 ---
 tests/safeHaskell/unsafeLibs/BadImport09.hs     | 12 ------------
 tests/safeHaskell/unsafeLibs/BadImport09.stderr |  4 ----
 tests/safeHaskell/unsafeLibs/all.T              |  2 --
 5 files changed, 33 deletions(-)
 delete mode 100644 tests/safeHaskell/unsafeLibs/BadImport04.hs
 delete mode 100644 tests/safeHaskell/unsafeLibs/BadImport04.stderr
 delete mode 100644 tests/safeHaskell/unsafeLibs/BadImport09.hs
 delete mode 100644 tests/safeHaskell/unsafeLibs/BadImport09.stderr

diff --git a/tests/safeHaskell/unsafeLibs/BadImport04.hs b/tests/safeHaskell/unsafeLibs/BadImport04.hs
deleted file mode 100644
index df369f3bb..000000000
--- a/tests/safeHaskell/unsafeLibs/BadImport04.hs
+++ /dev/null
@@ -1,12 +0,0 @@
-{-# LANGUAGE Safe #-}
--- | Import unsafe module System.IO.Unsafe to make sure it fails
-module Main where
-
-import System.IO.Unsafe (unsafePerformIO)
-
-f :: Int
-f = unsafePerformIO $ putStrLn "What kind of swallow?" >> return 2
-
-main :: IO ()
-main = putStrLn $ "X is: " ++ show f
-
diff --git a/tests/safeHaskell/unsafeLibs/BadImport04.stderr b/tests/safeHaskell/unsafeLibs/BadImport04.stderr
deleted file mode 100644
index e0fa256c3..000000000
--- a/tests/safeHaskell/unsafeLibs/BadImport04.stderr
+++ /dev/null
@@ -1,3 +0,0 @@
-
-BadImport04.hs:5:1:
-    System.IO.Unsafe: Can't be safely imported! The module itself isn't safe.
diff --git a/tests/safeHaskell/unsafeLibs/BadImport09.hs b/tests/safeHaskell/unsafeLibs/BadImport09.hs
deleted file mode 100644
index 30881b143..000000000
--- a/tests/safeHaskell/unsafeLibs/BadImport09.hs
+++ /dev/null
@@ -1,12 +0,0 @@
-{-# LANGUAGE Safe #-}
--- | Import unsafe module Foreign.Marshal to make sure it fails
-module Main where
-
-import Foreign.Marshal
-
-f :: Int
-f = unsafeLocalState $ putStrLn "What kind of swallow?" >> return 2
-
-main :: IO ()
-main = putStrLn $ "X is: " ++ show f
-
diff --git a/tests/safeHaskell/unsafeLibs/BadImport09.stderr b/tests/safeHaskell/unsafeLibs/BadImport09.stderr
deleted file mode 100644
index 2dd8e7cf5..000000000
--- a/tests/safeHaskell/unsafeLibs/BadImport09.stderr
+++ /dev/null
@@ -1,4 +0,0 @@
-
-BadImport09.hs:5:1:
-    Foreign.Marshal: Can't be safely imported!
-    The module itself isn't safe.
diff --git a/tests/safeHaskell/unsafeLibs/all.T b/tests/safeHaskell/unsafeLibs/all.T
index 69d1804b0..5fc0c6e28 100644
--- a/tests/safeHaskell/unsafeLibs/all.T
+++ b/tests/safeHaskell/unsafeLibs/all.T
@@ -31,12 +31,10 @@ test('BadImport03',
      extra_clean(['BadImport03_A.o', 'BadImport03_A.hi']),
      multimod_compile_fail,
      ['BadImport03', ''])
-test('BadImport04', normal, compile_fail, [''])
 test('BadImport05', normal, compile_fail, [''])
 test('BadImport06', normal, compile_fail, [''])
 test('BadImport07', normal, compile_fail, [''])
 test('BadImport08', normal, compile_fail, [''])
-test('BadImport09', normal, compile_fail, [''])
 
 # check safe modules are marked safe
 test('GoodImport01', normal, compile, [''])
-- 
GitLab


From 08d51aa72398ba1c0d1e5a57e62db853584cdce5 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 16 Feb 2013 14:15:16 +0000
Subject: [PATCH 184/223] Remove Dep0{3,4}

I'm not sure what they're supposed to test
---
 tests/safeHaskell/unsafeLibs/Dep03.hs     | 7 -------
 tests/safeHaskell/unsafeLibs/Dep03.stderr | 4 ----
 tests/safeHaskell/unsafeLibs/Dep04.hs     | 8 --------
 tests/safeHaskell/unsafeLibs/Dep04.stderr | 5 -----
 tests/safeHaskell/unsafeLibs/all.T        | 2 --
 5 files changed, 26 deletions(-)
 delete mode 100644 tests/safeHaskell/unsafeLibs/Dep03.hs
 delete mode 100644 tests/safeHaskell/unsafeLibs/Dep03.stderr
 delete mode 100644 tests/safeHaskell/unsafeLibs/Dep04.hs
 delete mode 100644 tests/safeHaskell/unsafeLibs/Dep04.stderr

diff --git a/tests/safeHaskell/unsafeLibs/Dep03.hs b/tests/safeHaskell/unsafeLibs/Dep03.hs
deleted file mode 100644
index b5f39affc..000000000
--- a/tests/safeHaskell/unsafeLibs/Dep03.hs
+++ /dev/null
@@ -1,7 +0,0 @@
-module Dep03 where
-
-import Foreign
-
-bad :: IO a -> a
-bad = unsafePerformIO
-
diff --git a/tests/safeHaskell/unsafeLibs/Dep03.stderr b/tests/safeHaskell/unsafeLibs/Dep03.stderr
deleted file mode 100644
index 719ab522f..000000000
--- a/tests/safeHaskell/unsafeLibs/Dep03.stderr
+++ /dev/null
@@ -1,4 +0,0 @@
-
-Dep03.hs:6:7: Warning:
-    In the use of `unsafePerformIO' (imported from Foreign):
-    Deprecated: "Use System.IO.Unsafe.unsafePerformIO instead; This function will be removed in the next release"
diff --git a/tests/safeHaskell/unsafeLibs/Dep04.hs b/tests/safeHaskell/unsafeLibs/Dep04.hs
deleted file mode 100644
index 5ff23ea0a..000000000
--- a/tests/safeHaskell/unsafeLibs/Dep04.hs
+++ /dev/null
@@ -1,8 +0,0 @@
-module Dep04 where
-
-import Foreign.Ptr
-import Foreign.ForeignPtr
-
-bad :: ForeignPtr a -> Ptr a
-bad = unsafeForeignPtrToPtr
-
diff --git a/tests/safeHaskell/unsafeLibs/Dep04.stderr b/tests/safeHaskell/unsafeLibs/Dep04.stderr
deleted file mode 100644
index 8a10f221c..000000000
--- a/tests/safeHaskell/unsafeLibs/Dep04.stderr
+++ /dev/null
@@ -1,5 +0,0 @@
-
-Dep04.hs:7:7: Warning:
-    In the use of `unsafeForeignPtrToPtr'
-    (imported from Foreign.ForeignPtr):
-    Deprecated: "Use Foreign.ForeignPtr.Unsafe.unsafeForeignPtrToPtr instead; This function will be removed in the next release"
diff --git a/tests/safeHaskell/unsafeLibs/all.T b/tests/safeHaskell/unsafeLibs/all.T
index 5fc0c6e28..81fd18a08 100644
--- a/tests/safeHaskell/unsafeLibs/all.T
+++ b/tests/safeHaskell/unsafeLibs/all.T
@@ -12,8 +12,6 @@ setTestOpts(f)
 # Check correct methods are deprecated
 test('Dep01', normal, compile, [''])
 test('Dep02', normal, compile, [''])
-test('Dep03', normal, compile, [''])
-test('Dep04', normal, compile, [''])
 test('Dep05', normal, compile_fail, [''])
 test('Dep06', normal, compile_fail, [''])
 test('Dep07', normal, compile_fail, [''])
-- 
GitLab


From 930a456a29b685f46239a394f7adbe85b7189d79 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 16 Feb 2013 17:20:57 +0000
Subject: [PATCH 185/223] Update GoodImport03

---
 tests/safeHaskell/unsafeLibs/GoodImport03.hs | 1 -
 1 file changed, 1 deletion(-)

diff --git a/tests/safeHaskell/unsafeLibs/GoodImport03.hs b/tests/safeHaskell/unsafeLibs/GoodImport03.hs
index 921858a39..6533e18b7 100644
--- a/tests/safeHaskell/unsafeLibs/GoodImport03.hs
+++ b/tests/safeHaskell/unsafeLibs/GoodImport03.hs
@@ -23,7 +23,6 @@ import Control.Exception.Base
 
 import Control.Monad
 import Control.Monad.Fix
-import Control.Monad.Instances
 import Control.Monad.Zip
 
 import Data.Bits
-- 
GitLab


From 6c17bbc3d2484abbab4ff5ccacf34b56798a6e19 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 16 Feb 2013 23:26:27 +0000
Subject: [PATCH 186/223] Add extra cleaning for ccfail004

---
 tests/ffi/should_fail/all.T | 6 +++++-
 1 file changed, 5 insertions(+), 1 deletion(-)

diff --git a/tests/ffi/should_fail/all.T b/tests/ffi/should_fail/all.T
index cb6ffe9ea..d1cba3c0d 100644
--- a/tests/ffi/should_fail/all.T
+++ b/tests/ffi/should_fail/all.T
@@ -6,7 +6,11 @@ test('ccfail001', only_compiler_types(['ghc']), compile_fail, [''])
 test('ccfail002', only_compiler_types(['ghc']), compile_fail, [''])
 test('ccfail003', only_compiler_types(['ghc']), compile_fail, [''])
 test('T3066', only_compiler_types(['ghc']), compile_fail, [''])
-test('ccfail004', only_compiler_types(['ghc']), multimod_compile_fail, ['ccfail004', '-v0'])
+test('ccfail004',
+     [only_compiler_types(['ghc']),
+      extra_clean(['Ccfail004A.hi', 'Ccfail004A.o'])],
+     multimod_compile_fail,
+     ['ccfail004', '-v0'])
 test('ccfail005', only_compiler_types(['ghc']), compile_fail, [''])
 test('ccall_value', normal, compile_fail, [''])
 test('capi_value_function', normal, compile_fail, [''])
-- 
GitLab


From ba8604b2c64873a7de5a57abfdf7d863141264e7 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 16 Feb 2013 23:28:15 +0000
Subject: [PATCH 187/223] Add extra cleaning for print035

---
 tests/ghci.debugger/scripts/all.T | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/tests/ghci.debugger/scripts/all.T b/tests/ghci.debugger/scripts/all.T
index c5ea2fb63..eaae14f68 100644
--- a/tests/ghci.debugger/scripts/all.T
+++ b/tests/ghci.debugger/scripts/all.T
@@ -36,7 +36,8 @@ test('print032', normal, ghci_script, ['print032.script'])
 test('print033', normal, ghci_script, ['print033.script'])
 test('print034', normal, ghci_script, ['print034.script'])
 test('print035',
-     when(ghci_dynamic(), expect_broken(7326)),
+     [when(ghci_dynamic(), expect_broken(7326)),
+      extra_clean(['../Unboxed.hi', '../Unboxed.o'])],
      ghci_script,
      ['print035.script'])
 
-- 
GitLab


From 3e2d8f1a57b340a65d1bd462766e26b668219d8e Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 17 Feb 2013 21:24:37 +0000
Subject: [PATCH 188/223] Follow the unsafePerformIO change in base

---
 tests/concurrent/should_run/conc039.hs | 1 +
 tests/concurrent/should_run/conc040.hs | 1 +
 2 files changed, 2 insertions(+)

diff --git a/tests/concurrent/should_run/conc039.hs b/tests/concurrent/should_run/conc039.hs
index dc5d181a3..dc493d4ac 100644
--- a/tests/concurrent/should_run/conc039.hs
+++ b/tests/concurrent/should_run/conc039.hs
@@ -1,6 +1,7 @@
 {-# LANGUAGE ForeignFunctionInterface #-}
 
 import Foreign
+import System.IO.Unsafe
 import System.Mem
 import Control.Concurrent
 
diff --git a/tests/concurrent/should_run/conc040.hs b/tests/concurrent/should_run/conc040.hs
index be3bfdb91..e4acd84ee 100644
--- a/tests/concurrent/should_run/conc040.hs
+++ b/tests/concurrent/should_run/conc040.hs
@@ -4,6 +4,7 @@ import Foreign
 import Data.IORef
 import Control.Concurrent
 import Control.Exception
+import System.IO.Unsafe
 
 foreign import ccall "wrapper"
   wrap :: IO () -> IO (FunPtr (IO ()))
-- 
GitLab


From 031dbd6fa7e32313962e2aa6cd70b92f07edeb3f Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 17 Feb 2013 21:48:16 +0000
Subject: [PATCH 189/223] Fix prog003 after forkOnIO was removed

---
 tests/concurrent/prog003/TestRun.hs | 8 ++++----
 1 file changed, 4 insertions(+), 4 deletions(-)

diff --git a/tests/concurrent/prog003/TestRun.hs b/tests/concurrent/prog003/TestRun.hs
index fd6e19de1..13c84ea89 100644
--- a/tests/concurrent/prog003/TestRun.hs
+++ b/tests/concurrent/prog003/TestRun.hs
@@ -176,10 +176,10 @@ run_testdata testdata_fname mode = do
 --          ; wait <- atomically (newTVar 0)
           ; wait <- newEmptyMVar
           ; start <- getCurrentTime
-          ; zipWithM (\n work -> forkOnIO n (do { executeTasks nl work
-                                                ; putMVar wait () }))
-                                                --atomically(do counter <- readTVar wait
---                                                                writeTVar wait (counter+1)) }))
+          ; zipWithM (\n work -> forkOn n (do { executeTasks nl work
+                                              ; putMVar wait () }))
+                                              --atomically(do counter <- readTVar wait
+--                                                              writeTVar wait (counter+1)) }))
             [0..] works
           ; replicateM_ (length works) (takeMVar wait)
 --          ; atomically ( do { counter <- readTVar wait
-- 
GitLab


From 8b6a1a2ba410e1c9a255909981a49437bec042b3 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 17 Feb 2013 21:51:30 +0000
Subject: [PATCH 190/223] Fix T4891 following GHC API changes

---
 tests/ghc-api/T4891/T4891.hs | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/ghc-api/T4891/T4891.hs b/tests/ghc-api/T4891/T4891.hs
index 02d2dee8c..ca4aff91c 100644
--- a/tests/ghc-api/T4891/T4891.hs
+++ b/tests/ghc-api/T4891/T4891.hs
@@ -52,7 +52,7 @@ chaseConstructor :: (GhcMonad m) => HValue -> m ()
 chaseConstructor !hv = do
   dflags <- getDynFlags
   liftIO $ putStrLn "====="
-  closure <- liftIO $ getClosureData hv
+  closure <- liftIO $ getClosureData dflags hv
   case tipe closure  of
     Indirection _ -> chaseConstructor (ptrs closure ! 0)
     Constr -> do
-- 
GitLab


From 815c4355ca6ec97fe476d46b2c09ef257bc753dc Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 17 Feb 2013 21:55:42 +0000
Subject: [PATCH 191/223] Fix T6145; MatchGroup was renamed to MG and altered

---
 tests/ghc-api/T6145.hs | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/ghc-api/T6145.hs b/tests/ghc-api/T6145.hs
index 42fc93bb0..0332b05a5 100644
--- a/tests/ghc-api/T6145.hs
+++ b/tests/ghc-api/T6145.hs
@@ -35,7 +35,7 @@ main = do
       getDataCon (L _ (AbsBinds { abs_binds = bs }))
         = not (isEmptyBag (filterBag getDataCon bs))
       getDataCon (L l (f@FunBind {}))
-        | (MatchGroup (m:_) _)<-fun_matches f,
+        | (MG (m:_) _ _) <- fun_matches f,
           (L _ (c@ConPatOut{}):_)<-hsLMatchPats m,
           (L l _)<-pat_con c
         = isGoodSrcSpan l       -- Check that the source location is a good one
-- 
GitLab


From 3a8b8c1bc6324e072bbd1671da33bf7c6737ee20 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 17 Feb 2013 23:07:36 +0000
Subject: [PATCH 192/223] Remove compose

---
 driver/testlib.py | 3 ---
 1 file changed, 3 deletions(-)

diff --git a/driver/testlib.py b/driver/testlib.py
index 355392656..66987a1f5 100644
--- a/driver/testlib.py
+++ b/driver/testlib.py
@@ -483,9 +483,6 @@ def executeSetups(fs, name, opts):
         # fs is a single function, so just apply it
         fs(name, opts)
 
-def compose( f, g ):
-    return [f, g]
-
 # -----------------------------------------------------------------------------
 # The current directory of tests
 
-- 
GitLab


From f8014c505a894c774a00d605027aeb2e9c73476a Mon Sep 17 00:00:00 2001
From: Manuel M T Chakravarty <chak@cse.unsw.edu.au>
Date: Mon, 18 Feb 2013 21:33:53 +1100
Subject: [PATCH 193/223] Fixed dph-classes

---
 tests/dph/classes/dph-classes.T | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/dph/classes/dph-classes.T b/tests/dph/classes/dph-classes.T
index aa10c831d..b493819bd 100644
--- a/tests/dph/classes/dph-classes.T
+++ b/tests/dph/classes/dph-classes.T
@@ -1,5 +1,5 @@
 test    ('dph-classes-vseg-fast' 
-        , [ expect_fail
+        , [ normal
           , extra_clean(['Main.o', 'Main.hi', 'DefsVect.hi', 'DefsVect.o'])
           , reqlib('dph-lifted-vseg')
           , reqlib('dph-prim-par')
-- 
GitLab


From 972e14164b8377d39aadecfd6567f0e7fa5b7840 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Mon, 18 Feb 2013 10:40:29 +0000
Subject: [PATCH 194/223] Revert "Significant (15%) bytes-allocated reduction
 in haddock.Cabal and haddock.base"

This reverts commit c3c9babf10990ccc36451b3758d6f19d749b879d.
---
 tests/perf/haddock/all.T | 6 ++----
 1 file changed, 2 insertions(+), 4 deletions(-)

diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T
index e1fdd869e..ba25e146b 100644
--- a/tests/perf/haddock/all.T
+++ b/tests/perf/haddock/all.T
@@ -25,13 +25,12 @@ test('haddock.base',
           ,(wordsize(32), 52237984, 1)])
             # 2013-02-10: 52237984 (x86/OSX)
      ,stats_num_field('bytes allocated',
-          [(wordsize(64), 5184155784, 5)
+          [(wordsize(64), 6282746976, 5)
             # 2012-08-14: 5920822352 (amd64/Linux)
             # 2012-09-20: 5829972376 (amd64/Linux)
             # 2012-10-08: 5902601224 (amd64/Linux)
             # 2013-01-17: 6064874536 (x86_64/Linux)
             # 2013-02-10: 6282746976 (x86_64/Linux)
-            # 2013-02-13: 5184155784 (x86_64/Linux)
           ,(platform('i386-unknown-mingw32'), 3358693084, 1)
             # 2013-02-10:                     3358693084 (x86/Windows)
           ,(wordsize(32), 3146596848, 1)])
@@ -68,11 +67,10 @@ test('haddock.Cabal',
             # 2012-08-14: 47461532 (x86/OSX)
             # 2013-02-10: 46563344 (x86/OSX)
      ,stats_num_field('bytes allocated',
-          [(wordsize(64), 2809307464, 5)
+          [(wordsize(64), 3373401360, 2)
             # 2012-08-14: 3255435248 (amd64/Linux)
             # 2012-08-29: 3324606664 (amd64/Linux, new codegen)
             # 2012-10-08: 3373401360 (amd64/Linux)
-            # 2013-02-13: 2809307464 (amd64/Linux)
           ,(platform('i386-unknown-mingw32'), 1906532680, 1)
             # 2012-10-30:                     1733638168 (x86/Windows)
             # 2013-02-10:                     1906532680 (x86/Windows)
-- 
GitLab


From cb85a272bef2f685f2f613c1c0fdb1b9f2238b46 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Mon, 18 Feb 2013 10:42:23 +0000
Subject: [PATCH 195/223] update T3064 max_bytes_used (up a little)

---
 tests/perf/compiler/all.T | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T
index fee07dd52..973e5ef95 100644
--- a/tests/perf/compiler/all.T
+++ b/tests/perf/compiler/all.T
@@ -177,10 +177,11 @@ test('T3064',
       compiler_stats_num_field('max_bytes_used',
           [(wordsize(32), 5511604, 20),
         # expected value: 2247016 (x86/Linux) (28/6/2011):
-           (wordsize(64), 8687360, 5)]),
+           (wordsize(64), 9397488, 10)]),
             # (amd64/Linux, intree) (28/06/2011):  4032024
             # (amd64/Linux, intree) (07/02/2013):  9819288
             # (amd64/Linux)         (14/02/2013):  8687360
+            # (amd64/Linux)         (18/02/2013):  9397488
        only_ways(['normal'])
       ],
      compile,
-- 
GitLab


From 5c9db4f47062732e365b2101ea4a9679a6e8a264 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Tue, 19 Feb 2013 09:39:38 +0000
Subject: [PATCH 196/223] unsafePerformIO moved

---
 tests/profiling/should_run/T3001-2.hs | 1 +
 1 file changed, 1 insertion(+)

diff --git a/tests/profiling/should_run/T3001-2.hs b/tests/profiling/should_run/T3001-2.hs
index 961d9c376..5c0cb3e97 100644
--- a/tests/profiling/should_run/T3001-2.hs
+++ b/tests/profiling/should_run/T3001-2.hs
@@ -21,6 +21,7 @@ import GHC.Word
 
 import Control.Monad
 import Foreign
+import System.IO.Unsafe
 import System.IO
 
 import Data.Char    (chr,ord)
-- 
GitLab


From 5190f9aff8e5ba0114afb5b7603a3d2c6dd9479e Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Tue, 19 Feb 2013 09:40:40 +0000
Subject: [PATCH 197/223] accept output

I think the change to compile top-level indirections more efficiently
removed the "CAF" entries from the stack.  That's a surprising
side-effect, but it's not really a problem.
---
 tests/profiling/should_run/callstack001.stdout | 4 ++--
 1 file changed, 2 insertions(+), 2 deletions(-)

diff --git a/tests/profiling/should_run/callstack001.stdout b/tests/profiling/should_run/callstack001.stdout
index f5a8580d7..13c64a0a7 100644
--- a/tests/profiling/should_run/callstack001.stdout
+++ b/tests/profiling/should_run/callstack001.stdout
@@ -1,2 +1,2 @@
-["Main.CAF (<entire-module>)","Main.main (callstack001.hs:17:8-21)","Main.mapM (callstack001.hs:10:13-17)","Main.mapM.go (callstack001.hs:13:17-19)","Main.f (callstack001.hs:7:10-35)"]
-["Main.CAF (<entire-module>)","Main.main (callstack001.hs:17:8-21)","Main.mapM (callstack001.hs:10:13-17)","Main.mapM.go (callstack001.hs:13:17-19)","Main.f (callstack001.hs:7:10-35)"]
+["Main.main (callstack001.hs:17:8-21)","Main.mapM (callstack001.hs:10:13-17)","Main.mapM.go (callstack001.hs:13:17-19)","Main.f (callstack001.hs:7:10-35)"]
+["Main.main (callstack001.hs:17:8-21)","Main.mapM (callstack001.hs:10:13-17)","Main.mapM.go (callstack001.hs:13:17-19)","Main.f (callstack001.hs:7:10-35)"]
-- 
GitLab


From de9a5457567313b5890f6aa8caee8f7802464acb Mon Sep 17 00:00:00 2001
From: Jan Stolarek <jan.stolarek@p.lodz.pl>
Date: Thu, 14 Feb 2013 13:07:26 +0100
Subject: [PATCH 198/223] Test #7689

Tests primitive bitwise `andI#`, `orI#`, `notI#`, `xorI#`
operations on Int#
---
 tests/numeric/should_run/T7689.hs     | 78 +++++++++++++++++++++++++++
 tests/numeric/should_run/T7689.stdout | 37 +++++++++++++
 tests/numeric/should_run/all.T        |  2 +
 3 files changed, 117 insertions(+)
 create mode 100644 tests/numeric/should_run/T7689.hs
 create mode 100644 tests/numeric/should_run/T7689.stdout

diff --git a/tests/numeric/should_run/T7689.hs b/tests/numeric/should_run/T7689.hs
new file mode 100644
index 000000000..4f0d8e439
--- /dev/null
+++ b/tests/numeric/should_run/T7689.hs
@@ -0,0 +1,78 @@
+{-# LANGUAGE BangPatterns, MagicHash #-}
+module Main where
+
+import Data.Bits (finiteBitSize)
+import GHC.Exts
+
+main :: IO ()
+main = do
+  -- 0 is the annihilator of andI#
+  print (I# (maxI# `andI#`    0#) == 0)
+  print (I# (minI# `andI#`    0#) == 0)
+  print (I# (0#    `andI#` maxI#) == 0)
+  print (I# (0#    `andI#` minI#) == 0)
+  print (I# (0#    `andI#`    0#) == 0)
+  -- integer with all bits set to 1 is the neutral element of orI#,
+  -- in two's complement this is -1
+  print (I# (maxI# `andI#`   -1#) == maxI)
+  print (I# (minI# `andI#`   -1#) == minI)
+  print (I# (-1#   `andI#` maxI#) == maxI)
+  print (I# (-1#   `andI#` minI#) == minI)
+  print (I# (-1#   `andI#`   -1#) == -1)
+  -- these two numbers have every other bit set, they should give 0
+  print (I# (magicInt1# `andI#` magicInt2#) == 0)
+
+  -- integer with all bits set to 1 is the annihilator of orI#,
+  print (I# (maxI# `orI#`    -1#) == -1)
+  print (I# (minI# `orI#`    -1#) == -1)
+  print (I# (-1#   `orI#`  maxI#) == -1)
+  print (I# (-1#   `orI#`  minI#) == -1)
+  print (I# (-1#   `orI#`    -1#) == -1)
+  -- 0 is the neutral element of orI#
+  print (I# (maxI# `orI#`     0#) == maxI)
+  print (I# (minI# `orI#`     0#) == minI)
+  print (I# (0#    `orI#`  maxI#) == maxI)
+  print (I# (0#    `orI#`  minI#) == minI)
+  print (I# (0#    `orI#`     0#) == 0)
+  -- this time we should get an integer with all bits set, that is -1
+  print (I# (magicInt1# `orI#` magicInt2#) == -1)
+
+  -- suprising as the first two tests may look, this is what we expect from
+  -- bitwise negation in two's complement enccoding
+  print (I# (notI#  0#) == -1)
+  print (I# (notI# -1#) ==  0)
+  -- magic int numbers are bitwise complementary
+  print (I# (notI# magicInt1#) == magicInt2)
+  print (I# (notI# magicInt2#) == magicInt1)
+
+  -- 0 is the identity of xor
+  print (I# (minI# `xorI#`    0#) == minI)
+  print (I# (maxI# `xorI#`    0#) == maxI)
+  print (I# (0#    `xorI#` minI#) == minI)
+  print (I# (0#    `xorI#` maxI#) == maxI)
+  -- anything xored with itself is 0
+  print (I# (maxI# `xorI#` maxI#) == 0)
+  print (I# (minI# `xorI#` minI#) == 0)
+  -- xoring with -1 is like bitwise negation (becuse -1 has all bits set to 1)
+  print (I# (minI# `xorI#`   -1#) == maxI)
+  print (I# (maxI# `xorI#`   -1#) == minI)
+  print (I# (-1#   `xorI#` minI#) == maxI)
+  print (I# (-1#   `xorI#` maxI#) == minI)
+  -- since these two have exactly the opposite bits turned on they should
+  -- give an int with all bits set, and that is -1 as you probably already
+  -- remember by now
+  print (I# (magicInt1# `xorI#` magicInt2#) == -1)
+    where
+      intBitSize = finiteBitSize (undefined :: Int)
+      minI  = minBound :: Int
+      maxI  = maxBound :: Int
+      minI# = x
+          where !(I# x) = minBound
+      maxI# = x
+          where !(I# x) = maxBound
+      magicInt1 = sum $ map (2^) [0,2..intBitSize] :: Int
+      magicInt2 = sum $ map (2^) [1,3..intBitSize] :: Int
+      magicInt1# = x
+          where !(I# x) = magicInt1
+      magicInt2# = x
+          where !(I# x) = magicInt2
diff --git a/tests/numeric/should_run/T7689.stdout b/tests/numeric/should_run/T7689.stdout
new file mode 100644
index 000000000..1a97da170
--- /dev/null
+++ b/tests/numeric/should_run/T7689.stdout
@@ -0,0 +1,37 @@
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
+True
diff --git a/tests/numeric/should_run/all.T b/tests/numeric/should_run/all.T
index 70bd59150..747b37f75 100644
--- a/tests/numeric/should_run/all.T
+++ b/tests/numeric/should_run/all.T
@@ -60,3 +60,5 @@ test('T7014',
      ['$MAKE -s --no-print-directory T7014'])
 
 test('T7233', normal, compile_and_run, [''])
+
+test('T7689', normal, compile_and_run, [''])
-- 
GitLab


From a6d80ce5fb2211af8dafc425705fefb316702802 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Tue, 19 Feb 2013 18:46:40 +0000
Subject: [PATCH 199/223] Update T3279 to use mask rather than block

I'm not 100% sure that this is still testing what it's meant to be
testing, but the test still passes.
---
 tests/concurrent/should_run/T3279.hs | 22 ++++++++++++++--------
 1 file changed, 14 insertions(+), 8 deletions(-)

diff --git a/tests/concurrent/should_run/T3279.hs b/tests/concurrent/should_run/T3279.hs
index f47970431..46e9b0367 100644
--- a/tests/concurrent/should_run/T3279.hs
+++ b/tests/concurrent/should_run/T3279.hs
@@ -1,24 +1,30 @@
 -- test for #3279
 
+import Data.IORef
 import System.IO.Unsafe
 import GHC.Conc
 import Control.Exception
 
-f :: Int
-f = (1 +) . unsafePerformIO $ do
-        error "foo" `catch` \(SomeException e) -> do
-            myThreadId >>= flip throwTo e
-            -- point X
-            unblock $ return 1
-
 main :: IO ()
 main = do
+    restoreRef <- newIORef id
+
+    let f :: Int
+        f = (1 +) . unsafePerformIO $ do
+                error "foo" `catch` \(SomeException e) -> do
+                    myThreadId >>= flip throwTo e
+                    -- point X
+                    restore <- readIORef restoreRef
+                    restore $ return 1
+
     evaluate f `catch` \(SomeException e) -> return 0
     -- the evaluation of 'x' is now suspended at point X
-    tid <- block $ forkIO (evaluate f >> return ())
+    tid <- mask $ \restore -> do writeIORef restoreRef restore
+                                 forkIO (evaluate f >> return ())
     killThread tid
     -- now execute the 'unblock' above with a pending exception
     yield
+    writeIORef restoreRef id
     -- should print 1 + 1 = 2
     print f
     
-- 
GitLab


From bcab545325390dc7ca145b9ab2ac9ee1d2b6f0b3 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Tue, 19 Feb 2013 18:47:48 +0000
Subject: [PATCH 200/223] Update a couple of tests to use mask rather than
 block/unblock

---
 tests/concurrent/should_run/T2910.hs | 2 +-
 tests/concurrent/should_run/T4030.hs | 6 +++---
 2 files changed, 4 insertions(+), 4 deletions(-)

diff --git a/tests/concurrent/should_run/T2910.hs b/tests/concurrent/should_run/T2910.hs
index 286700815..76b8d2f1e 100644
--- a/tests/concurrent/should_run/T2910.hs
+++ b/tests/concurrent/should_run/T2910.hs
@@ -2,7 +2,7 @@ import Control.Exception
 import GHC.Conc
   
 main = do
-    t1 <- block $ forkIO yield
+    t1 <- mask $ \_ -> forkIO yield
     t2 <- forkIO $ killThread t1
     threadDelay 100000
     threadStatus t1 >>= print
diff --git a/tests/concurrent/should_run/T4030.hs b/tests/concurrent/should_run/T4030.hs
index 1993bad86..f160dfda8 100644
--- a/tests/concurrent/should_run/T4030.hs
+++ b/tests/concurrent/should_run/T4030.hs
@@ -1,8 +1,8 @@
 module Main where
 
-import Control.Concurrent ( forkIO, killThread )
-import Control.Exception  ( block )
+import Control.Concurrent
+import Control.Exception
 
 main :: IO ()
-main = do tid <- block $ forkIO $ let x = x in x
+main = do tid <- mask $ \_ -> forkIO $ let x = x in x
           killThread tid
-- 
GitLab


From 8c6e8a4c773844ef5cc8ecf4163e30a2bccbd428 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Tue, 19 Feb 2013 18:50:49 +0000
Subject: [PATCH 201/223] Update a few more tests to use mask rather than
 block/unblock

---
 tests/concurrent/should_run/conc069.hs    |  4 ++--
 tests/concurrent/should_run/throwto002.hs | 10 +++++-----
 tests/concurrent/should_run/throwto003.hs |  2 +-
 3 files changed, 8 insertions(+), 8 deletions(-)

diff --git a/tests/concurrent/should_run/conc069.hs b/tests/concurrent/should_run/conc069.hs
index fd757133a..d2947a2b1 100644
--- a/tests/concurrent/should_run/conc069.hs
+++ b/tests/concurrent/should_run/conc069.hs
@@ -6,11 +6,11 @@ main = do
   m <- newEmptyMVar
   forkIO (do stat; putMVar m ())
   takeMVar m
-  block $ forkIO (do stat; putMVar m ())
+  mask $ \_ -> forkIO (do stat; putMVar m ())
   takeMVar m
   forkOS (do stat; putMVar m ())
   takeMVar m
-  block $ forkOS (do stat; putMVar m ())
+  mask $ \_ -> forkOS (do stat; putMVar m ())
   takeMVar m
 
 stat = do
diff --git a/tests/concurrent/should_run/throwto002.hs b/tests/concurrent/should_run/throwto002.hs
index db67c24df..e7fcc3601 100644
--- a/tests/concurrent/should_run/throwto002.hs
+++ b/tests/concurrent/should_run/throwto002.hs
@@ -11,14 +11,14 @@ import Data.IORef
 main = do
   r <- newIORef 0
   rec
-    t1 <- block $ forkIO (thread r t2)
-    t2 <- block $ forkIO (thread r t1)
+    t1 <- mask $ \restore -> forkIO (thread restore r t2)
+    t2 <- mask $ \restore -> forkIO (thread restore r t1)
   threadDelay 1000000
   readIORef r >>= print . (/= 0)
 
-thread r t = run
-  where 
-    run = (unblock $ forever $ do killThread t
+thread restore r t = run
+  where
+    run = (restore $ forever $ do killThread t
                                   i <- atomicModifyIORef r (\i -> (i + 1, i))
                                   evaluate i)
              `catch` \(e::SomeException) -> run
diff --git a/tests/concurrent/should_run/throwto003.hs b/tests/concurrent/should_run/throwto003.hs
index 7a7582f56..8f62fb30d 100644
--- a/tests/concurrent/should_run/throwto003.hs
+++ b/tests/concurrent/should_run/throwto003.hs
@@ -12,5 +12,5 @@ main = do
 
 thread m = run
   where 
-    run = (unblock $ forever $ modifyMVar_ m $ \v -> if v `mod` 2 == 1 then return (v*2) else return (v-1))
+    run = (forever $ modifyMVar_ m $ \v -> if v `mod` 2 == 1 then return (v*2) else return (v-1))
              `catch` \(e::SomeException) -> run
-- 
GitLab


From 74db433339c6e688d7dbd52d5b88a360cae02ab7 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Tue, 19 Feb 2013 19:20:21 +0000
Subject: [PATCH 202/223] Follow the removal of blocked in base

---
 tests/concurrent/should_run/conc069.hs     | 2 +-
 tests/concurrent/should_run/conc069.stdout | 8 ++++----
 2 files changed, 5 insertions(+), 5 deletions(-)

diff --git a/tests/concurrent/should_run/conc069.hs b/tests/concurrent/should_run/conc069.hs
index d2947a2b1..ec2af5db2 100644
--- a/tests/concurrent/should_run/conc069.hs
+++ b/tests/concurrent/should_run/conc069.hs
@@ -15,5 +15,5 @@ main = do
 
 stat = do
   x <- isCurrentThreadBound
-  y <- blocked
+  y <- getMaskingState
   print (x,y)
diff --git a/tests/concurrent/should_run/conc069.stdout b/tests/concurrent/should_run/conc069.stdout
index 240e16e63..0883f133d 100644
--- a/tests/concurrent/should_run/conc069.stdout
+++ b/tests/concurrent/should_run/conc069.stdout
@@ -1,4 +1,4 @@
-(False,False)
-(False,True)
-(True,False)
-(True,True)
+(False,Unmasked)
+(False,MaskedInterruptible)
+(True,Unmasked)
+(True,MaskedInterruptible)
-- 
GitLab


From e8a22acdd2c43ddb1b3d3a0817abbc017b818601 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Wed, 20 Feb 2013 09:16:52 +0000
Subject: [PATCH 203/223] Revert "Update T3279 to use mask rather than block"

This reverts commit a6d80ce5fb2211af8dafc425705fefb316702802.
---
 tests/concurrent/should_run/T3279.hs | 22 ++++++++--------------
 1 file changed, 8 insertions(+), 14 deletions(-)

diff --git a/tests/concurrent/should_run/T3279.hs b/tests/concurrent/should_run/T3279.hs
index 46e9b0367..f47970431 100644
--- a/tests/concurrent/should_run/T3279.hs
+++ b/tests/concurrent/should_run/T3279.hs
@@ -1,30 +1,24 @@
 -- test for #3279
 
-import Data.IORef
 import System.IO.Unsafe
 import GHC.Conc
 import Control.Exception
 
+f :: Int
+f = (1 +) . unsafePerformIO $ do
+        error "foo" `catch` \(SomeException e) -> do
+            myThreadId >>= flip throwTo e
+            -- point X
+            unblock $ return 1
+
 main :: IO ()
 main = do
-    restoreRef <- newIORef id
-
-    let f :: Int
-        f = (1 +) . unsafePerformIO $ do
-                error "foo" `catch` \(SomeException e) -> do
-                    myThreadId >>= flip throwTo e
-                    -- point X
-                    restore <- readIORef restoreRef
-                    restore $ return 1
-
     evaluate f `catch` \(SomeException e) -> return 0
     -- the evaluation of 'x' is now suspended at point X
-    tid <- mask $ \restore -> do writeIORef restoreRef restore
-                                 forkIO (evaluate f >> return ())
+    tid <- block $ forkIO (evaluate f >> return ())
     killThread tid
     -- now execute the 'unblock' above with a pending exception
     yield
-    writeIORef restoreRef id
     -- should print 1 + 1 = 2
     print f
     
-- 
GitLab


From 6272664b9c33ba9b9ac5bdf0c120413266716995 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Wed, 20 Feb 2013 09:19:54 +0000
Subject: [PATCH 204/223] use unsafeUnmask instead of an IORef containing
 restore

This is much closer to how the test originally worked, so it's more
likely that the test is still testing what it was testing before :-)
---
 tests/concurrent/should_run/T3279.hs | 5 +++--
 1 file changed, 3 insertions(+), 2 deletions(-)

diff --git a/tests/concurrent/should_run/T3279.hs b/tests/concurrent/should_run/T3279.hs
index f47970431..a90d38aaa 100644
--- a/tests/concurrent/should_run/T3279.hs
+++ b/tests/concurrent/should_run/T3279.hs
@@ -3,19 +3,20 @@
 import System.IO.Unsafe
 import GHC.Conc
 import Control.Exception
+import GHC.IO (unsafeUnmask)
 
 f :: Int
 f = (1 +) . unsafePerformIO $ do
         error "foo" `catch` \(SomeException e) -> do
             myThreadId >>= flip throwTo e
             -- point X
-            unblock $ return 1
+            unsafeUnmask $ return 1
 
 main :: IO ()
 main = do
     evaluate f `catch` \(SomeException e) -> return 0
     -- the evaluation of 'x' is now suspended at point X
-    tid <- block $ forkIO (evaluate f >> return ())
+    tid <- mask_ $ forkIO (evaluate f >> return ())
     killThread tid
     -- now execute the 'unblock' above with a pending exception
     yield
-- 
GitLab


From ee9acc42e0f698b94f42c3ac5f30d84cae2e679f Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Wed, 20 Feb 2013 09:25:43 +0000
Subject: [PATCH 205/223] small tidyup

---
 tests/concurrent/should_run/conc069.hs | 4 ++--
 1 file changed, 2 insertions(+), 2 deletions(-)

diff --git a/tests/concurrent/should_run/conc069.hs b/tests/concurrent/should_run/conc069.hs
index ec2af5db2..5bf619bec 100644
--- a/tests/concurrent/should_run/conc069.hs
+++ b/tests/concurrent/should_run/conc069.hs
@@ -6,11 +6,11 @@ main = do
   m <- newEmptyMVar
   forkIO (do stat; putMVar m ())
   takeMVar m
-  mask $ \_ -> forkIO (do stat; putMVar m ())
+  mask_ $ forkIO (do stat; putMVar m ())
   takeMVar m
   forkOS (do stat; putMVar m ())
   takeMVar m
-  mask $ \_ -> forkOS (do stat; putMVar m ())
+  mask_ $ forkOS (do stat; putMVar m ())
   takeMVar m
 
 stat = do
-- 
GitLab


From 3663f98c24192a8f6dcbdf225de8f9ffcfa7dd23 Mon Sep 17 00:00:00 2001
From: Simon Marlow <marlowsd@gmail.com>
Date: Wed, 20 Feb 2013 09:26:27 +0000
Subject: [PATCH 206/223] The "unblock" was important here

Because catch implicitly masks the exception handler.
---
 tests/concurrent/should_run/throwto003.hs | 6 +++---
 1 file changed, 3 insertions(+), 3 deletions(-)

diff --git a/tests/concurrent/should_run/throwto003.hs b/tests/concurrent/should_run/throwto003.hs
index 8f62fb30d..37540cc68 100644
--- a/tests/concurrent/should_run/throwto003.hs
+++ b/tests/concurrent/should_run/throwto003.hs
@@ -5,12 +5,12 @@ import Control.Monad
 
 main = do
   m <- newMVar 1
-  t1 <- forkIO $ thread m
+  t1 <- mask $ \restore -> forkIO $ thread restore m
   t2 <- forkIO $ forever $ killThread t1
   threadDelay 1000000
   takeMVar m
 
-thread m = run
+thread restore m = run
   where 
-    run = (forever $ modifyMVar_ m $ \v -> if v `mod` 2 == 1 then return (v*2) else return (v-1))
+    run = (restore $ forever $ modifyMVar_ m $ \v -> if v `mod` 2 == 1 then return (v*2) else return (v-1))
              `catch` \(e::SomeException) -> run
-- 
GitLab


From 572cd7091e7e2eee8475432cb0a356e5357269d3 Mon Sep 17 00:00:00 2001
From: Jose Pedro Magalhaes <jpm@cs.ox.ac.uk>
Date: Thu, 21 Feb 2013 09:40:47 +0000
Subject: [PATCH 207/223] Test #7710

---
 tests/deriving/should_compile/T7710.hs | 21 +++++++++++++++++++++
 tests/deriving/should_compile/all.T    |  1 +
 2 files changed, 22 insertions(+)
 create mode 100644 tests/deriving/should_compile/T7710.hs

diff --git a/tests/deriving/should_compile/T7710.hs b/tests/deriving/should_compile/T7710.hs
new file mode 100644
index 000000000..5375c2c0e
--- /dev/null
+++ b/tests/deriving/should_compile/T7710.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE TypeSynonymInstances #-}
+{-# LANGUAGE AutoDeriveTypeable #-}
+{-# LANGUAGE TypeFamilies #-}
+
+module T7710 where
+
+import Data.Typeable
+
+
+type T = Int
+type family F a
+type instance F Int = Int
+data family D a
+data instance D Int = DInt
+data instance D Float = DFloat
+
+test = [ typeRep ([] :: [T])
+       , typeRep ([] :: [F Int])
+       , typeRep (Proxy :: Proxy D)
+       , typeRep ([] :: [D Int]) ]
diff --git a/tests/deriving/should_compile/all.T b/tests/deriving/should_compile/all.T
index 5e9af5ee4..b2355f6ac 100644
--- a/tests/deriving/should_compile/all.T
+++ b/tests/deriving/should_compile/all.T
@@ -36,3 +36,4 @@ test('T1133',
      extra_clean(['T1133.o-boot', 'T1133.hi-boot']),
      run_command,
      ['$MAKE --no-print-directory -s T1133'])
+test('T7710', normal, compile, [''])
\ No newline at end of file
-- 
GitLab


From cf17d9058aaea5cf4c2e8720bc1c489ede473f0c Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 23 Feb 2013 19:13:49 +0000
Subject: [PATCH 208/223] Add a test for #7671

---
 tests/parser/unicode/T7671.hs | 8 ++++++++
 tests/parser/unicode/all.T    | 1 +
 2 files changed, 9 insertions(+)
 create mode 100644 tests/parser/unicode/T7671.hs

diff --git a/tests/parser/unicode/T7671.hs b/tests/parser/unicode/T7671.hs
new file mode 100644
index 000000000..4eb6a4b50
--- /dev/null
+++ b/tests/parser/unicode/T7671.hs
@@ -0,0 +1,8 @@
+
+{-# LANGUAGE EmptyDataDecls #-}
+-- ^ a U+00A0 no-break space
+module Foo where
+
+v = 5 +  3
+--     ^ a U+00A0 no-break space
+
diff --git a/tests/parser/unicode/all.T b/tests/parser/unicode/all.T
index c8ca793f7..71db26ff5 100644
--- a/tests/parser/unicode/all.T
+++ b/tests/parser/unicode/all.T
@@ -20,3 +20,4 @@ test('T1744', normal, compile_and_run, [''])
 test('T1103', normal, compile, [''])
 test('T2302', only_ways(['normal']), compile_fail, [''])
 test('T4373', normal, compile, [''])
+test('T7671', expect_broken(7671), compile, [''])
-- 
GitLab


From 6e9328926ad7c3a36beb390fafe9f82249a91221 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sat, 23 Feb 2013 22:45:45 +0000
Subject: [PATCH 209/223] Add a test for #6037

---
 tests/driver/Makefile     | 4 ++++
 tests/driver/T6037.hs     | 5 +++++
 tests/driver/T6037.stderr | 5 +++++
 tests/driver/all.T        | 2 ++
 4 files changed, 16 insertions(+)
 create mode 100644 tests/driver/T6037.hs
 create mode 100644 tests/driver/T6037.stderr

diff --git a/tests/driver/Makefile b/tests/driver/Makefile
index 5152061f2..e4120023e 100644
--- a/tests/driver/Makefile
+++ b/tests/driver/Makefile
@@ -536,3 +536,7 @@ T7130:
 T7563:
 	-"$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) -C T7563.hs
 
+.PHONY: T6037
+T6037:
+	-LC_ALL=C "$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) -c T6037.hs
+
diff --git a/tests/driver/T6037.hs b/tests/driver/T6037.hs
new file mode 100644
index 000000000..56aa03462
--- /dev/null
+++ b/tests/driver/T6037.hs
@@ -0,0 +1,5 @@
+
+module T6037 where
+
+fóo :: Int
+fóo = ()
diff --git a/tests/driver/T6037.stderr b/tests/driver/T6037.stderr
new file mode 100644
index 000000000..3059288d1
--- /dev/null
+++ b/tests/driver/T6037.stderr
@@ -0,0 +1,5 @@
+
+T6037.hs:5:7:
+    Couldn't match expected type `Int' with actual type `()'
+    In the expression: ()
+    In an equation for `f?o': f?o = ()
diff --git a/tests/driver/all.T b/tests/driver/all.T
index 0020f1836..4c81ba5cb 100644
--- a/tests/driver/all.T
+++ b/tests/driver/all.T
@@ -364,4 +364,6 @@ test('T7060',
 test('T7130', normal, compile_fail, ['-fflul-laziness'])
 test('T7563', when(unregisterised(), skip), run_command,
      ['$MAKE -s --no-print-directory T7563'])
+test('T6037', expect_broken(6037), run_command,
+     ['$MAKE -s --no-print-directory T6037'])
 
-- 
GitLab


From bbee43d720c2bb047fee7cc75c23272df83851f9 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 24 Feb 2013 14:48:43 +0000
Subject: [PATCH 210/223] Update outputs following the unicode quote change in
 GHC's output

---
 .../annotations/should_fail/annfail01.stderr  |   4 +-
 .../annotations/should_fail/annfail02.stderr  |   4 +-
 .../annotations/should_fail/annfail03.stderr  |   5 +-
 .../annotations/should_fail/annfail04.stderr  |   5 +-
 .../annotations/should_fail/annfail06.stderr  |   5 +-
 .../annotations/should_fail/annfail07.stderr  |   4 +-
 .../annotations/should_fail/annfail08.stderr  |   2 +-
 .../annotations/should_fail/annfail09.stderr  |   4 +-
 .../annotations/should_fail/annfail10.stderr  |  18 +--
 .../annotations/should_fail/annfail11.stderr  |   4 +-
 tests/arrows/should_fail/T5380.stderr         |  12 +-
 tests/arrows/should_fail/arrowfail001.stderr  |   4 +-
 tests/arrows/should_fail/arrowfail002.stderr  |   2 +-
 tests/arrows/should_fail/arrowfail004.stderr  |   2 +-
 .../deSugar/should_compile/GadtOverlap.stderr |   6 +-
 tests/deSugar/should_compile/T2395.stderr     |   6 +-
 tests/deSugar/should_compile/T5117.stderr     |   8 +-
 tests/deSugar/should_compile/ds002.stderr-ghc |  16 +--
 tests/deSugar/should_compile/ds003.stderr-ghc |  10 +-
 tests/deSugar/should_compile/ds019.stderr-ghc |  12 +-
 tests/deSugar/should_compile/ds020.stderr-ghc |  28 ++--
 tests/deSugar/should_compile/ds022.stderr-ghc |  10 +-
 tests/deSugar/should_compile/ds041.stderr-ghc |  10 +-
 tests/deSugar/should_compile/ds051.stderr-ghc |  18 +--
 tests/deSugar/should_compile/ds053.stderr-ghc |   2 +-
 tests/deSugar/should_compile/ds056.stderr     |   6 +-
 tests/deriving/should_compile/drv021.stderr   |   6 +-
 tests/deriving/should_fail/T1133A.stderr      |   6 +-
 tests/deriving/should_fail/T2394.stderr       |  12 +-
 tests/deriving/should_fail/T2604.stderr       |  20 +--
 tests/deriving/should_fail/T2701.stderr       |  10 +-
 tests/deriving/should_fail/T2721.stderr       |  12 +-
 tests/deriving/should_fail/T3101.stderr       |  12 +-
 tests/deriving/should_fail/T3833.stderr       |   6 +-
 tests/deriving/should_fail/T3834.stderr       |   6 +-
 tests/deriving/should_fail/T4528.stderr       |  14 +-
 tests/deriving/should_fail/T5287.stderr       |  20 +--
 tests/deriving/should_fail/T5478.stderr       |  10 +-
 tests/deriving/should_fail/T5686.stderr       |  10 +-
 tests/deriving/should_fail/T5922.stderr       |   8 +-
 .../drvfail-foldable-traversable1.stderr      |  12 +-
 .../should_fail/drvfail-functor1.stderr       |  10 +-
 .../should_fail/drvfail-functor2.stderr       |  24 ++--
 tests/deriving/should_fail/drvfail005.stderr  |  10 +-
 tests/deriving/should_fail/drvfail009.stderr  |  46 +++---
 tests/deriving/should_fail/drvfail011.stderr  |  10 +-
 tests/deriving/should_fail/drvfail014.stderr  |  18 +--
 tests/deriving/should_fail/drvfail015.stderr  |  26 ++--
 tests/driver/T1372/T1372.stderr               |   2 +-
 tests/driver/T5147/T5147.stderr               |   4 +-
 tests/driver/T6037.stderr                     |   4 +-
 tests/driver/bug1677/bug1677.stderr           |   4 +-
 tests/driver/driver063.stderr                 |   2 +-
 tests/driver/recomp001/recomp001.stderr       |   2 +-
 tests/driver/recomp005/recomp005.stderr       |   4 +-
 tests/driver/werror.stderr                    |  10 +-
 tests/gadt/T3163.stderr                       |  10 +-
 tests/gadt/T3169.stderr                       |   4 +-
 tests/gadt/T3651.stderr                       |  26 ++--
 tests/gadt/T7293.stderr                       |   6 +-
 tests/gadt/T7294.stderr                       |   6 +-
 tests/gadt/gadt-escape1.stderr                |  38 ++---
 tests/gadt/gadt10.stderr                      |  14 +-
 tests/gadt/gadt11.stderr                      |  12 +-
 tests/gadt/gadt13.stderr                      |  32 ++---
 tests/gadt/gadt21.stderr                      |  15 +-
 tests/gadt/gadt7.stderr                       |  40 +++---
 tests/gadt/gadtSyntaxFail001.stderr           |  12 +-
 tests/gadt/gadtSyntaxFail002.stderr           |  12 +-
 tests/gadt/gadtSyntaxFail003.stderr           |  12 +-
 tests/gadt/lazypat.stderr                     |   2 +-
 tests/gadt/records-fail1.stderr               |  10 +-
 tests/gadt/rw.stderr                          |  14 +-
 tests/generics/GenCannotDoRep0.stderr         |  16 +--
 tests/generics/GenCannotDoRep1.stderr         |  16 +--
 tests/generics/GenCannotDoRep1_0.stderr       |   4 +-
 tests/generics/GenCannotDoRep1_1.stderr       |   4 +-
 tests/generics/GenCannotDoRep1_2.stderr       |   4 +-
 tests/generics/GenCannotDoRep1_3.stderr       |   6 +-
 tests/generics/GenCannotDoRep1_4.stderr       |   6 +-
 tests/generics/GenCannotDoRep1_5.stderr       |   6 +-
 tests/generics/GenCannotDoRep1_6.stderr       |   6 +-
 tests/generics/GenCannotDoRep1_7.stderr       |   4 +-
 tests/generics/GenCannotDoRep1_8.stderr       |   6 +-
 tests/generics/GenCannotDoRep2.stderr         |   4 +-
 tests/generics/GenShouldFail0.stderr          |   4 +-
 tests/generics/GenShouldFail1_0.stderr        |   4 +-
 .../ghc-api/apirecomp001/apirecomp001.stderr  |  20 +--
 tests/ghc-e/should_run/T2636.stderr           |   2 +-
 tests/ghci.debugger/scripts/break003.stderr   |   2 +-
 tests/ghci.debugger/scripts/break006.stderr   |  20 +--
 tests/ghci.debugger/scripts/break019.stderr   |   4 +-
 tests/ghci.debugger/scripts/dynbrk001.stderr  |   2 +-
 tests/ghci.debugger/scripts/dynbrk001.stdout  |   2 +-
 tests/ghci.debugger/scripts/print019.stderr   |   4 +-
 tests/ghci.debugger/scripts/print020.stderr   |   4 +-
 tests/ghci/prog006/prog006.stderr             |   2 +-
 tests/ghci/prog009/ghci.prog009.stderr        |   4 +-
 tests/ghci/prog012/prog012.stderr             |   2 +-
 tests/ghci/scripts/T2452.stderr               |   2 +-
 tests/ghci/scripts/T2816.stderr               |   2 +-
 tests/ghci/scripts/T4127a.stderr              |   2 +-
 tests/ghci/scripts/T5545.stdout               |   2 +-
 tests/ghci/scripts/T5564.stderr               |   8 +-
 tests/ghci/scripts/T5836.stderr               |   2 +-
 tests/ghci/scripts/T5979.stderr               |   2 +-
 tests/ghci/scripts/T6007.stderr               |   4 +-
 tests/ghci/scripts/ghci008.stdout             |  16 +--
 tests/ghci/scripts/ghci011.stdout             |  42 +++---
 tests/ghci/scripts/ghci020.stdout             |   6 +-
 tests/ghci/scripts/ghci021.stderr             |   2 +-
 tests/ghci/scripts/ghci034.stderr             |   2 +-
 tests/ghci/scripts/ghci036.stderr             |  16 +--
 tests/ghci/scripts/ghci038.stderr             |   4 +-
 tests/ghci/scripts/ghci044.stderr             |   4 +-
 tests/ghci/scripts/ghci047.stderr             |   8 +-
 tests/ghci/scripts/ghci048.stderr             |   4 +-
 tests/ghci/scripts/ghci050.stderr             |   8 +-
 tests/ghci/scripts/ghci051.stderr             |   4 +-
 tests/ghci/scripts/ghci052.stderr             |  30 ++--
 tests/ghci/scripts/ghci053.stderr             |  16 +--
 tests/ghci/scripts/ghci057.stderr             |  34 ++---
 .../haddock_examples/haddock.Test.stderr      |   8 +-
 .../should_compile/Class3.stderr              |   6 +-
 .../should_compile/Simple14.stderr            |  10 +-
 .../should_compile/Simple2.stderr             |  60 ++++----
 .../should_fail/DerivUnsatFam.stderr          |  10 +-
 .../should_fail/ExtraTcsUntch.stderr          |   2 +-
 .../should_fail/GADTwrong1.stderr             |  42 +++---
 .../should_fail/NoMatchErr.stderr             |  26 ++--
 .../should_fail/NotRelaxedExamples.stderr     |  36 ++---
 .../should_fail/Overlap10.stderr              |  16 +--
 .../should_fail/Overlap11.stderr              |  16 +--
 .../indexed-types/should_fail/Overlap5.stderr |  12 +-
 .../indexed-types/should_fail/Overlap6.stderr |   6 +-
 .../indexed-types/should_fail/Overlap9.stderr |   4 +-
 .../should_fail/SimpleFail12.stderr           |   8 +-
 .../should_fail/SimpleFail13.stderr           |  16 +--
 .../should_fail/SimpleFail14.stderr           |  12 +-
 .../should_fail/SimpleFail15.stderr           |   2 +-
 .../should_fail/SimpleFail16.stderr           |  18 +--
 .../should_fail/SimpleFail1a.stderr           |   8 +-
 .../should_fail/SimpleFail1b.stderr           |   8 +-
 .../should_fail/SimpleFail2a.stderr           |   6 +-
 .../should_fail/SimpleFail3a.stderr           |  10 +-
 .../should_fail/SimpleFail4.stderr            |   6 +-
 .../should_fail/SimpleFail5a.stderr           |   6 +-
 .../should_fail/SimpleFail5b.stderr           |   4 +-
 .../should_fail/SimpleFail6.stderr            |   2 +-
 .../should_fail/SimpleFail7.stderr            |   8 +-
 .../should_fail/SimpleFail8.stderr            |  12 +-
 tests/indexed-types/should_fail/T1897b.stderr |  28 ++--
 tests/indexed-types/should_fail/T1900.stderr  |  26 ++--
 tests/indexed-types/should_fail/T2157.stderr  |   8 +-
 tests/indexed-types/should_fail/T2203a.stderr |   4 +-
 tests/indexed-types/should_fail/T2239.stderr  |  56 ++++----
 tests/indexed-types/should_fail/T2334A.stderr |  12 +-
 tests/indexed-types/should_fail/T2544.stderr  |  56 ++++----
 tests/indexed-types/should_fail/T2627b.stderr |  16 +--
 tests/indexed-types/should_fail/T2664.stderr  |  46 +++---
 tests/indexed-types/should_fail/T2693.stderr  |  86 +++++------
 tests/indexed-types/should_fail/T3092.stderr  |  20 +--
 tests/indexed-types/should_fail/T3330a.stderr |  26 ++--
 tests/indexed-types/should_fail/T3330c.stderr |   6 +-
 tests/indexed-types/should_fail/T3440.stderr  |  10 +-
 tests/indexed-types/should_fail/T4093a.stderr |   6 +-
 tests/indexed-types/should_fail/T4093b.stderr |   6 +-
 tests/indexed-types/should_fail/T4099.stderr  |  46 +++---
 tests/indexed-types/should_fail/T4174.stderr  |   4 +-
 tests/indexed-types/should_fail/T4179.stderr  |   6 +-
 tests/indexed-types/should_fail/T4272.stderr  |  10 +-
 tests/indexed-types/should_fail/T4485.stderr  |  60 ++++----
 tests/indexed-types/should_fail/T5439.stderr  |  56 ++++----
 tests/indexed-types/should_fail/T5515.stderr  |   4 +-
 tests/indexed-types/should_fail/T5934.stderr  |  14 +-
 tests/indexed-types/should_fail/T6123.stderr  |  14 +-
 tests/indexed-types/should_fail/T7010.stderr  |   6 +-
 tests/indexed-types/should_fail/T7194.stderr  |   8 +-
 tests/indexed-types/should_fail/T7354.stderr  |   4 +-
 tests/indexed-types/should_fail/T7354a.stderr |   6 +-
 tests/indexed-types/should_fail/T7536.stderr  |   4 +-
 .../should_fail/TyFamArity1.stderr            |   8 +-
 .../should_fail/TyFamArity2.stderr            |   8 +-
 .../should_fail/TyFamUndec.stderr             |  36 ++---
 tests/mdo/should_fail/mdofail001.stderr       |   4 +-
 tests/mdo/should_fail/mdofail002.stderr       |   2 +-
 tests/mdo/should_fail/mdofail003.stderr       |   2 +-
 tests/module/T414.stderr                      |   2 +-
 tests/module/mod1.stderr                      |   2 +-
 tests/module/mod10.stderr                     |   2 +-
 tests/module/mod101.stderr                    |   4 +-
 tests/module/mod102.stderr                    |   4 +-
 tests/module/mod110.stderr                    |  10 +-
 tests/module/mod114.stderr                    |   2 +-
 tests/module/mod116.stderr                    |   2 +-
 tests/module/mod120.stderr                    |   2 +-
 tests/module/mod121.stderr                    |   4 +-
 tests/module/mod122.stderr                    |   2 +-
 tests/module/mod123.stderr                    |   2 +-
 tests/module/mod124.stderr                    |   2 +-
 tests/module/mod125.stderr                    |   2 +-
 tests/module/mod126.stderr                    |   2 +-
 tests/module/mod127.stderr                    |   2 +-
 tests/module/mod128.stderr-ghc                |   2 +-
 tests/module/mod130.stderr                    |   2 +-
 tests/module/mod131.stderr                    |  10 +-
 tests/module/mod132.stderr                    |   2 +-
 tests/module/mod134.stderr                    |   8 +-
 tests/module/mod136.stderr                    |   6 +-
 tests/module/mod138.stderr                    |   2 +-
 tests/module/mod14.stderr-ghc                 |   5 +-
 tests/module/mod142.stderr                    |   8 +-
 tests/module/mod143.stderr                    |   8 +-
 tests/module/mod144.stderr                    |   8 +-
 tests/module/mod145.stderr                    |   8 +-
 tests/module/mod146.stderr                    |   8 +-
 tests/module/mod147.stderr                    |   2 +-
 tests/module/mod150.stderr                    |  10 +-
 tests/module/mod151.stderr                    |  10 +-
 tests/module/mod152.stderr                    |  20 +--
 tests/module/mod153.stderr                    |  10 +-
 tests/module/mod155.stderr                    |  10 +-
 tests/module/mod158.stderr                    |   2 +-
 tests/module/mod160.stderr                    |   4 +-
 tests/module/mod161.stderr                    |   2 +-
 tests/module/mod164.stderr                    |  10 +-
 tests/module/mod165.stderr                    |   8 +-
 tests/module/mod17.stderr                     |   2 +-
 tests/module/mod174.stderr                    |   2 +-
 tests/module/mod176.stderr                    |   6 +-
 tests/module/mod177.stderr                    |   8 +-
 tests/module/mod178.stderr                    |   4 +-
 tests/module/mod18.stderr                     |   2 +-
 tests/module/mod180.stderr                    |   4 +-
 tests/module/mod19.stderr                     |   4 +-
 tests/module/mod2.stderr                      |   2 +-
 tests/module/mod20.stderr                     |   2 +-
 tests/module/mod21.stderr                     |   2 +-
 tests/module/mod22.stderr                     |   2 +-
 tests/module/mod23.stderr                     |   2 +-
 tests/module/mod24.stderr                     |   2 +-
 tests/module/mod25.stderr                     |   2 +-
 tests/module/mod26.stderr                     |   2 +-
 tests/module/mod29.stderr                     |   2 +-
 tests/module/mod3.stderr                      |   2 +-
 tests/module/mod36.stderr                     |   2 +-
 tests/module/mod38.stderr                     |   2 +-
 tests/module/mod4.stderr                      |   2 +-
 tests/module/mod40.stderr                     |   4 +-
 tests/module/mod41.stderr                     |   4 +-
 tests/module/mod42.stderr                     |   4 +-
 tests/module/mod43.stderr                     |  10 +-
 tests/module/mod45.stderr                     |   2 +-
 tests/module/mod46.stderr                     |   2 +-
 tests/module/mod47.stderr                     |   2 +-
 tests/module/mod49.stderr                     |   2 +-
 tests/module/mod5.stderr-ghc                  |   4 +-
 tests/module/mod50.stderr                     |   2 +-
 tests/module/mod53.stderr                     |  10 +-
 tests/module/mod55.stderr                     |  12 +-
 tests/module/mod56.stderr                     |  16 +--
 tests/module/mod59.stderr                     |   2 +-
 tests/module/mod60.stderr                     |   4 +-
 tests/module/mod61.stderr                     |   2 +-
 tests/module/mod62.stderr                     |   4 +-
 tests/module/mod63.stderr                     |   2 +-
 tests/module/mod66.stderr                     |   2 +-
 tests/module/mod67.stderr                     |   2 +-
 tests/module/mod68.stderr                     |  10 +-
 tests/module/mod7.stderr                      |   2 +-
 tests/module/mod72.stderr                     |   2 +-
 tests/module/mod73.stderr                     |   8 +-
 tests/module/mod74.stderr                     |   2 +-
 tests/module/mod77.stderr                     |   2 +-
 tests/module/mod79.stderr                     |   2 +-
 tests/module/mod80.stderr                     |   2 +-
 tests/module/mod81.stderr                     |   2 +-
 tests/module/mod87.stderr                     |   2 +-
 tests/module/mod88.stderr                     |   2 +-
 tests/module/mod89.stderr                     |   2 +-
 tests/module/mod9.stderr                      |   2 +-
 tests/module/mod90.stderr                     |   8 +-
 tests/module/mod91.stderr                     |   2 +-
 tests/module/mod97.stderr                     |   2 +-
 .../should_fail/overloadedlistsfail01.stderr  |  32 ++---
 .../should_fail/overloadedlistsfail02.stderr  |   6 +-
 .../should_fail/overloadedlistsfail03.stderr  |   9 +-
 .../should_fail/overloadedlistsfail04.stderr  |  12 +-
 .../should_fail/overloadedlistsfail05.stderr  |   8 +-
 .../should_fail/overloadedlistsfail06.stderr  |   7 +-
 tests/parser/should_compile/T2245.stderr      |  54 +++----
 tests/parser/should_compile/T3303.stderr      |   2 +-
 .../parser/should_compile/read014.stderr-ghc  |  40 +++---
 tests/parser/should_fail/T3811d.stderr        |   8 +-
 tests/parser/should_fail/readFail001.stderr   |  20 +--
 tests/parser/should_fail/readFail008.stderr   |   6 +-
 tests/parser/should_fail/readFail016.stderr   |   2 +-
 tests/parser/should_fail/readFail021.stderr   |   3 +-
 tests/parser/should_fail/readFail023.stderr   |   4 +-
 tests/parser/should_fail/readFail025.stderr   |   8 +-
 tests/parser/should_fail/readFail035.stderr   |   8 +-
 tests/parser/should_fail/readFail036.stderr   |   4 +-
 tests/parser/should_fail/readFail037.stderr   |   4 +-
 tests/parser/should_fail/readFail039.stderr   |  12 +-
 tests/parser/should_fail/readFail041.stderr   |   4 +-
 tests/parser/should_fail/readFail042.stderr   |   4 +-
 tests/parser/should_fail/readFail043.stderr   |  14 +-
 tests/parser/should_fail/readFail046.stderr   |   2 +-
 tests/parser/unicode/T2302.stderr             |   2 +-
 tests/perf/compiler/parsing001.stderr         |   2 +-
 tests/plugins/plugins03.stderr                |   3 +-
 tests/plugins/plugins04.stderr                |   2 +-
 tests/polykinds/PolyKinds02.stderr            |   6 +-
 tests/polykinds/PolyKinds04.stderr            |  12 +-
 tests/polykinds/PolyKinds06.stderr            |  10 +-
 tests/polykinds/PolyKinds07.stderr            |  14 +-
 tests/polykinds/T5716.stderr                  |   8 +-
 tests/polykinds/T5716a.stderr                 |  14 +-
 tests/polykinds/T6021.stderr                  |   8 +-
 tests/polykinds/T6039.stderr                  |   4 +-
 tests/polykinds/T6054.stderr                  |   6 +-
 tests/polykinds/T6129.stderr                  |  14 +-
 tests/polykinds/T7053.stderr                  |  16 +--
 tests/polykinds/T7151.stderr                  |   2 +-
 tests/polykinds/T7224.stderr                  |   6 +-
 tests/polykinds/T7230.stderr                  |   6 +-
 tests/polykinds/T7278.stderr                  |   4 +-
 tests/polykinds/T7328.stderr                  |   8 +-
 tests/polykinds/T7341.stderr                  |  12 +-
 tests/polykinds/T7404.stderr                  |   4 +-
 tests/polykinds/T7433.stderr                  |   6 +-
 tests/polykinds/T7438.stderr                  |  12 +-
 tests/polykinds/T7594.stderr                  |  10 +-
 tests/programs/hs-boot/hs-boot.stderr         |   2 +-
 tests/quasiquotation/T3953.stderr             |   2 +-
 tests/rebindable/rebindable6.stderr           | 134 +++++++++---------
 tests/rename/prog002/rename.prog002.stderr    |   2 +-
 tests/rename/prog003/rename.prog003.stderr    |   2 +-
 tests/rename/should_compile/T1789.stderr      |  16 +--
 tests/rename/should_compile/T1972.stderr      |  16 +--
 tests/rename/should_compile/T3262.stderr-ghc  |  12 +-
 tests/rename/should_compile/T3371.stderr      |   2 +-
 tests/rename/should_compile/T3449.stderr      |   2 +-
 tests/rename/should_compile/T3823.stderr      |   6 +-
 tests/rename/should_compile/T4489.stderr      |  12 +-
 tests/rename/should_compile/T5331.stderr      |  26 ++--
 tests/rename/should_compile/T5334.stderr      |  12 +-
 tests/rename/should_compile/T5867.stderr      |   4 +-
 tests/rename/should_compile/T7145b.stderr     |   2 +-
 tests/rename/should_compile/T7167.stderr      |   2 +-
 tests/rename/should_compile/T7336.stderr      |   6 +-
 tests/rename/should_compile/mc10.stderr-ghc   |   2 +-
 tests/rename/should_compile/rn037.stderr-ghc  |   8 +-
 tests/rename/should_compile/rn039.stderr-ghc  |   8 +-
 tests/rename/should_compile/rn040.stderr-ghc  |   4 +-
 tests/rename/should_compile/rn041.stderr-ghc  |   6 +-
 tests/rename/should_compile/rn046.stderr-ghc  |  12 +-
 tests/rename/should_compile/rn047.stderr-ghc  |   2 +-
 tests/rename/should_compile/rn050.stderr      |   4 +-
 tests/rename/should_compile/rn063.stderr      |   4 +-
 tests/rename/should_compile/rn064.stderr      |   6 +-
 tests/rename/should_compile/rn066.stderr      |   4 +-
 tests/rename/should_fail/T1595a.stderr        |   2 +-
 tests/rename/should_fail/T2310.stderr         |   6 +-
 tests/rename/should_fail/T2723.stderr         |   6 +-
 tests/rename/should_fail/T2901.stderr         |   4 +-
 tests/rename/should_fail/T2993.stderr         |   2 +-
 tests/rename/should_fail/T3265.stderr         |   4 +-
 tests/rename/should_fail/T5211.stderr         |   4 +-
 tests/rename/should_fail/T5281.stderr         |   2 +-
 tests/rename/should_fail/T5372.stderr         |   6 +-
 tests/rename/should_fail/T5385.stderr         |   8 +-
 tests/rename/should_fail/T5533.stderr         |   2 +-
 tests/rename/should_fail/T5589.stderr         |  10 +-
 tests/rename/should_fail/T5657.stderr         |   2 +-
 tests/rename/should_fail/T5745.stderr         |   2 +-
 tests/rename/should_fail/T5892a.stderr        |   4 +-
 tests/rename/should_fail/T5892b.stderr        |   8 +-
 tests/rename/should_fail/T7164.stderr         |   2 +-
 tests/rename/should_fail/T7338.stderr         |   2 +-
 tests/rename/should_fail/T7338a.stderr        |   4 +-
 tests/rename/should_fail/T7454.stderr         |   2 +-
 tests/rename/should_fail/mc13.stderr          |   2 +-
 tests/rename/should_fail/mc14.stderr          |   2 +-
 tests/rename/should_fail/rn_dup.stderr        |   8 +-
 tests/rename/should_fail/rnfail001.stderr     |   4 +-
 tests/rename/should_fail/rnfail002.stderr     |   2 +-
 tests/rename/should_fail/rnfail003.stderr     |   2 +-
 tests/rename/should_fail/rnfail004.stderr     |   4 +-
 tests/rename/should_fail/rnfail007.stderr     |   2 +-
 tests/rename/should_fail/rnfail008.stderr     |   2 +-
 tests/rename/should_fail/rnfail009.stderr     |   2 +-
 tests/rename/should_fail/rnfail010.stderr     |   2 +-
 tests/rename/should_fail/rnfail011.stderr     |   2 +-
 tests/rename/should_fail/rnfail012.stderr     |   2 +-
 tests/rename/should_fail/rnfail013.stderr     |   2 +-
 tests/rename/should_fail/rnfail015.stderr     |   2 +-
 tests/rename/should_fail/rnfail017.stderr     |   4 +-
 tests/rename/should_fail/rnfail018.stderr     |   8 +-
 tests/rename/should_fail/rnfail019.stderr     |   6 +-
 tests/rename/should_fail/rnfail022.stderr     |   4 +-
 tests/rename/should_fail/rnfail023.stderr     |   6 +-
 tests/rename/should_fail/rnfail024.stderr     |   4 +-
 tests/rename/should_fail/rnfail025.stderr     |   2 +-
 tests/rename/should_fail/rnfail026.stderr     |   8 +-
 tests/rename/should_fail/rnfail027.stderr     |   2 +-
 tests/rename/should_fail/rnfail029.stderr     |  10 +-
 tests/rename/should_fail/rnfail030.stderr     |   2 +-
 tests/rename/should_fail/rnfail031.stderr     |   2 +-
 tests/rename/should_fail/rnfail032.stderr     |   8 +-
 tests/rename/should_fail/rnfail033.stderr     |   8 +-
 tests/rename/should_fail/rnfail034.stderr     |   4 +-
 tests/rename/should_fail/rnfail035.stderr     |   2 +-
 tests/rename/should_fail/rnfail040.stderr     |  10 +-
 tests/rename/should_fail/rnfail041.stderr     |   4 +-
 tests/rename/should_fail/rnfail043.stderr     |   2 +-
 tests/rename/should_fail/rnfail044.stderr     |  10 +-
 tests/rename/should_fail/rnfail045.stderr     |   4 +-
 tests/rename/should_fail/rnfail048.stderr     |  18 +--
 tests/rename/should_fail/rnfail049.stderr     |   2 +-
 tests/rename/should_fail/rnfail050.stderr     |   2 +-
 tests/rename/should_fail/rnfail053.stderr     |   2 +-
 tests/rename/should_fail/rnfail054.stderr     |   4 +-
 tests/rename/should_fail/rnfail055.stderr     |  20 +--
 tests/rename/should_fail/rnfail057.stderr     |   2 +-
 tests/safeHaskell/flags/SafeFlags22.stderr    |   2 +-
 tests/safeHaskell/flags/SafeFlags23.stderr    |   2 +-
 tests/safeHaskell/flags/SafeFlags25.stderr    |   2 +-
 tests/safeHaskell/flags/SafeFlags26.stderr    |   2 +-
 tests/safeHaskell/ghci/p10.stderr             |   2 +-
 tests/safeHaskell/ghci/p13.stderr             |   4 +-
 tests/safeHaskell/ghci/p15.stderr             |   8 +-
 tests/safeHaskell/ghci/p16.stderr             |  12 +-
 tests/safeHaskell/ghci/p4.stderr              |   6 +-
 tests/safeHaskell/ghci/p6.stderr              |   4 +-
 tests/safeHaskell/ghci/p9.stderr              |   2 +-
 .../safeInfered/UnsafeInfered07.stderr        |   8 +-
 .../safeInfered/UnsafeInfered11.stderr        |   2 +-
 .../safeInfered/UnsafeInfered12.stderr        |   2 +-
 .../safeLanguage/SafeLang07.stderr            |   6 +-
 .../safeLanguage/SafeLang10.stderr            |   4 +-
 tests/safeHaskell/unsafeLibs/Dep01.stderr     |   2 +-
 tests/safeHaskell/unsafeLibs/Dep02.stderr     |   2 +-
 tests/simplCore/should_compile/T4398.stderr   |   7 +-
 tests/simplCore/should_compile/T5359b.stderr  |   2 +-
 .../should_compile/T6082-RULE.stderr          |   8 +-
 .../simplCore/should_compile/simpl016.stderr  |   6 +-
 .../simplCore/should_compile/simpl017.stderr  |  36 ++---
 .../simplCore/should_compile/simpl020.stderr  |  12 +-
 tests/th/T2597b.stderr                        |   2 +-
 tests/th/T2674.stderr                         |   2 +-
 tests/th/T2713.stderr                         |   8 +-
 tests/th/T3177a.stderr                        |  10 +-
 tests/th/T3395.stderr                         |   7 +-
 tests/th/T5358.stderr                         |  34 ++---
 tests/th/T5795.stderr                         |   4 +-
 tests/th/T5971.stderr                         |   2 +-
 tests/th/T6114.stderr                         |   4 +-
 tests/th/T7276.stderr                         |   4 +-
 tests/th/T7276a.stdout                        |   8 +-
 tests/th/TH_1tuple.stderr                     |   2 +-
 tests/th/TH_dupdecl.stderr                    |   2 +-
 tests/th/TH_runIO.stderr                      |   4 +-
 tests/th/TH_spliceD1.stderr                   |   4 +-
 tests/th/TH_unresolvedInfix2.stderr           |   8 +-
 tests/typecheck/bug1465/bug1465.stderr        |   6 +-
 .../prog001/typecheck.prog001.stderr-ghc      |   7 +-
 tests/typecheck/should_compile/FD1.stderr     |   6 +-
 tests/typecheck/should_compile/FD2.stderr     |  10 +-
 tests/typecheck/should_compile/FD3.stderr     |  10 +-
 tests/typecheck/should_compile/T2494.stderr   |  20 +--
 tests/typecheck/should_compile/T2497.stderr   |   2 +-
 tests/typecheck/should_compile/T5481.stderr   |   4 +-
 tests/typecheck/should_compile/T7050.stderr   |   6 +-
 tests/typecheck/should_compile/T7562.stderr   |   6 +-
 tests/typecheck/should_compile/holes.stderr   |  24 ++--
 tests/typecheck/should_compile/holes2.stderr  |  20 +--
 tests/typecheck/should_compile/holes3.stderr  |  24 ++--
 tests/typecheck/should_compile/tc056.stderr   |   6 +-
 .../typecheck/should_compile/tc115.stderr-ghc |   6 +-
 .../typecheck/should_compile/tc116.stderr-ghc |   6 +-
 .../typecheck/should_compile/tc125.stderr-ghc |  30 ++--
 .../typecheck/should_compile/tc126.stderr-ghc |  12 +-
 tests/typecheck/should_compile/tc141.stderr   |  14 +-
 .../typecheck/should_compile/tc161.stderr-ghc |   6 +-
 tests/typecheck/should_compile/tc167.stderr   |   4 +-
 tests/typecheck/should_compile/tc168.stderr   |  22 +--
 tests/typecheck/should_compile/tc211.stderr   |  14 +-
 tests/typecheck/should_compile/tc254.stderr   |   6 +-
 .../typecheck/should_fail/AssocTyDef01.stderr |   2 +-
 .../typecheck/should_fail/AssocTyDef02.stderr |  12 +-
 .../typecheck/should_fail/AssocTyDef03.stderr |  10 +-
 .../typecheck/should_fail/AssocTyDef04.stderr |  14 +-
 .../typecheck/should_fail/AssocTyDef05.stderr |   4 +-
 .../typecheck/should_fail/AssocTyDef06.stderr |   4 +-
 .../typecheck/should_fail/AssocTyDef07.stderr |   2 +-
 .../typecheck/should_fail/AssocTyDef08.stderr |   2 +-
 .../typecheck/should_fail/AssocTyDef09.stderr |   2 +-
 .../should_fail/FDsFromGivens.stderr          |   8 +-
 .../FailDueToGivenOverlapping.stderr          |   6 +-
 .../should_fail/FrozenErrorTests.stderr       | 106 +++++++-------
 tests/typecheck/should_fail/IPFail.stderr     |   4 +-
 .../should_fail/LongWayOverlapping.stderr     |   6 +-
 tests/typecheck/should_fail/SCLoop.stderr     |   4 +-
 .../SilentParametersOverlapping.stderr        |   8 +-
 tests/typecheck/should_fail/T1595.stderr      |   4 +-
 tests/typecheck/should_fail/T1633.stderr      |   6 +-
 tests/typecheck/should_fail/T1897a.stderr     |  22 +--
 tests/typecheck/should_fail/T1899.stderr      |   8 +-
 tests/typecheck/should_fail/T2126.stderr      |   4 +-
 tests/typecheck/should_fail/T2247.stderr      |   4 +-
 tests/typecheck/should_fail/T2354.stderr      |   4 +-
 tests/typecheck/should_fail/T2414.stderr      |   4 +-
 tests/typecheck/should_fail/T2534.stderr      |   6 +-
 tests/typecheck/should_fail/T2538.stderr      |   6 +-
 tests/typecheck/should_fail/T2688.stderr      |  14 +-
 tests/typecheck/should_fail/T2714.stderr      |  12 +-
 tests/typecheck/should_fail/T2806.stderr      |   8 +-
 tests/typecheck/should_fail/T2846b.stderr     |   4 +-
 tests/typecheck/should_fail/T2994.stderr      |  18 +--
 tests/typecheck/should_fail/T3102.stderr      |   8 +-
 tests/typecheck/should_fail/T3176.stderr      |   4 +-
 tests/typecheck/should_fail/T3323.stderr      |   2 +-
 tests/typecheck/should_fail/T3406.stderr      |   6 +-
 tests/typecheck/should_fail/T3468.stderr      |  24 ++--
 tests/typecheck/should_fail/T3540.stderr      |  20 +--
 tests/typecheck/should_fail/T3592.stderr      |   8 +-
 tests/typecheck/should_fail/T3613.stderr      |  14 +-
 tests/typecheck/should_fail/T3966.stderr      |   6 +-
 tests/typecheck/should_fail/T4875.stderr      |  10 +-
 tests/typecheck/should_fail/T5051.stderr      |   8 +-
 tests/typecheck/should_fail/T5084.stderr      |   2 +-
 tests/typecheck/should_fail/T5095.stderr      |  56 ++++----
 tests/typecheck/should_fail/T5236.stderr      |  24 ++--
 tests/typecheck/should_fail/T5246.stderr      |   4 +-
 tests/typecheck/should_fail/T5300.stderr      |  64 ++++-----
 tests/typecheck/should_fail/T5570.stderr      |  18 +--
 tests/typecheck/should_fail/T5684.stderr      |  32 ++---
 tests/typecheck/should_fail/T5689.stderr      |  78 +++++-----
 tests/typecheck/should_fail/T5691.stderr      |  34 ++---
 tests/typecheck/should_fail/T5853.stderr      |   2 +-
 tests/typecheck/should_fail/T5858.stderr      |   6 +-
 tests/typecheck/should_fail/T5957.stderr      |   2 +-
 tests/typecheck/should_fail/T5978.stderr      |  20 +--
 tests/typecheck/should_fail/T6001.stderr      |   2 +-
 tests/typecheck/should_fail/T6069.stderr      |  14 +-
 tests/typecheck/should_fail/T6078.stderr      |   2 +-
 tests/typecheck/should_fail/T6161.stderr      |   4 +-
 tests/typecheck/should_fail/T7019.stderr      |   4 +-
 tests/typecheck/should_fail/T7019a.stderr     |   6 +-
 tests/typecheck/should_fail/T7175.stderr      |   8 +-
 tests/typecheck/should_fail/T7210.stderr      |   6 +-
 tests/typecheck/should_fail/T7220.stderr      |   4 +-
 tests/typecheck/should_fail/T7264.stderr      |   8 +-
 tests/typecheck/should_fail/T7279.stderr      |   4 +-
 tests/typecheck/should_fail/T7368.stderr      |  14 +-
 tests/typecheck/should_fail/T7368a.stderr     |  20 +--
 tests/typecheck/should_fail/T7410.stderr      |   8 +-
 tests/typecheck/should_fail/T7453.stderr      |  24 ++--
 tests/typecheck/should_fail/T7525.stderr      |   4 +-
 tests/typecheck/should_fail/T7545.stderr      |   2 +-
 tests/typecheck/should_fail/T7609.stderr      |  14 +-
 tests/typecheck/should_fail/T7645.stderr      |   8 +-
 .../should_fail/TcMultiWayIfFail.stderr       |   8 +-
 tests/typecheck/should_fail/fd-loop.stderr    |  24 ++--
 tests/typecheck/should_fail/mc19.stderr       |   4 +-
 tests/typecheck/should_fail/mc20.stderr       |   2 +-
 tests/typecheck/should_fail/mc21.stderr       |   6 +-
 tests/typecheck/should_fail/mc22.stderr       |   6 +-
 tests/typecheck/should_fail/mc23.stderr       |   6 +-
 tests/typecheck/should_fail/mc24.stderr       |   6 +-
 tests/typecheck/should_fail/mc25.stderr       |   2 +-
 tests/typecheck/should_fail/tcfail001.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail002.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail003.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail004.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail005.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail006.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail007.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail008.stderr  |  40 +++---
 tests/typecheck/should_fail/tcfail009.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail010.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail011.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail012.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail013.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail014.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail015.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail016.stderr  |  12 +-
 tests/typecheck/should_fail/tcfail017.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail018.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail019.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail020.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail027.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail028.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail029.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail030.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail031.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail032.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail033.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail034.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail036.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail037.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail038.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail040.stderr  |  18 +--
 tests/typecheck/should_fail/tcfail041.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail042.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail043.stderr  |  80 +++++------
 tests/typecheck/should_fail/tcfail044.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail047.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail048.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail049.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail050.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail051.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail052.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail053.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail054.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail055.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail056.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail057.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail058.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail061.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail062.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail063.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail065.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail067.stderr  |  28 ++--
 tests/typecheck/should_fail/tcfail068.stderr  |  40 +++---
 tests/typecheck/should_fail/tcfail069.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail070.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail072.stderr  |  32 ++---
 tests/typecheck/should_fail/tcfail073.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail076.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail077.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail078.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail079.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail080.stderr  |  26 ++--
 tests/typecheck/should_fail/tcfail082.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail083.stderr  |  40 +++---
 tests/typecheck/should_fail/tcfail084.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail085.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail086.stderr  |  12 +-
 tests/typecheck/should_fail/tcfail088.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail090.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail092.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail097.stderr  |  18 +--
 tests/typecheck/should_fail/tcfail098.stderr  |  20 +--
 tests/typecheck/should_fail/tcfail099.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail100.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail101.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail102.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail103.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail104.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail106.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail107.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail108.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail109.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail110.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail112.stderr  |  12 +-
 tests/typecheck/should_fail/tcfail113.stderr  |  16 +--
 tests/typecheck/should_fail/tcfail114.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail116.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail117.stderr  |  26 ++--
 tests/typecheck/should_fail/tcfail119.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail121.stderr  |   7 +-
 tests/typecheck/should_fail/tcfail122.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail123.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail125.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail127.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail128.stderr  |  42 +++---
 tests/typecheck/should_fail/tcfail129.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail130.stderr  |   5 +-
 tests/typecheck/should_fail/tcfail131.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail132.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail133.stderr  |  52 +++----
 tests/typecheck/should_fail/tcfail134.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail135.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail136.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail137.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail139.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail140.stderr  |  32 ++---
 tests/typecheck/should_fail/tcfail142.stderr  |  20 +--
 tests/typecheck/should_fail/tcfail143.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail146.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail147.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail148.stderr  |  14 +-
 tests/typecheck/should_fail/tcfail151.stderr  |  16 +--
 tests/typecheck/should_fail/tcfail152.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail153.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail154.stderr  |  12 +-
 tests/typecheck/should_fail/tcfail155.stderr  |  12 +-
 tests/typecheck/should_fail/tcfail156.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail157.stderr  |  24 ++--
 tests/typecheck/should_fail/tcfail158.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail159.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail160.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail161.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail162.stderr  |  14 +-
 tests/typecheck/should_fail/tcfail164.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail165.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail167.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail168.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail170.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail171.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail173.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail174.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail175.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail176.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail177.stderr  | 114 +++++++--------
 tests/typecheck/should_fail/tcfail178.stderr  |  12 +-
 tests/typecheck/should_fail/tcfail179.stderr  |   8 +-
 tests/typecheck/should_fail/tcfail180.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail181.stderr  |  30 ++--
 tests/typecheck/should_fail/tcfail182.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail184.stderr  |  14 +-
 tests/typecheck/should_fail/tcfail185.stderr  |  24 ++--
 tests/typecheck/should_fail/tcfail186.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail187.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail189.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail190.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail191.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail192.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail193.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail194.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail195.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail196.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail197.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail198.stderr  |   6 +-
 tests/typecheck/should_fail/tcfail199.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail200.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail201.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail203.stderr  |  32 ++---
 tests/typecheck/should_fail/tcfail204.stderr  |  16 +--
 tests/typecheck/should_fail/tcfail206.stderr  |  16 +--
 tests/typecheck/should_fail/tcfail207.stderr  |  20 +--
 tests/typecheck/should_fail/tcfail208.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail209.stderr  |  10 +-
 tests/typecheck/should_fail/tcfail209a.stderr |   2 +-
 tests/typecheck/should_fail/tcfail210.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail211.stderr  |   7 +-
 tests/typecheck/should_fail/tcfail212.stderr  |  12 +-
 tests/typecheck/should_fail/tcfail213.stderr  |  14 +-
 tests/typecheck/should_fail/tcfail214.stderr  |  14 +-
 tests/typecheck/should_fail/tcfail215.stderr  |   4 +-
 tests/typecheck/should_fail/tcfail216.stderr  |   2 +-
 tests/typecheck/should_fail/tcfail217.stderr  |   2 +-
 tests/typecheck/should_run/tcrun035.stderr    |  22 +--
 745 files changed, 3464 insertions(+), 3475 deletions(-)

diff --git a/tests/annotations/should_fail/annfail01.stderr b/tests/annotations/should_fail/annfail01.stderr
index 70553f983..160575cf9 100644
--- a/tests/annotations/should_fail/annfail01.stderr
+++ b/tests/annotations/should_fail/annfail01.stderr
@@ -1,4 +1,4 @@
 
-annfail01.hs:4:1: Not in scope: type constructor or class `Foo'
+annfail01.hs:4:1: Not in scope: type constructor or class ‛Foo’
 
-annfail01.hs:5:1: Not in scope: `f'
+annfail01.hs:5:1: Not in scope: ‛f’
diff --git a/tests/annotations/should_fail/annfail02.stderr b/tests/annotations/should_fail/annfail02.stderr
index 83d54f984..21f7aff82 100644
--- a/tests/annotations/should_fail/annfail02.stderr
+++ b/tests/annotations/should_fail/annfail02.stderr
@@ -1,4 +1,4 @@
 
-annfail02.hs:6:1: Not in scope: data constructor `Foo'
+annfail02.hs:6:1: Not in scope: data constructor ‛Foo’
 
-annfail02.hs:7:1: Not in scope: type constructor or class `Bar'
+annfail02.hs:7:1: Not in scope: type constructor or class ‛Bar’
diff --git a/tests/annotations/should_fail/annfail03.stderr b/tests/annotations/should_fail/annfail03.stderr
index a7be7feb9..9c1585507 100644
--- a/tests/annotations/should_fail/annfail03.stderr
+++ b/tests/annotations/should_fail/annfail03.stderr
@@ -1,7 +1,8 @@
 
 annfail03.hs:17:1:
-    GHC stage restriction: instance for `Data InModule'
-      is used in a top-level splice or annotation,
+    GHC stage restriction:
+      instance for ‛Data
+                      InModule’ is used in a top-level splice or annotation,
       and must be imported, not defined locally
     In the expression: InModule
     In the annotation: {-# ANN f InModule #-}
diff --git a/tests/annotations/should_fail/annfail04.stderr b/tests/annotations/should_fail/annfail04.stderr
index dcbe0e794..9d7bf3977 100644
--- a/tests/annotations/should_fail/annfail04.stderr
+++ b/tests/annotations/should_fail/annfail04.stderr
@@ -1,7 +1,8 @@
 
 annfail04.hs:14:12:
-    GHC stage restriction: instance for `Thing Int'
-      is used in a top-level splice or annotation,
+    GHC stage restriction:
+      instance for ‛Thing
+                      Int’ is used in a top-level splice or annotation,
       and must be imported, not defined locally
     In the expression: (thing :: Int)
     In the annotation: {-# ANN f (thing :: Int) #-}
diff --git a/tests/annotations/should_fail/annfail06.stderr b/tests/annotations/should_fail/annfail06.stderr
index c5082c386..aec329d5f 100644
--- a/tests/annotations/should_fail/annfail06.stderr
+++ b/tests/annotations/should_fail/annfail06.stderr
@@ -1,7 +1,8 @@
 
 annfail06.hs:21:1:
-    GHC stage restriction: instance for `Data InstancesInWrongModule'
-      is used in a top-level splice or annotation,
+    GHC stage restriction:
+      instance for ‛Data
+                      InstancesInWrongModule’ is used in a top-level splice or annotation,
       and must be imported, not defined locally
     In the expression: InstancesInWrongModule
     In the annotation: {-# ANN f InstancesInWrongModule #-}
diff --git a/tests/annotations/should_fail/annfail07.stderr b/tests/annotations/should_fail/annfail07.stderr
index 01f4b62c4..678a1609e 100644
--- a/tests/annotations/should_fail/annfail07.stderr
+++ b/tests/annotations/should_fail/annfail07.stderr
@@ -1,6 +1,6 @@
 
 annfail07.hs:9:17:
-    Couldn't match expected type `[a0]' with actual type `Bool'
-    In the first argument of `head', namely `True'
+    Couldn't match expected type ‛[a0]’ with actual type ‛Bool’
+    In the first argument of ‛head’, namely ‛True’
     In the expression: (head True)
     In the annotation: {-# ANN f (head True) #-}
diff --git a/tests/annotations/should_fail/annfail08.stderr b/tests/annotations/should_fail/annfail08.stderr
index df18d002e..b9023476f 100644
--- a/tests/annotations/should_fail/annfail08.stderr
+++ b/tests/annotations/should_fail/annfail08.stderr
@@ -6,6 +6,6 @@ annfail08.hs:9:1:
     In the annotation: {-# ANN f (id + 1) #-}
 
 annfail08.hs:9:15:
-    No instance for (Num (a0 -> a0)) arising from a use of `+'
+    No instance for (Num (a0 -> a0)) arising from a use of ‛+’
     In the expression: (id + 1)
     In the annotation: {-# ANN f (id + 1) #-}
diff --git a/tests/annotations/should_fail/annfail09.stderr b/tests/annotations/should_fail/annfail09.stderr
index 5eae63a01..4bddab8dd 100644
--- a/tests/annotations/should_fail/annfail09.stderr
+++ b/tests/annotations/should_fail/annfail09.stderr
@@ -1,7 +1,7 @@
 
 annfail09.hs:11:11:
-    GHC stage restriction: `g'
-      is used in a top-level splice or annotation,
+    GHC stage restriction:
+      ‛g’ is used in a top-level splice or annotation,
       and must be imported, not defined locally
     In the expression: g
     In the annotation: {-# ANN f g #-}
diff --git a/tests/annotations/should_fail/annfail10.stderr b/tests/annotations/should_fail/annfail10.stderr
index c5b035689..0fd7859ef 100644
--- a/tests/annotations/should_fail/annfail10.stderr
+++ b/tests/annotations/should_fail/annfail10.stderr
@@ -1,27 +1,27 @@
 
 annfail10.hs:9:1:
     No instance for (Data.Data.Data a0) arising from an annotation
-    The type variable `a0' is ambiguous
+    The type variable ‛a0’ is ambiguous
     Note: there are several potential instances:
-      instance Data.Data.Data () -- Defined in `Data.Data'
+      instance Data.Data.Data () -- Defined in ‛Data.Data’
       instance (Data.Data.Data a, Data.Data.Data b) =>
                Data.Data.Data (a, b)
-        -- Defined in `Data.Data'
+        -- Defined in ‛Data.Data’
       instance (Data.Data.Data a, Data.Data.Data b, Data.Data.Data c) =>
                Data.Data.Data (a, b, c)
-        -- Defined in `Data.Data'
+        -- Defined in ‛Data.Data’
       ...plus 27 others
     In the expression: 1
     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
+    No instance for (Num a0) arising from the literal ‛1’
+    The type variable ‛a0’ is ambiguous
     Note: there are several potential instances:
-      instance Num Double -- Defined in `GHC.Float'
-      instance Num Float -- Defined in `GHC.Float'
+      instance Num Double -- Defined in ‛GHC.Float’
+      instance Num Float -- Defined in ‛GHC.Float’
       instance Integral a => Num (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
+        -- Defined in ‛GHC.Real’
       ...plus 11 others
     In the expression: 1
     In the annotation: {-# ANN f 1 #-}
diff --git a/tests/annotations/should_fail/annfail11.stderr b/tests/annotations/should_fail/annfail11.stderr
index 18769f746..39ff0e82e 100644
--- a/tests/annotations/should_fail/annfail11.stderr
+++ b/tests/annotations/should_fail/annfail11.stderr
@@ -1,4 +1,4 @@
 
-annfail11.hs:3:1: Not in scope: `length'
+annfail11.hs:3:1: Not in scope: ‛length’
 
-annfail11.hs:4:1: Not in scope: type constructor or class `Integer'
+annfail11.hs:4:1: Not in scope: type constructor or class ‛Integer’
diff --git a/tests/arrows/should_fail/T5380.stderr b/tests/arrows/should_fail/T5380.stderr
index 1d3fa3a1e..567450ef2 100644
--- a/tests/arrows/should_fail/T5380.stderr
+++ b/tests/arrows/should_fail/T5380.stderr
@@ -1,7 +1,7 @@
 
 T5380.hs:7:27:
-    Couldn't match expected type `Bool' with actual type `not_bool'
-      `not_bool' is a rigid type variable bound by
+    Couldn't match expected type ‛Bool’ with actual type ‛not_bool’
+      ‛not_bool’ is a rigid type variable bound by
                  the type signature for
                    testB :: not_bool -> (() -> ()) -> () -> not_unit
                  at T5380.hs:6:10
@@ -11,12 +11,12 @@ T5380.hs:7:27:
       b :: not_bool (bound at T5380.hs:7:7)
     In the expression: b
     In the expression: proc () -> if b then f -< () else f -< ()
-    In an equation for `testB':
+    In an equation for ‛testB’:
         testB b f = proc () -> if b then f -< () else f -< ()
 
 T5380.hs:7:34:
-    Couldn't match type `not_unit' with `()'
-      `not_unit' is a rigid type variable bound by
+    Couldn't match type ‛not_unit’ with ‛()’
+      ‛not_unit’ is a rigid type variable bound by
                  the type signature for
                    testB :: not_bool -> (() -> ()) -> () -> not_unit
                  at T5380.hs:6:10
@@ -27,5 +27,5 @@ T5380.hs:7:34:
         (bound at T5380.hs:7:1)
     In the expression: f
     In the expression: proc () -> if b then f -< () else f -< ()
-    In an equation for `testB':
+    In an equation for ‛testB’:
         testB b f = proc () -> if b then f -< () else f -< ()
diff --git a/tests/arrows/should_fail/arrowfail001.stderr b/tests/arrows/should_fail/arrowfail001.stderr
index 261aa278a..6dc2cb76c 100644
--- a/tests/arrows/should_fail/arrowfail001.stderr
+++ b/tests/arrows/should_fail/arrowfail001.stderr
@@ -1,7 +1,7 @@
 
 arrowfail001.hs:16:36:
-    No instance for (Foo a) arising from a use of `foo'
+    No instance for (Foo a) arising from a use of ‛foo’
     In the expression: foo
     In the expression: proc x -> case x of { Bar a -> foo -< a }
-    In an equation for `get':
+    In an equation for ‛get’:
         get = proc x -> case x of { Bar a -> foo -< a }
diff --git a/tests/arrows/should_fail/arrowfail002.stderr b/tests/arrows/should_fail/arrowfail002.stderr
index c653acc33..67a93db71 100644
--- a/tests/arrows/should_fail/arrowfail002.stderr
+++ b/tests/arrows/should_fail/arrowfail002.stderr
@@ -1,2 +1,2 @@
 
-arrowfail002.hs:6:17: Not in scope: `x'
+arrowfail002.hs:6:17: Not in scope: ‛x’
diff --git a/tests/arrows/should_fail/arrowfail004.stderr b/tests/arrows/should_fail/arrowfail004.stderr
index 8a20c6bcb..65cef2545 100644
--- a/tests/arrows/should_fail/arrowfail004.stderr
+++ b/tests/arrows/should_fail/arrowfail004.stderr
@@ -3,5 +3,5 @@ arrowfail004.hs:12:15:
     Proc patterns cannot use existential or GADT data constructors
     In the pattern: T x
     In the expression: proc (T x) -> do { returnA -< T x }
-    In an equation for `panic':
+    In an equation for ‛panic’:
         panic = proc (T x) -> do { returnA -< T x }
diff --git a/tests/deSugar/should_compile/GadtOverlap.stderr b/tests/deSugar/should_compile/GadtOverlap.stderr
index 423d69469..359a352ed 100644
--- a/tests/deSugar/should_compile/GadtOverlap.stderr
+++ b/tests/deSugar/should_compile/GadtOverlap.stderr
@@ -1,4 +1,4 @@
 
-GadtOverlap.hs:19:1:
-    Warning: Pattern match(es) are non-exhaustive
-             In an equation for `h': Patterns not matched: T3
+GadtOverlap.hs:19:1: Warning:
+    Pattern match(es) are non-exhaustive
+    In an equation for ‛h’: Patterns not matched: T3
diff --git a/tests/deSugar/should_compile/T2395.stderr b/tests/deSugar/should_compile/T2395.stderr
index 4bfd9d6bb..241a767f7 100644
--- a/tests/deSugar/should_compile/T2395.stderr
+++ b/tests/deSugar/should_compile/T2395.stderr
@@ -1,4 +1,4 @@
 
-T2395.hs:12:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `bar': bar _ = ...
+T2395.hs:12:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛bar’: bar _ = ...
diff --git a/tests/deSugar/should_compile/T5117.stderr b/tests/deSugar/should_compile/T5117.stderr
index e9ddba143..2860940b0 100644
--- a/tests/deSugar/should_compile/T5117.stderr
+++ b/tests/deSugar/should_compile/T5117.stderr
@@ -1,4 +1,4 @@
-
-T5117.hs:15:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `f3': f3 (MyString "a") = ...
+
+T5117.hs:15:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛f3’: f3 (MyString "a") = ...
diff --git a/tests/deSugar/should_compile/ds002.stderr-ghc b/tests/deSugar/should_compile/ds002.stderr-ghc
index baf7ffde5..c526e0db4 100644
--- a/tests/deSugar/should_compile/ds002.stderr-ghc
+++ b/tests/deSugar/should_compile/ds002.stderr-ghc
@@ -1,10 +1,10 @@
 
-ds002.hs:7:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `f':
-                 f y = ...
-                 f z = ...
+ds002.hs:7:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛f’:
+        f y = ...
+        f z = ...
 
-ds002.hs:11:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `g': g x y z = ...
+ds002.hs:11:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛g’: g x y z = ...
diff --git a/tests/deSugar/should_compile/ds003.stderr-ghc b/tests/deSugar/should_compile/ds003.stderr-ghc
index 5b1bd3949..f12789da4 100644
--- a/tests/deSugar/should_compile/ds003.stderr-ghc
+++ b/tests/deSugar/should_compile/ds003.stderr-ghc
@@ -1,6 +1,6 @@
 
-ds003.hs:5:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `f':
-                 f (x : x1 : x2 : x3) ~(y, ys) z = ...
-                 f x y True = ...
+ds003.hs:5:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛f’:
+        f (x : x1 : x2 : x3) ~(y, ys) z = ...
+        f x y True = ...
diff --git a/tests/deSugar/should_compile/ds019.stderr-ghc b/tests/deSugar/should_compile/ds019.stderr-ghc
index 68816686b..fd13ec720 100644
--- a/tests/deSugar/should_compile/ds019.stderr-ghc
+++ b/tests/deSugar/should_compile/ds019.stderr-ghc
@@ -1,7 +1,7 @@
 
-ds019.hs:5:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `f':
-                 f d (j, k) p = ...
-                 f (e, f, g) l q = ...
-                 f h (m, n) r = ...
+ds019.hs:5:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛f’:
+        f d (j, k) p = ...
+        f (e, f, g) l q = ...
+        f h (m, n) r = ...
diff --git a/tests/deSugar/should_compile/ds020.stderr-ghc b/tests/deSugar/should_compile/ds020.stderr-ghc
index 3f9205a72..423232002 100644
--- a/tests/deSugar/should_compile/ds020.stderr-ghc
+++ b/tests/deSugar/should_compile/ds020.stderr-ghc
@@ -1,18 +1,18 @@
 
-ds020.hs:8:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `a': a ~(~[], ~[], ~[]) = ...
+ds020.hs:8:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛a’: a ~(~[], ~[], ~[]) = ...
 
-ds020.hs:11:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `b': b ~(~x : ~xs : ~ys) = ...
+ds020.hs:11:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛b’: b ~(~x : ~xs : ~ys) = ...
 
-ds020.hs:16:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `d':
-                 d ~(n+43) = ...
-                 d ~(n+999) = ...
+ds020.hs:16:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛d’:
+        d ~(n+43) = ...
+        d ~(n+999) = ...
 
-ds020.hs:22:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `f': f x@(~[]) = ...
+ds020.hs:22:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛f’: f x@(~[]) = ...
diff --git a/tests/deSugar/should_compile/ds022.stderr-ghc b/tests/deSugar/should_compile/ds022.stderr-ghc
index ce6d4a52c..7dd50a261 100644
--- a/tests/deSugar/should_compile/ds022.stderr-ghc
+++ b/tests/deSugar/should_compile/ds022.stderr-ghc
@@ -1,6 +1,6 @@
 
-ds022.hs:20:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `i':
-                 i 1 0.011e2 = ...
-                 i 2 2.20000 = ...
+ds022.hs:20:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛i’:
+        i 1 0.011e2 = ...
+        i 2 2.20000 = ...
diff --git a/tests/deSugar/should_compile/ds041.stderr-ghc b/tests/deSugar/should_compile/ds041.stderr-ghc
index acf3e1ae6..48129316f 100644
--- a/tests/deSugar/should_compile/ds041.stderr-ghc
+++ b/tests/deSugar/should_compile/ds041.stderr-ghc
@@ -1,8 +1,8 @@
 
-ds041.hs:1:14:
-    Warning: -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
+ds041.hs:1:14: Warning:
+    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
-ds041.hs:16:7:
-    Warning: Fields of `Foo' not initialised: x
+ds041.hs:16:7: Warning:
+    Fields of ‛Foo’ not initialised: x
     In the expression: Foo {}
-    In an equation for `foo': foo = Foo {}
+    In an equation for ‛foo’: foo = Foo {}
diff --git a/tests/deSugar/should_compile/ds051.stderr-ghc b/tests/deSugar/should_compile/ds051.stderr-ghc
index a098efee3..c40c44620 100644
--- a/tests/deSugar/should_compile/ds051.stderr-ghc
+++ b/tests/deSugar/should_compile/ds051.stderr-ghc
@@ -1,12 +1,12 @@
 
-ds051.hs:6:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `f1': f1 "ab" = ...
+ds051.hs:6:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛f1’: f1 "ab" = ...
 
-ds051.hs:11:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `f2': f2 ('a' : 'b' : []) = ...
+ds051.hs:11:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛f2’: f2 ('a' : 'b' : []) = ...
 
-ds051.hs:16:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `f3': f3 "ab" = ...
+ds051.hs:16:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛f3’: f3 "ab" = ...
diff --git a/tests/deSugar/should_compile/ds053.stderr-ghc b/tests/deSugar/should_compile/ds053.stderr-ghc
index 3bce90686..861e66b84 100644
--- a/tests/deSugar/should_compile/ds053.stderr-ghc
+++ b/tests/deSugar/should_compile/ds053.stderr-ghc
@@ -1,2 +1,2 @@
 
-ds053.hs:5:1: Warning: Defined but not used: `f'
+ds053.hs:5:1: Warning: Defined but not used: ‛f’
diff --git a/tests/deSugar/should_compile/ds056.stderr b/tests/deSugar/should_compile/ds056.stderr
index 6e0972bef..f4d2e81b5 100644
--- a/tests/deSugar/should_compile/ds056.stderr
+++ b/tests/deSugar/should_compile/ds056.stderr
@@ -1,4 +1,4 @@
 
-ds056.hs:8:1:
-    Warning: Pattern match(es) are overlapped
-             In an equation for `g': g _ = ...
+ds056.hs:8:1: Warning:
+    Pattern match(es) are overlapped
+    In an equation for ‛g’: g _ = ...
diff --git a/tests/deriving/should_compile/drv021.stderr b/tests/deriving/should_compile/drv021.stderr
index 8143dfee6..2071183c5 100644
--- a/tests/deriving/should_compile/drv021.stderr
+++ b/tests/deriving/should_compile/drv021.stderr
@@ -1,13 +1,13 @@
 
 drv021.hs:9:1: Warning:
-    Module `Data.OldTypeable' is deprecated: Use Data.Typeable instead
+    Module ‛Data.OldTypeable’ is deprecated: Use Data.Typeable instead
 
 drv021.hs:14:19: Warning:
-    In the use of type constructor or class `Typeable1'
+    In the use of type constructor or class ‛Typeable1’
     (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
     Deprecated: "Use Data.Typeable.Internal instead"
 
 drv021.hs:15:19: Warning:
-    In the use of type constructor or class `Typeable2'
+    In the use of type constructor or class ‛Typeable2’
     (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
     Deprecated: "Use Data.Typeable.Internal instead"
diff --git a/tests/deriving/should_fail/T1133A.stderr b/tests/deriving/should_fail/T1133A.stderr
index 734081ede..c1830b143 100644
--- a/tests/deriving/should_fail/T1133A.stderr
+++ b/tests/deriving/should_fail/T1133A.stderr
@@ -1,7 +1,7 @@
 
 T1133A.hs:6:28:
-    Can't make a derived instance of `Enum X':
-      `X' must be an enumeration type
+    Can't make a derived instance of ‛Enum X’:
+      ‛X’ must be an enumeration type
       (an enumeration consists of one or more nullary, non-GADT constructors)
       Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension
-    In the newtype declaration for `X'
+    In the newtype declaration for ‛X’
diff --git a/tests/deriving/should_fail/T2394.stderr b/tests/deriving/should_fail/T2394.stderr
index 9972186ed..f8ccbda84 100644
--- a/tests/deriving/should_fail/T2394.stderr
+++ b/tests/deriving/should_fail/T2394.stderr
@@ -1,6 +1,6 @@
-
-T2394.hs:9:1:
-    Can't make a derived instance of `Data (a -> b)':
-      The last argument of the instance must be a data or newtype application
-    In the stand-alone deriving instance for
-      `(Data a, Data b) => Data (a -> b)'
+
+T2394.hs:9:1:
+    Can't make a derived instance of ‛Data (a -> b)’:
+      The last argument of the instance must be a data or newtype application
+    In the stand-alone deriving instance for
+      ‛(Data a, Data b) => Data (a -> b)’
diff --git a/tests/deriving/should_fail/T2604.stderr b/tests/deriving/should_fail/T2604.stderr
index 8fe5ffff5..fc5320030 100644
--- a/tests/deriving/should_fail/T2604.stderr
+++ b/tests/deriving/should_fail/T2604.stderr
@@ -1,10 +1,10 @@
-
-T2604.hs:7:35:
-    Can't make a derived instance of `Typeable * (DList a)':
-      You need -XDeriveDataTypeable to derive an instance for this class
-    In the data declaration for `DList'
-
-T2604.hs:9:38:
-    Can't make a derived instance of `Typeable * (NList a)':
-      You need -XDeriveDataTypeable to derive an instance for this class
-    In the newtype declaration for `NList'
+
+T2604.hs:7:35:
+    Can't make a derived instance of ‛Typeable * (DList a)’:
+      You need -XDeriveDataTypeable to derive an instance for this class
+    In the data declaration for ‛DList’
+
+T2604.hs:9:38:
+    Can't make a derived instance of ‛Typeable * (NList a)’:
+      You need -XDeriveDataTypeable to derive an instance for this class
+    In the newtype declaration for ‛NList’
diff --git a/tests/deriving/should_fail/T2701.stderr b/tests/deriving/should_fail/T2701.stderr
index 150add58c..722c0c12b 100644
--- a/tests/deriving/should_fail/T2701.stderr
+++ b/tests/deriving/should_fail/T2701.stderr
@@ -1,5 +1,5 @@
-
-T2701.hs:10:32:
-    Can't make a derived instance of `Data Foo':
-      Don't know how to derive `Data' for type `Int#'
-    In the data declaration for `Foo'
+
+T2701.hs:10:32:
+    Can't make a derived instance of ‛Data Foo’:
+      Don't know how to derive ‛Data’ for type ‛Int#’
+    In the data declaration for ‛Foo’
diff --git a/tests/deriving/should_fail/T2721.stderr b/tests/deriving/should_fail/T2721.stderr
index 03339d3bf..64e93c3d1 100644
--- a/tests/deriving/should_fail/T2721.stderr
+++ b/tests/deriving/should_fail/T2721.stderr
@@ -1,6 +1,6 @@
-
-T2721.hs:15:28:
-    Can't make a derived instance of `C N'
-      (even with cunning newtype deriving):
-      the class has associated types
-    In the newtype declaration for `N'
+
+T2721.hs:15:28:
+    Can't make a derived instance of ‛C N’
+      (even with cunning newtype deriving):
+      the class has associated types
+    In the newtype declaration for ‛N’
diff --git a/tests/deriving/should_fail/T3101.stderr b/tests/deriving/should_fail/T3101.stderr
index b49175938..b07e2570a 100644
--- a/tests/deriving/should_fail/T3101.stderr
+++ b/tests/deriving/should_fail/T3101.stderr
@@ -1,6 +1,6 @@
-
-T3101.hs:9:12:
-    Can't make a derived instance of `Show Boom':
-      Constructor `Boom' must have a Haskell-98 type
-      Possible fix: use a standalone deriving declaration instead
-    In the data declaration for `Boom'
+
+T3101.hs:9:12:
+    Can't make a derived instance of ‛Show Boom’:
+      Constructor ‛Boom’ must have a Haskell-98 type
+      Possible fix: use a standalone deriving declaration instead
+    In the data declaration for ‛Boom’
diff --git a/tests/deriving/should_fail/T3833.stderr b/tests/deriving/should_fail/T3833.stderr
index 2d31cc136..3221c355b 100644
--- a/tests/deriving/should_fail/T3833.stderr
+++ b/tests/deriving/should_fail/T3833.stderr
@@ -1,6 +1,6 @@
 
 T3833.hs:9:1:
-    Can't make a derived instance of `Monoid (DecodeMap e)':
-      `Monoid' is not a derivable class
+    Can't make a derived instance of ‛Monoid (DecodeMap e)’:
+      ‛Monoid’ is not a derivable class
       Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension
-    In the stand-alone deriving instance for `Monoid (DecodeMap e)'
+    In the stand-alone deriving instance for ‛Monoid (DecodeMap e)’
diff --git a/tests/deriving/should_fail/T3834.stderr b/tests/deriving/should_fail/T3834.stderr
index 199b4bb79..ba51c74d5 100644
--- a/tests/deriving/should_fail/T3834.stderr
+++ b/tests/deriving/should_fail/T3834.stderr
@@ -1,6 +1,6 @@
 
 T3834.hs:8:1:
-    Can't make a derived instance of `C T':
-      `C' is not a derivable class
+    Can't make a derived instance of ‛C T’:
+      ‛C’ is not a derivable class
       Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension
-    In the stand-alone deriving instance for `C T'
+    In the stand-alone deriving instance for ‛C T’
diff --git a/tests/deriving/should_fail/T4528.stderr b/tests/deriving/should_fail/T4528.stderr
index 8f008e890..174623915 100644
--- a/tests/deriving/should_fail/T4528.stderr
+++ b/tests/deriving/should_fail/T4528.stderr
@@ -1,14 +1,14 @@
 
 T4528.hs:9:1:
-    Can't make a derived instance of `Enum (Foo a)':
-      `Foo' must be an enumeration type
+    Can't make a derived instance of ‛Enum (Foo a)’:
+      ‛Foo’ must be an enumeration type
       (an enumeration consists of one or more nullary, non-GADT constructors)
-    In the stand-alone deriving instance for `Enum (Foo a)'
+    In the stand-alone deriving instance for ‛Enum (Foo a)’
 
 T4528.hs:10:1:
-    Can't make a derived instance of `Bounded (Foo a)':
-      `Foo' must be an enumeration type
+    Can't make a derived instance of ‛Bounded (Foo a)’:
+      ‛Foo’ must be an enumeration type
       (an enumeration consists of one or more nullary, non-GADT constructors)
         or
-      `Foo' must have precisely one constructor
-    In the stand-alone deriving instance for `Bounded (Foo a)'
+      ‛Foo’ must have precisely one constructor
+    In the stand-alone deriving instance for ‛Bounded (Foo a)’
diff --git a/tests/deriving/should_fail/T5287.stderr b/tests/deriving/should_fail/T5287.stderr
index 9de62ef2f..8bacf0634 100644
--- a/tests/deriving/should_fail/T5287.stderr
+++ b/tests/deriving/should_fail/T5287.stderr
@@ -1,10 +1,10 @@
-
-T5287.hs:6:10:
-    Could not deduce (A a oops0)
-      arising from the ambiguity check for an instance declaration
-    from the context (A a oops)
-      bound by an instance declaration: A a oops => Read (D a)
-      at T5287.hs:6:10-31
-    The type variable `oops0' is ambiguous
-    In the ambiguity check for: forall a oops. A a oops => Read (D a)
-    In the instance declaration for `Read (D a)'
+
+T5287.hs:6:10:
+    Could not deduce (A a oops0)
+      arising from the ambiguity check for an instance declaration
+    from the context (A a oops)
+      bound by an instance declaration: A a oops => Read (D a)
+      at T5287.hs:6:10-31
+    The type variable ‛oops0’ is ambiguous
+    In the ambiguity check for: forall a oops. A a oops => Read (D a)
+    In the instance declaration for ‛Read (D a)’
diff --git a/tests/deriving/should_fail/T5478.stderr b/tests/deriving/should_fail/T5478.stderr
index a49b188da..e3c968f62 100644
--- a/tests/deriving/should_fail/T5478.stderr
+++ b/tests/deriving/should_fail/T5478.stderr
@@ -1,5 +1,5 @@
-
-T5478.hs:6:38:
-    Can't make a derived instance of `Show Foo':
-      Don't know how to derive `Show' for type `ByteArray#'
-    In the data declaration for `Foo'
+
+T5478.hs:6:38:
+    Can't make a derived instance of ‛Show Foo’:
+      Don't know how to derive ‛Show’ for type ‛ByteArray#’
+    In the data declaration for ‛Foo’
diff --git a/tests/deriving/should_fail/T5686.stderr b/tests/deriving/should_fail/T5686.stderr
index 27f998fe9..0bffdf569 100644
--- a/tests/deriving/should_fail/T5686.stderr
+++ b/tests/deriving/should_fail/T5686.stderr
@@ -1,5 +1,5 @@
-
-T5686.hs:4:29:
-    Can't make a derived instance of `Functor U':
-      Constructor `U' must use the type variable only as the last argument of a data type
-    In the data declaration for `U'
+
+T5686.hs:4:29:
+    Can't make a derived instance of ‛Functor U’:
+      Constructor ‛U’ must use the type variable only as the last argument of a data type
+    In the data declaration for ‛U’
diff --git a/tests/deriving/should_fail/T5922.stderr b/tests/deriving/should_fail/T5922.stderr
index 8b8de18d2..1b58511d9 100644
--- a/tests/deriving/should_fail/T5922.stderr
+++ b/tests/deriving/should_fail/T5922.stderr
@@ -1,4 +1,4 @@
-
-T5922.hs:3:42:
-    Illegal deriving item `show'
-    In the data declaration for `Proposition'
+
+T5922.hs:3:42:
+    Illegal deriving item ‛show’
+    In the data declaration for ‛Proposition’
diff --git a/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr b/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr
index fa5633e78..e4c07b522 100644
--- a/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr
+++ b/tests/deriving/should_fail/drvfail-foldable-traversable1.stderr
@@ -16,11 +16,11 @@ drvfail-foldable-traversable1.hs:13:22:
     When deriving the instance for (Traversable Trivial2)
 
 drvfail-foldable-traversable1.hs:17:22:
-    Can't make a derived instance of `Foldable Infinite':
-      Constructor `Infinite' must not contain function types
-    In the data declaration for `Infinite'
+    Can't make a derived instance of ‛Foldable Infinite’:
+      Constructor ‛Infinite’ must not contain function types
+    In the data declaration for ‛Infinite’
 
 drvfail-foldable-traversable1.hs:21:22:
-    Can't make a derived instance of `Traversable (Cont r)':
-      Constructor `Cont' must not contain function types
-    In the data declaration for `Cont'
+    Can't make a derived instance of ‛Traversable (Cont r)’:
+      Constructor ‛Cont’ must not contain function types
+    In the data declaration for ‛Cont’
diff --git a/tests/deriving/should_fail/drvfail-functor1.stderr b/tests/deriving/should_fail/drvfail-functor1.stderr
index 54632ba05..ec0e79499 100644
--- a/tests/deriving/should_fail/drvfail-functor1.stderr
+++ b/tests/deriving/should_fail/drvfail-functor1.stderr
@@ -1,5 +1,5 @@
-
-drvfail-functor1.hs:6:14:
-    Can't make a derived instance of `Functor List':
-      You need -XDeriveFunctor to derive an instance for this class
-    In the data declaration for `List'
+
+drvfail-functor1.hs:6:14:
+    Can't make a derived instance of ‛Functor List’:
+      You need -XDeriveFunctor to derive an instance for this class
+    In the data declaration for ‛List’
diff --git a/tests/deriving/should_fail/drvfail-functor2.stderr b/tests/deriving/should_fail/drvfail-functor2.stderr
index 54dc6f701..8691b3871 100644
--- a/tests/deriving/should_fail/drvfail-functor2.stderr
+++ b/tests/deriving/should_fail/drvfail-functor2.stderr
@@ -3,24 +3,24 @@ drvfail-functor2.hs:1:29: Warning:
     -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
 drvfail-functor2.hs:7:14:
-    Can't make a derived instance of `Functor InFunctionArgument':
-      Constructor `InFunctionArgument' must not use the type variable in a function argument
-    In the newtype declaration for `InFunctionArgument'
+    Can't make a derived instance of ‛Functor InFunctionArgument’:
+      Constructor ‛InFunctionArgument’ must not use the type variable in a function argument
+    In the newtype declaration for ‛InFunctionArgument’
 
 drvfail-functor2.hs:10:14:
-    Can't make a derived instance of `Functor OnSecondArg':
-      Constructor `OnSecondArg' must use the type variable only as the last argument of a data type
-    In the newtype declaration for `OnSecondArg'
+    Can't make a derived instance of ‛Functor OnSecondArg’:
+      Constructor ‛OnSecondArg’ must use the type variable only as the last argument of a data type
+    In the newtype declaration for ‛OnSecondArg’
 
 drvfail-functor2.hs:15:14:
-    Cannot derive well-kinded instance of form `Functor (NoArguments ...)'
-      Class `Functor' expects an argument of kind `* -> *'
-    In the newtype declaration for `NoArguments'
+    Cannot derive well-kinded instance of form ‛Functor (NoArguments ...)’
+      Class ‛Functor’ expects an argument of kind ‛* -> *’
+    In the newtype declaration for ‛NoArguments’
 
 drvfail-functor2.hs:20:14:
-    Can't make a derived instance of `Functor StupidConstraint':
-      Data type `StupidConstraint' must not have a class context (Eq a)
-    In the data declaration for `StupidConstraint'
+    Can't make a derived instance of ‛Functor StupidConstraint’:
+      Data type ‛StupidConstraint’ must not have a class context (Eq a)
+    In the data declaration for ‛StupidConstraint’
 
 drvfail-functor2.hs:26:14:
     No instance for (Functor NoFunctor)
diff --git a/tests/deriving/should_fail/drvfail005.stderr b/tests/deriving/should_fail/drvfail005.stderr
index 327eb7c3c..c77f904dc 100644
--- a/tests/deriving/should_fail/drvfail005.stderr
+++ b/tests/deriving/should_fail/drvfail005.stderr
@@ -1,5 +1,5 @@
-
-drvfail005.hs:4:13:
-    Can't make a derived instance of `Show a (Test a)':
-      `Show a' is not a class
-    In the data declaration for `Test'
+
+drvfail005.hs:4:13:
+    Can't make a derived instance of ‛Show a (Test a)’:
+      ‛Show a’ is not a class
+    In the data declaration for ‛Test’
diff --git a/tests/deriving/should_fail/drvfail009.stderr b/tests/deriving/should_fail/drvfail009.stderr
index 7594baef3..d9592c466 100644
--- a/tests/deriving/should_fail/drvfail009.stderr
+++ b/tests/deriving/should_fail/drvfail009.stderr
@@ -1,23 +1,23 @@
-
-drvfail009.hs:10:31:
-    Can't make a derived instance of `C T1'
-      (even with cunning newtype deriving):
-      `C' does not have arity 1
-    In the newtype declaration for `T1'
-
-drvfail009.hs:13:31:
-    Cannot derive well-kinded instance of form `Monad (T2 ...)'
-      Class `Monad' expects an argument of kind `* -> *'
-    In the newtype declaration for `T2'
-
-drvfail009.hs:16:33:
-    Can't make a derived instance of `Monad T3'
-      (even with cunning newtype deriving):
-      cannot eta-reduce the representation type enough
-    In the newtype declaration for `T3'
-
-drvfail009.hs:19:42:
-    Can't make a derived instance of `Monad T4'
-      (even with cunning newtype deriving):
-      cannot eta-reduce the representation type enough
-    In the newtype declaration for `T4'
+
+drvfail009.hs:10:31:
+    Can't make a derived instance of ‛C T1’
+      (even with cunning newtype deriving):
+      ‛C’ does not have arity 1
+    In the newtype declaration for ‛T1’
+
+drvfail009.hs:13:31:
+    Cannot derive well-kinded instance of form ‛Monad (T2 ...)’
+      Class ‛Monad’ expects an argument of kind ‛* -> *’
+    In the newtype declaration for ‛T2’
+
+drvfail009.hs:16:33:
+    Can't make a derived instance of ‛Monad T3’
+      (even with cunning newtype deriving):
+      cannot eta-reduce the representation type enough
+    In the newtype declaration for ‛T3’
+
+drvfail009.hs:19:42:
+    Can't make a derived instance of ‛Monad T4’
+      (even with cunning newtype deriving):
+      cannot eta-reduce the representation type enough
+    In the newtype declaration for ‛T4’
diff --git a/tests/deriving/should_fail/drvfail011.stderr b/tests/deriving/should_fail/drvfail011.stderr
index 9bb04bfde..6ec1df7a0 100644
--- a/tests/deriving/should_fail/drvfail011.stderr
+++ b/tests/deriving/should_fail/drvfail011.stderr
@@ -1,10 +1,10 @@
 
 drvfail011.hs:8:1:
-    No instance for (Eq a) arising from a use of `=='
+    No instance for (Eq a) arising from a use of ‛==’
     Possible fix: add (Eq a) to the context of the instance declaration
     In the expression: ((a1 == b1))
-    In an equation for `==': == (T1 a1) (T1 b1) = ((a1 == b1))
-    When typechecking the code for  `=='
-      in a standalone derived instance for `Eq (T a)':
+    In an equation for ‛==’: == (T1 a1) (T1 b1) = ((a1 == b1))
+    When typechecking the code for  ‛==’
+      in a standalone derived instance for ‛Eq (T a)’:
       To see the code I am typechecking, use -ddump-deriv
-    In the instance declaration for `Eq (T a)'
+    In the instance declaration for ‛Eq (T a)’
diff --git a/tests/deriving/should_fail/drvfail014.stderr b/tests/deriving/should_fail/drvfail014.stderr
index 47b4aabf4..93a4c7812 100644
--- a/tests/deriving/should_fail/drvfail014.stderr
+++ b/tests/deriving/should_fail/drvfail014.stderr
@@ -1,9 +1,9 @@
-
-drvfail014.hs:8:28:
-    Use deriving( Typeable ) on a data type declaration
-    In the data declaration for `T1'
-
-drvfail014.hs:12:1:
-    Derived typeable instance must be of form (Typeable2 T2)
-    In the stand-alone deriving instance for
-      `(Typeable a, Typeable b) => Typeable (T2 a b)'
+
+drvfail014.hs:8:28:
+    Use deriving( Typeable ) on a data type declaration
+    In the data declaration for ‛T1’
+
+drvfail014.hs:12:1:
+    Derived typeable instance must be of form (Typeable2 T2)
+    In the stand-alone deriving instance for
+      ‛(Typeable a, Typeable b) => Typeable (T2 a b)’
diff --git a/tests/deriving/should_fail/drvfail015.stderr b/tests/deriving/should_fail/drvfail015.stderr
index a7d8ac6cf..7a755c697 100644
--- a/tests/deriving/should_fail/drvfail015.stderr
+++ b/tests/deriving/should_fail/drvfail015.stderr
@@ -1,13 +1,13 @@
-
-drvfail015.hs:10:19:
-    Illegal instance declaration for `Eq T'
-      (All instance types must be of the form (T t1 ... tn)
-       where T is not a synonym.
-       Use -XTypeSynonymInstances if you want to disable this.)
-    In the stand-alone deriving instance for `Eq T'
-
-drvfail015.hs:13:1:
-    Can't make a derived instance of `Eq Handle':
-      The data constructors of `Handle' are not all in scope
-        so you cannot derive an instance for it
-    In the stand-alone deriving instance for `Eq Handle'
+
+drvfail015.hs:10:19:
+    Illegal instance declaration for ‛Eq T’
+      (All instance types must be of the form (T t1 ... tn)
+       where T is not a synonym.
+       Use -XTypeSynonymInstances if you want to disable this.)
+    In the stand-alone deriving instance for ‛Eq T’
+
+drvfail015.hs:13:1:
+    Can't make a derived instance of ‛Eq Handle’:
+      The data constructors of ‛Handle’ are not all in scope
+        so you cannot derive an instance for it
+    In the stand-alone deriving instance for ‛Eq Handle’
diff --git a/tests/driver/T1372/T1372.stderr b/tests/driver/T1372/T1372.stderr
index f06f294da..e332c563a 100644
--- a/tests/driver/T1372/T1372.stderr
+++ b/tests/driver/T1372/T1372.stderr
@@ -1,2 +1,2 @@
 
-Main.hs:5:5: Not in scope: data constructor `T'
+Main.hs:5:5: Not in scope: data constructor ‛T’
diff --git a/tests/driver/T5147/T5147.stderr b/tests/driver/T5147/T5147.stderr
index 6e8427b94..43f0f935d 100644
--- a/tests/driver/T5147/T5147.stderr
+++ b/tests/driver/T5147/T5147.stderr
@@ -1,5 +1,5 @@
 
 A.hs:6:15:
-    No instance for (Show (Fields v)) arising from a use of `show'
+    No instance for (Show (Fields v)) arising from a use of ‛show’
     In the expression: show a
-    In an equation for `showField': showField a = show a
+    In an equation for ‛showField’: showField a = show a
diff --git a/tests/driver/T6037.stderr b/tests/driver/T6037.stderr
index 3059288d1..7b7d07ecb 100644
--- a/tests/driver/T6037.stderr
+++ b/tests/driver/T6037.stderr
@@ -1,5 +1,5 @@
 
 T6037.hs:5:7:
-    Couldn't match expected type `Int' with actual type `()'
+    Couldn't match expected type ‛Int’ with actual type ‛()’
     In the expression: ()
-    In an equation for `f?o': f?o = ()
+    In an equation for ‛f?o’: f?o = ()
diff --git a/tests/driver/bug1677/bug1677.stderr b/tests/driver/bug1677/bug1677.stderr
index bc55b86c2..9ee41b5ca 100644
--- a/tests/driver/bug1677/bug1677.stderr
+++ b/tests/driver/bug1677/bug1677.stderr
@@ -1,5 +1,5 @@
 
 Foo.hs:1:1:
     File name does not match module name:
-    Saw: `Main'
-    Expected: `Foo'
+    Saw: ‛Main’
+    Expected: ‛Foo’
diff --git a/tests/driver/driver063.stderr b/tests/driver/driver063.stderr
index 0a6801537..a50340dc4 100644
--- a/tests/driver/driver063.stderr
+++ b/tests/driver/driver063.stderr
@@ -1,4 +1,4 @@
 
 D063.hs:2:8:
-    Could not find module `A063'
+    Could not find module ‛A063’
     It is not a module in the current program, or in any known package.
diff --git a/tests/driver/recomp001/recomp001.stderr b/tests/driver/recomp001/recomp001.stderr
index 4b95415c8..bd75be7bd 100644
--- a/tests/driver/recomp001/recomp001.stderr
+++ b/tests/driver/recomp001/recomp001.stderr
@@ -1,2 +1,2 @@
 
-C.hs:3:11: Module `B' does not export `foo'
+C.hs:3:11: Module ‛B’ does not export ‛foo’
diff --git a/tests/driver/recomp005/recomp005.stderr b/tests/driver/recomp005/recomp005.stderr
index 8e4ad9383..130e56249 100644
--- a/tests/driver/recomp005/recomp005.stderr
+++ b/tests/driver/recomp005/recomp005.stderr
@@ -1,4 +1,4 @@
 
 C.hs:7:11: Warning:
-    Rule "f/g" may never fire because `f' might inline first
-    Probable fix: add an INLINE[n] or NOINLINE[n] pragma on `f'
+    Rule "f/g" may never fire because ‛f’ might inline first
+    Probable fix: add an INLINE[n] or NOINLINE[n] pragma on ‛f’
diff --git a/tests/driver/werror.stderr b/tests/driver/werror.stderr
index 4bad5e6b4..45c00e93e 100644
--- a/tests/driver/werror.stderr
+++ b/tests/driver/werror.stderr
@@ -3,14 +3,14 @@ werror.hs:6:1: Warning:
     Top-level binding with no type signature: main :: IO ()
 
 werror.hs:7:13: Warning:
-    This binding for `main' shadows the existing binding
+    This binding for ‛main’ shadows the existing binding
       defined at werror.hs:6:1
 
-werror.hs:7:13: Warning: Defined but not used: `main'
+werror.hs:7:13: Warning: Defined but not used: ‛main’
 
 werror.hs:8:1: Warning: Tab character
 
-werror.hs:10:1: Warning: Defined but not used: `f'
+werror.hs:10:1: Warning: Defined but not used: ‛f’
 
 werror.hs:10:1: Warning:
     Top-level binding with no type signature:
@@ -18,11 +18,11 @@ werror.hs:10:1: Warning:
 
 werror.hs:10:1: Warning:
     Pattern match(es) are overlapped
-    In an equation for `f': f [] = ...
+    In an equation for ‛f’: f [] = ...
 
 werror.hs:10:1: Warning:
     Pattern match(es) are non-exhaustive
-    In an equation for `f': Patterns not matched: _ : _
+    In an equation for ‛f’: Patterns not matched: _ : _
 
 <no location info>: 
 Failing due to -Werror.
diff --git a/tests/gadt/T3163.stderr b/tests/gadt/T3163.stderr
index b93b52344..ce6401085 100644
--- a/tests/gadt/T3163.stderr
+++ b/tests/gadt/T3163.stderr
@@ -1,5 +1,5 @@
-
-T3163.hs:8:5:
-    Illegal polymorphic or qualified type: forall s. s
-    In the definition of data constructor `Unreached'
-    In the data declaration for `Taker'
+
+T3163.hs:8:5:
+    Illegal polymorphic or qualified type: forall s. s
+    In the definition of data constructor ‛Unreached’
+    In the data declaration for ‛Taker’
diff --git a/tests/gadt/T3169.stderr b/tests/gadt/T3169.stderr
index 62f49d467..292342031 100644
--- a/tests/gadt/T3169.stderr
+++ b/tests/gadt/T3169.stderr
@@ -3,7 +3,7 @@ T3169.hs:13:22:
     Could not deduce (elt ~ Map b elt)
     from the context (Key a, Key b)
       bound by the instance declaration at T3169.hs:10:10-36
-      `elt' is a rigid type variable bound by
+      ‛elt’ is a rigid type variable bound by
             the type signature for
               lookup :: (a, b) -> Map (a, b) elt -> Maybe elt
             at T3169.hs:12:3
@@ -14,7 +14,7 @@ T3169.hs:13:22:
         (bound at T3169.hs:12:3)
       b :: b (bound at T3169.hs:12:13)
       m :: Map (a, b) elt (bound at T3169.hs:12:17)
-    In the second argument of `lookup', namely `m'
+    In the second argument of ‛lookup’, namely ‛m’
     In the expression: lookup a m :: Maybe (Map b elt)
     In the expression:
       case lookup a m :: Maybe (Map b elt) of {
diff --git a/tests/gadt/T3651.stderr b/tests/gadt/T3651.stderr
index 778fe0feb..8f53dc05e 100644
--- a/tests/gadt/T3651.stderr
+++ b/tests/gadt/T3651.stderr
@@ -1,35 +1,35 @@
 
 T3651.hs:11:11:
-    Couldn't match type `Bool' with `()'
+    Couldn't match type ‛Bool’ with ‛()’
     Inaccessible code in
-      a pattern with constructor U :: Z (), in an equation for `unsafe1'
+      a pattern with constructor U :: Z (), in an equation for ‛unsafe1’
     In the pattern: U
-    In an equation for `unsafe1': unsafe1 B U = ()
+    In an equation for ‛unsafe1’: unsafe1 B U = ()
 
 T3651.hs:11:15:
-    Couldn't match type `Bool' with `()'
+    Couldn't match type ‛Bool’ with ‛()’
     Expected type: a
       Actual type: ()
     In the expression: ()
-    In an equation for `unsafe1': unsafe1 B U = ()
+    In an equation for ‛unsafe1’: unsafe1 B U = ()
 
 T3651.hs:14:11:
-    Couldn't match type `Bool' with `()'
+    Couldn't match type ‛Bool’ with ‛()’
     Inaccessible code in
-      a pattern with constructor U :: Z (), in an equation for `unsafe2'
+      a pattern with constructor U :: Z (), in an equation for ‛unsafe2’
     In the pattern: U
-    In an equation for `unsafe2': unsafe2 B U = ()
+    In an equation for ‛unsafe2’: unsafe2 B U = ()
 
 T3651.hs:14:15:
-    Couldn't match type `Bool' with `()'
+    Couldn't match type ‛Bool’ with ‛()’
     Expected type: a
       Actual type: ()
     In the expression: ()
-    In an equation for `unsafe2': unsafe2 B U = ()
+    In an equation for ‛unsafe2’: unsafe2 B U = ()
 
 T3651.hs:17:11:
-    Couldn't match type `Bool' with `()'
+    Couldn't match type ‛Bool’ with ‛()’
     Inaccessible code in
-      a pattern with constructor U :: Z (), in an equation for `unsafe3'
+      a pattern with constructor U :: Z (), in an equation for ‛unsafe3’
     In the pattern: U
-    In an equation for `unsafe3': unsafe3 B U = True
+    In an equation for ‛unsafe3’: unsafe3 B U = True
diff --git a/tests/gadt/T7293.stderr b/tests/gadt/T7293.stderr
index 61cdc25f3..98a4fe402 100644
--- a/tests/gadt/T7293.stderr
+++ b/tests/gadt/T7293.stderr
@@ -1,9 +1,9 @@
 
 T7293.hs:24:5:
-    Couldn't match type 'False with 'True
+    Couldn't match type ‛'False’ with ‛'True’
     Inaccessible code in
       a pattern with constructor
         Nil :: forall a. Vec a 'Zero,
-      in an equation for `nth'
+      in an equation for ‛nth’
     In the pattern: Nil
-    In an equation for `nth': nth Nil _ = undefined
+    In an equation for ‛nth’: nth Nil _ = undefined
diff --git a/tests/gadt/T7294.stderr b/tests/gadt/T7294.stderr
index dc1eef1ca..bfb64966f 100644
--- a/tests/gadt/T7294.stderr
+++ b/tests/gadt/T7294.stderr
@@ -1,9 +1,9 @@
 
 T7294.hs:25:5: Warning:
-    Couldn't match type 'False with 'True
+    Couldn't match type ‛'False’ with ‛'True’
     Inaccessible code in
       a pattern with constructor
         Nil :: forall a. Vec a 'Zero,
-      in an equation for `nth'
+      in an equation for ‛nth’
     In the pattern: Nil
-    In an equation for `nth': nth Nil _ = undefined
+    In an equation for ‛nth’: nth Nil _ = undefined
diff --git a/tests/gadt/gadt-escape1.stderr b/tests/gadt/gadt-escape1.stderr
index 53885ffaf..fbc1b6703 100644
--- a/tests/gadt/gadt-escape1.stderr
+++ b/tests/gadt/gadt-escape1.stderr
@@ -1,19 +1,19 @@
-
-gadt-escape1.hs:19:58:
-    Couldn't match type `t' with `ExpGADT Int'
-      `t' is untouchable
-        inside the constraints (t1 ~ Int)
-        bound by a pattern with constructor
-                   ExpInt :: Int -> ExpGADT Int,
-                 in a case alternative
-        at gadt-escape1.hs:19:43-50
-      `t' is a rigid type variable bound by
-          the inferred type of weird1 :: t at gadt-escape1.hs:19:1
-    Expected type: t
-      Actual type: ExpGADT t1
-    Relevant bindings include
-      weird1 :: t (bound at gadt-escape1.hs:19:1)
-    In the expression: a
-    In a case alternative: Hidden (ExpInt _) a -> a
-    In the expression:
-      case (hval :: Hidden) of { Hidden (ExpInt _) a -> a }
+
+gadt-escape1.hs:19:58:
+    Couldn't match type ‛t’ with ‛ExpGADT Int’
+      ‛t’ is untouchable
+        inside the constraints (t1 ~ Int)
+        bound by a pattern with constructor
+                   ExpInt :: Int -> ExpGADT Int,
+                 in a case alternative
+        at gadt-escape1.hs:19:43-50
+      ‛t’ is a rigid type variable bound by
+          the inferred type of weird1 :: t at gadt-escape1.hs:19:1
+    Expected type: t
+      Actual type: ExpGADT t1
+    Relevant bindings include
+      weird1 :: t (bound at gadt-escape1.hs:19:1)
+    In the expression: a
+    In a case alternative: Hidden (ExpInt _) a -> a
+    In the expression:
+      case (hval :: Hidden) of { Hidden (ExpInt _) a -> a }
diff --git a/tests/gadt/gadt10.stderr b/tests/gadt/gadt10.stderr
index e244eca05..fa485aade 100644
--- a/tests/gadt/gadt10.stderr
+++ b/tests/gadt/gadt10.stderr
@@ -1,7 +1,7 @@
-
-gadt10.hs:6:24:
-    Expecting one more argument to `RInt'
-    Expected kind `*', but `RInt' has kind `k0 -> *'
-    In the type `RInt'
-    In the definition of data constructor `R'
-    In the data declaration for `RInt'
+
+gadt10.hs:6:24:
+    Expecting one more argument to ‛RInt’
+    Expected kind ‛*’, but ‛RInt’ has kind ‛k0 -> *’
+    In the type ‛RInt’
+    In the definition of data constructor ‛R’
+    In the data declaration for ‛RInt’
diff --git a/tests/gadt/gadt11.stderr b/tests/gadt/gadt11.stderr
index bfe38d43b..96f636c0a 100644
--- a/tests/gadt/gadt11.stderr
+++ b/tests/gadt/gadt11.stderr
@@ -1,6 +1,6 @@
-
-gadt11.hs:9:3:
-    Data constructor `B1' returns type `X []'
-      instead of an instance of its parent type `B a'
-    In the definition of data constructor `B1'
-    In the data declaration for `B'
+
+gadt11.hs:9:3:
+    Data constructor ‛B1’ returns type ‛X []’
+      instead of an instance of its parent type ‛B a’
+    In the definition of data constructor ‛B1’
+    In the data declaration for ‛B’
diff --git a/tests/gadt/gadt13.stderr b/tests/gadt/gadt13.stderr
index b03ff492f..3b39f07b8 100644
--- a/tests/gadt/gadt13.stderr
+++ b/tests/gadt/gadt13.stderr
@@ -1,16 +1,16 @@
-
-gadt13.hs:15:13:
-    Couldn't match expected type `t'
-                with actual type `String -> [Char]'
-      `t' is untouchable
-        inside the constraints (t1 ~ Int)
-        bound by a pattern with constructor
-                   I :: Int -> Term Int,
-                 in an equation for `shw'
-        at gadt13.hs:15:6-8
-      `t' is a rigid type variable bound by
-          the inferred type of shw :: Term t1 -> t at gadt13.hs:15:1
-    Relevant bindings include
-      shw :: Term t1 -> t (bound at gadt13.hs:15:1)
-    In the expression: ("I " ++) . shows t
-    In an equation for `shw': shw (I t) = ("I " ++) . shows t
+
+gadt13.hs:15:13:
+    Couldn't match expected type ‛t’
+                with actual type ‛String -> [Char]’
+      ‛t’ is untouchable
+        inside the constraints (t1 ~ Int)
+        bound by a pattern with constructor
+                   I :: Int -> Term Int,
+                 in an equation for ‛shw’
+        at gadt13.hs:15:6-8
+      ‛t’ is a rigid type variable bound by
+          the inferred type of shw :: Term t1 -> t at gadt13.hs:15:1
+    Relevant bindings include
+      shw :: Term t1 -> t (bound at gadt13.hs:15:1)
+    In the expression: ("I " ++) . shows t
+    In an equation for ‛shw’: shw (I t) = ("I " ++) . shows t
diff --git a/tests/gadt/gadt21.stderr b/tests/gadt/gadt21.stderr
index 061c56346..0293eaafb 100644
--- a/tests/gadt/gadt21.stderr
+++ b/tests/gadt/gadt21.stderr
@@ -1,20 +1,19 @@
 
 gadt21.hs:21:60:
-    Could not deduce (Ord a1) arising from a use of `f'
+    Could not deduce (Ord a1) arising from a use of ‛f’
     from the context (a ~ Set a1)
       bound by a pattern with constructor
                  TypeSet :: forall a. Type a -> Type (Set a),
-               in an equation for `withOrdDynExpr'
+               in an equation for ‛withOrdDynExpr’
       at gadt21.hs:21:35-43
     Possible fix:
       add (Ord a1) to the context of
-        the data constructor `TypeSet'
-        or the data constructor `DynExpr'
+        the data constructor ‛TypeSet’
+        or the data constructor ‛DynExpr’
         or the type signature for
              withOrdDynExpr :: DynExpr
-                               -> (forall a. Ord a => Expr a -> b)
-                               -> Maybe b
-    In the first argument of `Just', namely `(f e)'
+                               -> (forall a. Ord a => Expr a -> b) -> Maybe b
+    In the first argument of ‛Just’, namely ‛(f e)’
     In the expression: Just (f e)
-    In an equation for `withOrdDynExpr':
+    In an equation for ‛withOrdDynExpr’:
         withOrdDynExpr (DynExpr e@(Const (TypeSet _) _)) f = Just (f e)
diff --git a/tests/gadt/gadt7.stderr b/tests/gadt/gadt7.stderr
index 561b0b52b..186bfd33f 100644
--- a/tests/gadt/gadt7.stderr
+++ b/tests/gadt/gadt7.stderr
@@ -1,20 +1,20 @@
-
-gadt7.hs:16:38:
-    Couldn't match expected type `t' with actual type `t1'
-      `t1' is untouchable
-        inside the constraints (t2 ~ Int)
-        bound by a pattern with constructor
-                   K :: T Int,
-                 in a case alternative
-        at gadt7.hs:16:33
-      `t1' is a rigid type variable bound by
-           the inferred type of i1b :: T t2 -> t1 -> t at gadt7.hs:16:1
-      `t' is a rigid type variable bound by
-          the inferred type of i1b :: T t2 -> t1 -> t at gadt7.hs:16:1
-    Relevant bindings include
-      i1b :: T t2 -> t1 -> t (bound at gadt7.hs:16:1)
-      y :: t1 (bound at gadt7.hs:16:7)
-      y1 :: t1 (bound at gadt7.hs:16:16)
-    In the expression: y1
-    In a case alternative: K -> y1
-    In the expression: case t1 of { K -> y1 }
+
+gadt7.hs:16:38:
+    Couldn't match expected type ‛t’ with actual type ‛t1’
+      ‛t1’ is untouchable
+        inside the constraints (t2 ~ Int)
+        bound by a pattern with constructor
+                   K :: T Int,
+                 in a case alternative
+        at gadt7.hs:16:33
+      ‛t1’ is a rigid type variable bound by
+           the inferred type of i1b :: T t2 -> t1 -> t at gadt7.hs:16:1
+      ‛t’ is a rigid type variable bound by
+          the inferred type of i1b :: T t2 -> t1 -> t at gadt7.hs:16:1
+    Relevant bindings include
+      i1b :: T t2 -> t1 -> t (bound at gadt7.hs:16:1)
+      y :: t1 (bound at gadt7.hs:16:7)
+      y1 :: t1 (bound at gadt7.hs:16:16)
+    In the expression: y1
+    In a case alternative: K -> y1
+    In the expression: case t1 of { K -> y1 }
diff --git a/tests/gadt/gadtSyntaxFail001.stderr b/tests/gadt/gadtSyntaxFail001.stderr
index aa837b7a8..53b198a14 100644
--- a/tests/gadt/gadtSyntaxFail001.stderr
+++ b/tests/gadt/gadtSyntaxFail001.stderr
@@ -1,6 +1,6 @@
-
-gadtSyntaxFail001.hs:8:5:
-    Data constructor `C2' has existential type variables, a context, or a specialised result type
-      (Use -XExistentialQuantification or -XGADTs to allow this)
-    In the definition of data constructor `C2'
-    In the data declaration for `Foo'
+
+gadtSyntaxFail001.hs:8:5:
+    Data constructor ‛C2’ has existential type variables, a context, or a specialised result type
+      (Use -XExistentialQuantification or -XGADTs to allow this)
+    In the definition of data constructor ‛C2’
+    In the data declaration for ‛Foo’
diff --git a/tests/gadt/gadtSyntaxFail002.stderr b/tests/gadt/gadtSyntaxFail002.stderr
index a2b101a97..ca1060d8e 100644
--- a/tests/gadt/gadtSyntaxFail002.stderr
+++ b/tests/gadt/gadtSyntaxFail002.stderr
@@ -1,6 +1,6 @@
-
-gadtSyntaxFail002.hs:8:5:
-    Data constructor `C2' has existential type variables, a context, or a specialised result type
-      (Use -XExistentialQuantification or -XGADTs to allow this)
-    In the definition of data constructor `C2'
-    In the data declaration for `Foo'
+
+gadtSyntaxFail002.hs:8:5:
+    Data constructor ‛C2’ has existential type variables, a context, or a specialised result type
+      (Use -XExistentialQuantification or -XGADTs to allow this)
+    In the definition of data constructor ‛C2’
+    In the data declaration for ‛Foo’
diff --git a/tests/gadt/gadtSyntaxFail003.stderr b/tests/gadt/gadtSyntaxFail003.stderr
index 3cd4611cd..eb2e370a6 100644
--- a/tests/gadt/gadtSyntaxFail003.stderr
+++ b/tests/gadt/gadtSyntaxFail003.stderr
@@ -1,6 +1,6 @@
-
-gadtSyntaxFail003.hs:7:5:
-    Data constructor `C1' has existential type variables, a context, or a specialised result type
-      (Use -XExistentialQuantification or -XGADTs to allow this)
-    In the definition of data constructor `C1'
-    In the data declaration for `Foo'
+
+gadtSyntaxFail003.hs:7:5:
+    Data constructor ‛C1’ has existential type variables, a context, or a specialised result type
+      (Use -XExistentialQuantification or -XGADTs to allow this)
+    In the definition of data constructor ‛C1’
+    In the data declaration for ‛Foo’
diff --git a/tests/gadt/lazypat.stderr b/tests/gadt/lazypat.stderr
index d64f40e48..460c600b3 100644
--- a/tests/gadt/lazypat.stderr
+++ b/tests/gadt/lazypat.stderr
@@ -4,4 +4,4 @@ lazypat.hs:7:5:
       inside a lazy (~) pattern
     In the pattern: T x f
     In the pattern: ~(T x f)
-    In an equation for `f': f ~(T x f) = f x
+    In an equation for ‛f’: f ~(T x f) = f x
diff --git a/tests/gadt/records-fail1.stderr b/tests/gadt/records-fail1.stderr
index 829114e51..690649d46 100644
--- a/tests/gadt/records-fail1.stderr
+++ b/tests/gadt/records-fail1.stderr
@@ -1,5 +1,5 @@
-
-records-fail1.hs:7:1:
-    Constructors T1 and T4 have a common field `x',
-      but have different result types
-    In the data declaration for `T'
+
+records-fail1.hs:7:1:
+    Constructors T1 and T4 have a common field ‛x’,
+      but have different result types
+    In the data declaration for ‛T’
diff --git a/tests/gadt/rw.stderr b/tests/gadt/rw.stderr
index ef5453ca6..584c94475 100644
--- a/tests/gadt/rw.stderr
+++ b/tests/gadt/rw.stderr
@@ -1,20 +1,20 @@
 
 rw.hs:14:47:
-    Couldn't match expected type `a' with actual type `Int'
-      `a' is a rigid type variable bound by
+    Couldn't match expected type ‛a’ with actual type ‛Int’
+      ‛a’ is a rigid type variable bound by
           the type signature for writeInt :: T a -> IORef a -> IO ()
           at rw.hs:12:12
     Relevant bindings include
       writeInt :: T a -> IORef a -> IO () (bound at rw.hs:13:1)
       v :: T a (bound at rw.hs:13:10)
       ref :: IORef a (bound at rw.hs:13:12)
-    In the second argument of `writeIORef', namely `(1 :: Int)'
+    In the second argument of ‛writeIORef’, namely ‛(1 :: Int)’
     In the expression: writeIORef ref (1 :: Int)
     In a case alternative: ~(Li x) -> writeIORef ref (1 :: Int)
 
 rw.hs:19:51:
-    Couldn't match type `a' with `Bool'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛Bool’
+      ‛a’ is a rigid type variable bound by
           the type signature for readBool :: T a -> IORef a -> IO ()
           at rw.hs:16:12
     Expected type: a -> Bool
@@ -23,6 +23,6 @@ rw.hs:19:51:
       readBool :: T a -> IORef a -> IO () (bound at rw.hs:17:1)
       v :: T a (bound at rw.hs:17:10)
       ref :: IORef a (bound at rw.hs:17:12)
-    In the second argument of `(.)', namely `not'
-    In the second argument of `(>>=)', namely `(print . not)'
+    In the second argument of ‛(.)’, namely ‛not’
+    In the second argument of ‛(>>=)’, namely ‛(print . not)’
     In the expression: readIORef ref >>= (print . not)
diff --git a/tests/generics/GenCannotDoRep0.stderr b/tests/generics/GenCannotDoRep0.stderr
index 291ab14b5..d216a703b 100644
--- a/tests/generics/GenCannotDoRep0.stderr
+++ b/tests/generics/GenCannotDoRep0.stderr
@@ -3,21 +3,21 @@ GenCannotDoRep0.hs:6:14: Warning:
     -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
 GenCannotDoRep0.hs:13:45:
-    Can't make a derived instance of `Generic Dynamic':
+    Can't make a derived instance of ‛Generic Dynamic’:
       Dynamic must be a vanilla data constructor
-    In the data declaration for `Dynamic'
+    In the data declaration for ‛Dynamic’
 
 GenCannotDoRep0.hs:17:1:
-    Can't make a derived instance of `Generic (P Int)':
+    Can't make a derived instance of ‛Generic (P Int)’:
       P must not be instantiated; try deriving `P a' instead
-    In the stand-alone deriving instance for `Generic (P Int)'
+    In the stand-alone deriving instance for ‛Generic (P Int)’
 
 GenCannotDoRep0.hs:26:1:
-    Can't make a derived instance of `Generic (D Char Char)':
+    Can't make a derived instance of ‛Generic (D Char Char)’:
       D must not be instantiated; try deriving `D Char b' instead
-    In the stand-alone deriving instance for `Generic (D Char Char)'
+    In the stand-alone deriving instance for ‛Generic (D Char Char)’
 
 GenCannotDoRep0.hs:28:1:
-    Can't make a derived instance of `Generic (D Int a)':
+    Can't make a derived instance of ‛Generic (D Int a)’:
       D must not have a datatype context
-    In the stand-alone deriving instance for `Generic (D Int a)'
+    In the stand-alone deriving instance for ‛Generic (D Int a)’
diff --git a/tests/generics/GenCannotDoRep1.stderr b/tests/generics/GenCannotDoRep1.stderr
index dde1d5b0d..7e0f124b1 100644
--- a/tests/generics/GenCannotDoRep1.stderr
+++ b/tests/generics/GenCannotDoRep1.stderr
@@ -1,8 +1,8 @@
-
-GenCannotDoRep1.hs:1:29: Warning:
-    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
-
-GenCannotDoRep1.hs:8:49:
-    Can't make a derived instance of `Generic (Context a)':
-      Context must not have a datatype context
-    In the data declaration for `Context'
+
+GenCannotDoRep1.hs:1:29: Warning:
+    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
+
+GenCannotDoRep1.hs:8:49:
+    Can't make a derived instance of ‛Generic (Context a)’:
+      Context must not have a datatype context
+    In the data declaration for ‛Context’
diff --git a/tests/generics/GenCannotDoRep1_0.stderr b/tests/generics/GenCannotDoRep1_0.stderr
index 2e602af0e..c75205a38 100644
--- a/tests/generics/GenCannotDoRep1_0.stderr
+++ b/tests/generics/GenCannotDoRep1_0.stderr
@@ -1,5 +1,5 @@
 
 GenCannotDoRep1_0.hs:9:49:
-    Can't make a derived instance of `Generic1 Dynamic':
+    Can't make a derived instance of ‛Generic1 Dynamic’:
       Dynamic must be a vanilla data constructor
-    In the data declaration for `Dynamic'
+    In the data declaration for ‛Dynamic’
diff --git a/tests/generics/GenCannotDoRep1_1.stderr b/tests/generics/GenCannotDoRep1_1.stderr
index df9f518c6..97eeca51a 100644
--- a/tests/generics/GenCannotDoRep1_1.stderr
+++ b/tests/generics/GenCannotDoRep1_1.stderr
@@ -3,6 +3,6 @@ GenCannotDoRep1_1.hs:1:29: Warning:
     -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
 GenCannotDoRep1_1.hs:8:49:
-    Can't make a derived instance of `Generic1 Context':
+    Can't make a derived instance of ‛Generic1 Context’:
       Context must not have a datatype context
-    In the data declaration for `Context'
+    In the data declaration for ‛Context’
diff --git a/tests/generics/GenCannotDoRep1_2.stderr b/tests/generics/GenCannotDoRep1_2.stderr
index ffda5ffd2..32aebb7fc 100644
--- a/tests/generics/GenCannotDoRep1_2.stderr
+++ b/tests/generics/GenCannotDoRep1_2.stderr
@@ -1,5 +1,5 @@
 
 GenCannotDoRep1_2.hs:13:1:
-    Can't make a derived instance of `Generic1 Term':
+    Can't make a derived instance of ‛Generic1 Term’:
       Int must be a vanilla data constructor
-    In the stand-alone deriving instance for `Generic1 Term'
+    In the stand-alone deriving instance for ‛Generic1 Term’
diff --git a/tests/generics/GenCannotDoRep1_3.stderr b/tests/generics/GenCannotDoRep1_3.stderr
index 7312a9515..7e54463ff 100644
--- a/tests/generics/GenCannotDoRep1_3.stderr
+++ b/tests/generics/GenCannotDoRep1_3.stderr
@@ -1,5 +1,5 @@
 
 GenCannotDoRep1_3.hs:11:33:
-    Can't make a derived instance of `Generic1 T':
-      Constructor `T' must use the last type parameter only as the last argument of a data type, newtype, or (->)
-    In the data declaration for `T'
+    Can't make a derived instance of ‛Generic1 T’:
+      Constructor ‛T’ must use the last type parameter only as the last argument of a data type, newtype, or (->)
+    In the data declaration for ‛T’
diff --git a/tests/generics/GenCannotDoRep1_4.stderr b/tests/generics/GenCannotDoRep1_4.stderr
index 2a8d2a699..e4b39838d 100644
--- a/tests/generics/GenCannotDoRep1_4.stderr
+++ b/tests/generics/GenCannotDoRep1_4.stderr
@@ -1,5 +1,5 @@
 
 GenCannotDoRep1_4.hs:8:34:
-    Can't make a derived instance of `Generic1 T':
-      Constructor `T' must use the last type parameter only as the last argument of a data type, newtype, or (->)
-    In the data declaration for `T'
+    Can't make a derived instance of ‛Generic1 T’:
+      Constructor ‛T’ must use the last type parameter only as the last argument of a data type, newtype, or (->)
+    In the data declaration for ‛T’
diff --git a/tests/generics/GenCannotDoRep1_5.stderr b/tests/generics/GenCannotDoRep1_5.stderr
index 13d25089a..21e849098 100644
--- a/tests/generics/GenCannotDoRep1_5.stderr
+++ b/tests/generics/GenCannotDoRep1_5.stderr
@@ -1,5 +1,5 @@
 
 GenCannotDoRep1_5.hs:9:32:
-    Can't make a derived instance of `Generic1 T':
-      Constructor `T' must use the last type parameter only as the last argument of a data type, newtype, or (->)
-    In the data declaration for `T'
+    Can't make a derived instance of ‛Generic1 T’:
+      Constructor ‛T’ must use the last type parameter only as the last argument of a data type, newtype, or (->)
+    In the data declaration for ‛T’
diff --git a/tests/generics/GenCannotDoRep1_6.stderr b/tests/generics/GenCannotDoRep1_6.stderr
index 16b822e1c..06d95b223 100644
--- a/tests/generics/GenCannotDoRep1_6.stderr
+++ b/tests/generics/GenCannotDoRep1_6.stderr
@@ -1,5 +1,5 @@
 
 GenCannotDoRep1_6.hs:9:43:
-    Can't make a derived instance of `Generic1 T':
-      Constructor `T' must use the last type parameter only as the last argument of a data type, newtype, or (->)
-    In the data declaration for `T'
+    Can't make a derived instance of ‛Generic1 T’:
+      Constructor ‛T’ must use the last type parameter only as the last argument of a data type, newtype, or (->)
+    In the data declaration for ‛T’
diff --git a/tests/generics/GenCannotDoRep1_7.stderr b/tests/generics/GenCannotDoRep1_7.stderr
index 3b6af68fb..2830a6d77 100644
--- a/tests/generics/GenCannotDoRep1_7.stderr
+++ b/tests/generics/GenCannotDoRep1_7.stderr
@@ -1,5 +1,5 @@
 
 GenCannotDoRep1_7.hs:11:29:
-    Can't make a derived instance of `Generic1 T':
+    Can't make a derived instance of ‛Generic1 T’:
       must not apply type constructors that cannot be represented with `Rep1' (such as `B') to arguments that involve the last type parameter
-    In the data declaration for `T'
+    In the data declaration for ‛T’
diff --git a/tests/generics/GenCannotDoRep1_8.stderr b/tests/generics/GenCannotDoRep1_8.stderr
index c0d692907..305944471 100644
--- a/tests/generics/GenCannotDoRep1_8.stderr
+++ b/tests/generics/GenCannotDoRep1_8.stderr
@@ -1,5 +1,5 @@
 
 GenCannotDoRep1_8.hs:12:30:
-    Can't make a derived instance of `Generic1 T':
-      Constructor `T' must use the last type parameter only as the last argument of a data type, newtype, or (->)
-    In the data declaration for `T'
+    Can't make a derived instance of ‛Generic1 T’:
+      Constructor ‛T’ must use the last type parameter only as the last argument of a data type, newtype, or (->)
+    In the data declaration for ‛T’
diff --git a/tests/generics/GenCannotDoRep2.stderr b/tests/generics/GenCannotDoRep2.stderr
index 35caf2c3b..635102310 100644
--- a/tests/generics/GenCannotDoRep2.stderr
+++ b/tests/generics/GenCannotDoRep2.stderr
@@ -1,5 +1,5 @@
 
 GenCannotDoRep2.hs:13:1:
-    Can't make a derived instance of `Generic (Term a)':
+    Can't make a derived instance of ‛Generic (Term a)’:
       Int must be a vanilla data constructor
-    In the stand-alone deriving instance for `Generic (Term a)'
+    In the stand-alone deriving instance for ‛Generic (Term a)’
diff --git a/tests/generics/GenShouldFail0.stderr b/tests/generics/GenShouldFail0.stderr
index 3685e6778..f85cd9289 100644
--- a/tests/generics/GenShouldFail0.stderr
+++ b/tests/generics/GenShouldFail0.stderr
@@ -1,5 +1,5 @@
 
 GenShouldFail0.hs:9:1:
-    Can't make a derived instance of `Generic X':
+    Can't make a derived instance of ‛Generic X’:
       You need -XDeriveGeneric to derive an instance for this class
-    In the stand-alone deriving instance for `Generic X'
+    In the stand-alone deriving instance for ‛Generic X’
diff --git a/tests/generics/GenShouldFail1_0.stderr b/tests/generics/GenShouldFail1_0.stderr
index 9b7ba3ef0..00779d00e 100644
--- a/tests/generics/GenShouldFail1_0.stderr
+++ b/tests/generics/GenShouldFail1_0.stderr
@@ -1,5 +1,5 @@
 
 GenShouldFail1_0.hs:9:1:
-    Can't make a derived instance of `Generic1 X':
+    Can't make a derived instance of ‛Generic1 X’:
       You need -XDeriveGeneric to derive an instance for this class
-    In the stand-alone deriving instance for `Generic1 X'
+    In the stand-alone deriving instance for ‛Generic1 X’
diff --git a/tests/ghc-api/apirecomp001/apirecomp001.stderr b/tests/ghc-api/apirecomp001/apirecomp001.stderr
index 920a10a79..b7666b7a4 100644
--- a/tests/ghc-api/apirecomp001/apirecomp001.stderr
+++ b/tests/ghc-api/apirecomp001/apirecomp001.stderr
@@ -4,12 +4,12 @@ B.hs:4:1: Warning:
       answer_to_live_the_universe_and_everything :: Int
 
 B.hs:5:12: Warning:
-    Defaulting the following constraint(s) to type `Integer'
+    Defaulting the following constraint(s) to type ‛Integer’
       (Enum a0)
-        arising from the arithmetic sequence `1 .. 23 * 2' at B.hs:5:12-20
-      (Num a0) arising from the literal `1' at B.hs:5:13
-    In the first argument of `length', namely `[1 .. 23 * 2]'
-    In the first argument of `(-)', namely `length [1 .. 23 * 2]'
+        arising from the arithmetic sequence ‛1 .. 23 * 2’ at B.hs:5:12-20
+      (Num a0) arising from the literal ‛1’ at B.hs:5:13
+    In the first argument of ‛length’, namely ‛[1 .. 23 * 2]’
+    In the first argument of ‛(-)’, namely ‛length [1 .. 23 * 2]’
     In the expression: length [1 .. 23 * 2] - 4
 
 A.hs:7:1: Warning:
@@ -20,12 +20,12 @@ B.hs:4:1: Warning:
       answer_to_live_the_universe_and_everything :: Int
 
 B.hs:5:12: Warning:
-    Defaulting the following constraint(s) to type `Integer'
+    Defaulting the following constraint(s) to type ‛Integer’
       (Enum a0)
-        arising from the arithmetic sequence `1 .. 23 * 2' at B.hs:5:12-20
-      (Num a0) arising from the literal `1' at B.hs:5:13
-    In the first argument of `length', namely `[1 .. 23 * 2]'
-    In the first argument of `(-)', namely `length [1 .. 23 * 2]'
+        arising from the arithmetic sequence ‛1 .. 23 * 2’ at B.hs:5:12-20
+      (Num a0) arising from the literal ‛1’ at B.hs:5:13
+    In the first argument of ‛length’, namely ‛[1 .. 23 * 2]’
+    In the first argument of ‛(-)’, namely ‛length [1 .. 23 * 2]’
     In the expression: length [1 .. 23 * 2] - 4
 
 A.hs:7:1: Warning:
diff --git a/tests/ghc-e/should_run/T2636.stderr b/tests/ghc-e/should_run/T2636.stderr
index 369890fa2..dbe70bece 100644
--- a/tests/ghc-e/should_run/T2636.stderr
+++ b/tests/ghc-e/should_run/T2636.stderr
@@ -1,4 +1,4 @@
 
 T2636.hs:1:8:
-    Could not find module `MissingModule'
+    Could not find module ‛MissingModule’
     Use -v to see a list of the files searched for.
diff --git a/tests/ghci.debugger/scripts/break003.stderr b/tests/ghci.debugger/scripts/break003.stderr
index fc7bb337d..c1dda071d 100644
--- a/tests/ghci.debugger/scripts/break003.stderr
+++ b/tests/ghci.debugger/scripts/break003.stderr
@@ -1,4 +1,4 @@
 
 <interactive>:5:1:
-    No instance for (Show (t -> t1)) arising from a use of `print'
+    No instance for (Show (t -> t1)) arising from a use of ‛print’
     In a stmt of an interactive GHCi command: print it
diff --git a/tests/ghci.debugger/scripts/break006.stderr b/tests/ghci.debugger/scripts/break006.stderr
index 9543d675e..7e2261718 100644
--- a/tests/ghci.debugger/scripts/break006.stderr
+++ b/tests/ghci.debugger/scripts/break006.stderr
@@ -1,26 +1,26 @@
 
 <interactive>:6:1:
-    No instance for (Show t1) arising from a use of `print'
-    Cannot resolve unknown runtime type `t1'
+    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 Double -- Defined in `GHC.Float'
-      instance Show Float -- Defined in `GHC.Float'
+      instance Show Double -- Defined in ‛GHC.Float’
+      instance Show Float -- Defined in ‛GHC.Float’
       instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
+        -- Defined in ‛GHC.Real’
       ...plus 23 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'
+    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 Double -- Defined in `GHC.Float'
-      instance Show Float -- Defined in `GHC.Float'
+      instance Show Double -- Defined in ‛GHC.Float’
+      instance Show Float -- Defined in ‛GHC.Float’
       instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
+        -- Defined in ‛GHC.Real’
       ...plus 23 others
     In a stmt of an interactive GHCi command: print it
diff --git a/tests/ghci.debugger/scripts/break019.stderr b/tests/ghci.debugger/scripts/break019.stderr
index fe27afda1..41ec1e89e 100644
--- a/tests/ghci.debugger/scripts/break019.stderr
+++ b/tests/ghci.debugger/scripts/break019.stderr
@@ -1,2 +1,2 @@
-
-Top level: Not in scope: data constructor `Test2'
+
+Top level: Not in scope: data constructor ‛Test2’
diff --git a/tests/ghci.debugger/scripts/dynbrk001.stderr b/tests/ghci.debugger/scripts/dynbrk001.stderr
index adb8dca65..ebc73e5d8 100644
--- a/tests/ghci.debugger/scripts/dynbrk001.stderr
+++ b/tests/ghci.debugger/scripts/dynbrk001.stderr
@@ -1,4 +1,4 @@
 
 <no location info>:
-    Could not find module `NonModule'
+    Could not find module ‛NonModule’
     It is not a module in the current program, or in any known package.
diff --git a/tests/ghci.debugger/scripts/dynbrk001.stdout b/tests/ghci.debugger/scripts/dynbrk001.stdout
index 3d8780cee..358f44990 100644
--- a/tests/ghci.debugger/scripts/dynbrk001.stdout
+++ b/tests/ghci.debugger/scripts/dynbrk001.stdout
@@ -2,4 +2,4 @@ Breakpoint 1 does not exist
 No breakpoints found at that location.
 No active breakpoints.
 [4,8,15,16,23,42]
-map :: forall a b. (a -> b) -> [a] -> [b] 	-- Defined in `GHC.Base'
+map :: forall a b. (a -> b) -> [a] -> [b] 	-- Defined in ‛GHC.Base’
diff --git a/tests/ghci.debugger/scripts/print019.stderr b/tests/ghci.debugger/scripts/print019.stderr
index e5bcb7f1c..3473c99dd 100644
--- a/tests/ghci.debugger/scripts/print019.stderr
+++ b/tests/ghci.debugger/scripts/print019.stderr
@@ -1,7 +1,7 @@
 
 <interactive>:11:1:
-    No instance for (Show a1) arising from a use of `print'
-    Cannot resolve unknown runtime type `a1'
+    No instance for (Show a1) arising from a use of ‛print’
+    Cannot resolve unknown runtime type ‛a1’
     Use :print or :force to determine these types
     Relevant bindings include it :: a1 (bound at <interactive>:11:1)
     Note: there are several potential instances:
diff --git a/tests/ghci.debugger/scripts/print020.stderr b/tests/ghci.debugger/scripts/print020.stderr
index 296718dae..6642bb7ba 100644
--- a/tests/ghci.debugger/scripts/print020.stderr
+++ b/tests/ghci.debugger/scripts/print020.stderr
@@ -3,7 +3,7 @@ GenericTemplate.hs:219:14: Warning:
     Pattern bindings containing unlifted types should use an outermost bang pattern:
       sts1@((HappyCons (st1@(action)) (_)))
         = happyDrop k (HappyCons (st) (sts))
-    In an equation for `happyMonadReduce':
+    In an equation for ‛happyMonadReduce’:
         happyMonadReduce k nt fn j tk st sts stk
           = happyThen1
               (fn stk tk)
@@ -17,7 +17,7 @@ GenericTemplate.hs:226:14: Warning:
     Pattern bindings containing unlifted types should use an outermost bang pattern:
       sts1@((HappyCons (st1@(action)) (_)))
         = happyDrop k (HappyCons (st) (sts))
-    In an equation for `happyMonad2Reduce':
+    In an equation for ‛happyMonad2Reduce’:
         happyMonad2Reduce k nt fn j tk st sts stk
           = happyThen1
               (fn stk tk)
diff --git a/tests/ghci/prog006/prog006.stderr b/tests/ghci/prog006/prog006.stderr
index 472272a01..53c82d546 100644
--- a/tests/ghci/prog006/prog006.stderr
+++ b/tests/ghci/prog006/prog006.stderr
@@ -1,4 +1,4 @@
 
 Boot.hs:5:13:
-    Not a data constructor: `forall'
+    Not a data constructor: ‛forall’
     Perhaps you intended to use -XExistentialQuantification
diff --git a/tests/ghci/prog009/ghci.prog009.stderr b/tests/ghci/prog009/ghci.prog009.stderr
index e63a322c2..bf608499b 100644
--- a/tests/ghci/prog009/ghci.prog009.stderr
+++ b/tests/ghci/prog009/ghci.prog009.stderr
@@ -2,7 +2,7 @@
 A.hs:1:16: parse error on input `where'
 
 <interactive>:26:1:
-    Not in scope: `yan'
-    Perhaps you meant `tan' (imported from Prelude)
+    Not in scope: ‛yan’
+    Perhaps you meant ‛tan’ (imported from Prelude)
 
 A.hs:1:16: parse error on input `where'
diff --git a/tests/ghci/prog012/prog012.stderr b/tests/ghci/prog012/prog012.stderr
index 71f2bbeb0..db122d9c6 100644
--- a/tests/ghci/prog012/prog012.stderr
+++ b/tests/ghci/prog012/prog012.stderr
@@ -1,2 +1,2 @@
 
-Bar.hs:3:7: Not in scope: `nonexistent'
+Bar.hs:3:7: Not in scope: ‛nonexistent’
diff --git a/tests/ghci/scripts/T2452.stderr b/tests/ghci/scripts/T2452.stderr
index 2802ee2bd..a2fa4fc8a 100644
--- a/tests/ghci/scripts/T2452.stderr
+++ b/tests/ghci/scripts/T2452.stderr
@@ -1,2 +1,2 @@
 
-<interactive>:1:1: Not in scope: `System.IO.hPutStrLn'
+<interactive>:1:1: Not in scope: ‛System.IO.hPutStrLn’
diff --git a/tests/ghci/scripts/T2816.stderr b/tests/ghci/scripts/T2816.stderr
index 3a9e97220..ba4c1bd95 100644
--- a/tests/ghci/scripts/T2816.stderr
+++ b/tests/ghci/scripts/T2816.stderr
@@ -1,2 +1,2 @@
 
-<interactive>:2:1: Not in scope: `α'
+<interactive>:2:1: Not in scope: ‛α’
diff --git a/tests/ghci/scripts/T4127a.stderr b/tests/ghci/scripts/T4127a.stderr
index 970b6db0a..cc118a9e2 100644
--- a/tests/ghci/scripts/T4127a.stderr
+++ b/tests/ghci/scripts/T4127a.stderr
@@ -1,5 +1,5 @@
 
 <interactive>:3:68:
-    Multiple declarations of `f'
+    Multiple declarations of ‛f’
     Declared at: <interactive>:3:32
                  <interactive>:3:68
diff --git a/tests/ghci/scripts/T5545.stdout b/tests/ghci/scripts/T5545.stdout
index 8c7c69ad5..8ba680a5c 100644
--- a/tests/ghci/scripts/T5545.stdout
+++ b/tests/ghci/scripts/T5545.stdout
@@ -1,2 +1,2 @@
-($!) :: (a -> b) -> a -> b 	-- Defined in `Prelude'
+($!) :: (a -> b) -> a -> b 	-- Defined in ‛Prelude’
 infixr 0 $!
diff --git a/tests/ghci/scripts/T5564.stderr b/tests/ghci/scripts/T5564.stderr
index d76c4df78..6fb94e4f1 100644
--- a/tests/ghci/scripts/T5564.stderr
+++ b/tests/ghci/scripts/T5564.stderr
@@ -1,9 +1,9 @@
 
 <interactive>:3:1:
-    Not in scope: `git'
-    Perhaps you meant `it' (line 2)
+    Not in scope: ‛git’
+    Perhaps you meant ‛it’ (line 2)
 
 <interactive>:5:1:
-    Not in scope: `fit'
+    Not in scope: ‛fit’
     Perhaps you meant one of these:
-      `it' (line 4), `fst' (imported from Prelude)
+      ‛it’ (line 4), ‛fst’ (imported from Prelude)
diff --git a/tests/ghci/scripts/T5836.stderr b/tests/ghci/scripts/T5836.stderr
index 9b0cfc65e..5bd37b5c0 100644
--- a/tests/ghci/scripts/T5836.stderr
+++ b/tests/ghci/scripts/T5836.stderr
@@ -1,4 +1,4 @@
 
 <no location info>:
-    Could not find module `Does.Not.Exist'
+    Could not find module ‛Does.Not.Exist’
     It is not a module in the current program, or in any known package.
diff --git a/tests/ghci/scripts/T5979.stderr b/tests/ghci/scripts/T5979.stderr
index 84f8c6ba0..b4cd88492 100644
--- a/tests/ghci/scripts/T5979.stderr
+++ b/tests/ghci/scripts/T5979.stderr
@@ -1,4 +1,4 @@
 
 <no location info>:
-    Could not find module `Control.Monad.Trans.State'
+    Could not find module ‛Control.Monad.Trans.State’
     It is not a module in the current program, or in any known package.
diff --git a/tests/ghci/scripts/T6007.stderr b/tests/ghci/scripts/T6007.stderr
index b461ef19b..695d25b3a 100644
--- a/tests/ghci/scripts/T6007.stderr
+++ b/tests/ghci/scripts/T6007.stderr
@@ -1,6 +1,6 @@
 
 <interactive>:1:19:
-    Module `System.IO' does not export `does_not_exist'
+    Module ‛System.IO’ does not export ‛does_not_exist’
 
 <interactive>:1:20:
-    Module `Data.Maybe' does not export `does_not_exist'
+    Module ‛Data.Maybe’ does not export ‛does_not_exist’
diff --git a/tests/ghci/scripts/ghci008.stdout b/tests/ghci/scripts/ghci008.stdout
index cac9db2c4..9eaf1dc96 100644
--- a/tests/ghci/scripts/ghci008.stdout
+++ b/tests/ghci/scripts/ghci008.stdout
@@ -1,18 +1,18 @@
 class Num a where
   (+) :: a -> a -> a
   ...
-  	-- Defined in `GHC.Num'
+  	-- Defined in ‛GHC.Num’
 infixl 6 +
 class Num a where
   (+) :: a -> a -> a
   ...
-  	-- Defined in `GHC.Num'
+  	-- Defined in ‛GHC.Num’
 infixl 6 +
 data Data.Complex.Complex a = !a Data.Complex.:+ !a
-  	-- Defined in `Data.Complex'
+  	-- Defined in ‛Data.Complex’
 infix 6 Data.Complex.:+
 data Data.Complex.Complex a = !a Data.Complex.:+ !a
-  	-- Defined in `Data.Complex'
+  	-- Defined in ‛Data.Complex’
 infix 6 Data.Complex.:+
 class (RealFrac a, Floating a) => RealFloat a where
   floatRadix :: a -> Integer
@@ -29,8 +29,8 @@ class (RealFrac a, Floating a) => RealFloat a where
   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'
+  	-- Defined in ‛GHC.Float’
+instance RealFloat Float -- Defined in ‛GHC.Float’
+instance RealFloat Double -- Defined in ‛GHC.Float’
 Data.List.isPrefixOf :: Eq a => [a] -> [a] -> Bool
-  	-- Defined in `Data.List'
+  	-- Defined in ‛Data.List’
diff --git a/tests/ghci/scripts/ghci011.stdout b/tests/ghci/scripts/ghci011.stdout
index caed5d0f0..540572ea8 100644
--- a/tests/ghci/scripts/ghci011.stdout
+++ b/tests/ghci/scripts/ghci011.stdout
@@ -1,22 +1,22 @@
-data [] a = [] | a : [a] 	-- Defined in `GHC.Types'
-instance Eq a => Eq [a] -- Defined in `GHC.Classes'
-instance Monad [] -- Defined in `GHC.Base'
-instance Functor [] -- Defined in `GHC.Base'
-instance Ord a => Ord [a] -- Defined in `GHC.Classes'
-instance Read a => Read [a] -- Defined in `GHC.Read'
-instance Show a => Show [a] -- Defined in `GHC.Show'
-data () = () 	-- Defined in `GHC.Tuple'
-instance Bounded () -- Defined in `GHC.Enum'
-instance Enum () -- Defined in `GHC.Enum'
-instance Eq () -- Defined in `GHC.Classes'
-instance Ord () -- Defined in `GHC.Classes'
-instance Read () -- Defined in `GHC.Read'
-instance Show () -- Defined in `GHC.Show'
-data (,) a b = (,) a b 	-- Defined in `GHC.Tuple'
+data [] a = [] | a : [a] 	-- Defined in ‛GHC.Types’
+instance Eq a => Eq [a] -- Defined in ‛GHC.Classes’
+instance Monad [] -- Defined in ‛GHC.Base’
+instance Functor [] -- Defined in ‛GHC.Base’
+instance Ord a => Ord [a] -- Defined in ‛GHC.Classes’
+instance Read a => Read [a] -- Defined in ‛GHC.Read’
+instance Show a => Show [a] -- Defined in ‛GHC.Show’
+data () = () 	-- Defined in ‛GHC.Tuple’
+instance Bounded () -- Defined in ‛GHC.Enum’
+instance Enum () -- Defined in ‛GHC.Enum’
+instance Eq () -- Defined in ‛GHC.Classes’
+instance Ord () -- Defined in ‛GHC.Classes’
+instance Read () -- Defined in ‛GHC.Read’
+instance Show () -- Defined in ‛GHC.Show’
+data (,) a b = (,) a b 	-- Defined in ‛GHC.Tuple’
 instance (Bounded a, Bounded b) => Bounded (a, b)
-  -- Defined in `GHC.Enum'
-instance (Eq a, Eq b) => Eq (a, b) -- Defined in `GHC.Classes'
-instance Functor ((,) a) -- Defined in `GHC.Base'
-instance (Ord a, Ord b) => Ord (a, b) -- Defined in `GHC.Classes'
-instance (Read a, Read b) => Read (a, b) -- Defined in `GHC.Read'
-instance (Show a, Show b) => Show (a, b) -- Defined in `GHC.Show'
+  -- Defined in ‛GHC.Enum’
+instance (Eq a, Eq b) => Eq (a, b) -- Defined in ‛GHC.Classes’
+instance Functor ((,) a) -- Defined in ‛GHC.Base’
+instance (Ord a, Ord b) => Ord (a, b) -- Defined in ‛GHC.Classes’
+instance (Read a, Read b) => Read (a, b) -- Defined in ‛GHC.Read’
+instance (Show a, Show b) => Show (a, b) -- Defined in ‛GHC.Show’
diff --git a/tests/ghci/scripts/ghci020.stdout b/tests/ghci/scripts/ghci020.stdout
index 333e78570..6d621d3c1 100644
--- a/tests/ghci/scripts/ghci020.stdout
+++ b/tests/ghci/scripts/ghci020.stdout
@@ -1,3 +1,3 @@
-data (->) a b 	-- Defined in `GHC.Prim'
-instance Monad ((->) r) -- Defined in `GHC.Base'
-instance Functor ((->) r) -- Defined in `GHC.Base'
+data (->) a b 	-- Defined in ‛GHC.Prim’
+instance Monad ((->) r) -- Defined in ‛GHC.Base’
+instance Functor ((->) r) -- Defined in ‛GHC.Base’
diff --git a/tests/ghci/scripts/ghci021.stderr b/tests/ghci/scripts/ghci021.stderr
index ae7c75b6b..18216b8f1 100644
--- a/tests/ghci/scripts/ghci021.stderr
+++ b/tests/ghci/scripts/ghci021.stderr
@@ -1,2 +1,2 @@
 
-<no location info>: no such module: `ThisDoesNotExist'
+<no location info>: no such module: ‛ThisDoesNotExist’
diff --git a/tests/ghci/scripts/ghci034.stderr b/tests/ghci/scripts/ghci034.stderr
index 59501b244..00bf3dfb6 100644
--- a/tests/ghci/scripts/ghci034.stderr
+++ b/tests/ghci/scripts/ghci034.stderr
@@ -1,2 +1,2 @@
 
-Top level: Not in scope: `thisIsNotDefined'
+Top level: Not in scope: ‛thisIsNotDefined’
diff --git a/tests/ghci/scripts/ghci036.stderr b/tests/ghci/scripts/ghci036.stderr
index f070bdd9d..5b53b08d2 100644
--- a/tests/ghci/scripts/ghci036.stderr
+++ b/tests/ghci/scripts/ghci036.stderr
@@ -1,18 +1,18 @@
 
-<interactive>:1:1: Not in scope: `nubBy'
+<interactive>:1:1: Not in scope: ‛nubBy’
 
-<interactive>:1:1: Not in scope: `nub'
+<interactive>:1:1: Not in scope: ‛nub’
 
-<interactive>:1:1: Not in scope: `nubBy'
+<interactive>:1:1: Not in scope: ‛nubBy’
 
-<interactive>:1:1: Not in scope: `nub'
+<interactive>:1:1: Not in scope: ‛nub’
 
 <interactive>:1:1:
-    Not in scope: `nub'
-    Perhaps you meant `L.nub' (imported from Data.List)
+    Not in scope: ‛nub’
+    Perhaps you meant ‛L.nub’ (imported from Data.List)
 
 <interactive>:1:1:
-    Failed to load interface for `L'
+    Failed to load interface for ‛L’
     Use -v to see a list of the files searched for.
 
-<interactive>:1:1: Not in scope: `nub'
+<interactive>:1:1: Not in scope: ‛nub’
diff --git a/tests/ghci/scripts/ghci038.stderr b/tests/ghci/scripts/ghci038.stderr
index 5b3b85c25..bb2fb850c 100644
--- a/tests/ghci/scripts/ghci038.stderr
+++ b/tests/ghci/scripts/ghci038.stderr
@@ -1,4 +1,4 @@
 
-<interactive>:1:1: Not in scope: `map'
+<interactive>:1:1: Not in scope: ‛map’
 
-<interactive>:1:1: Not in scope: `x'
+<interactive>:1:1: Not in scope: ‛x’
diff --git a/tests/ghci/scripts/ghci044.stderr b/tests/ghci/scripts/ghci044.stderr
index a5e6a543e..c0737d13b 100644
--- a/tests/ghci/scripts/ghci044.stderr
+++ b/tests/ghci/scripts/ghci044.stderr
@@ -1,11 +1,11 @@
 
 <interactive>:5:10:
-    Illegal instance declaration for `C [Int]'
+    Illegal instance declaration for ‛C [Int]’
       (All instance types must be of the form (T a1 ... an)
        where a1 ... an are *distinct type variables*,
        and each type variable appears at most once in the instance head.
        Use -XFlexibleInstances if you want to disable this.)
-    In the instance declaration for `C [Int]'
+    In the instance declaration for ‛C [Int]’
 
 <interactive>:7:10:
     Overlapping instance declarations:
diff --git a/tests/ghci/scripts/ghci047.stderr b/tests/ghci/scripts/ghci047.stderr
index 005171037..c888b0492 100644
--- a/tests/ghci/scripts/ghci047.stderr
+++ b/tests/ghci/scripts/ghci047.stderr
@@ -1,16 +1,16 @@
 
 <interactive>:38:1:
-    Couldn't match type `HFalse' with `HTrue'
+    Couldn't match type ‛HFalse’ with ‛HTrue’
     Expected type: HTrue
       Actual type: Or HFalse HFalse
     In the expression: f
     In the expression: f $ Baz 'a'
-    In an equation for `it': it = f $ Baz 'a'
+    In an equation for ‛it’: it = f $ Baz 'a'
 
 <interactive>:39:1:
-    Couldn't match type `HFalse' with `HTrue'
+    Couldn't match type ‛HFalse’ with ‛HTrue’
     Expected type: HTrue
       Actual type: Or HFalse HFalse
     In the expression: f
     In the expression: f $ Quz
-    In an equation for `it': it = f $ Quz
+    In an equation for ‛it’: it = f $ Quz
diff --git a/tests/ghci/scripts/ghci048.stderr b/tests/ghci/scripts/ghci048.stderr
index 408c1e9ee..3809db88e 100644
--- a/tests/ghci/scripts/ghci048.stderr
+++ b/tests/ghci/scripts/ghci048.stderr
@@ -1,10 +1,10 @@
 
 <interactive>:4:16:
-    Multiple declarations of `A'
+    Multiple declarations of ‛A’
     Declared at: <interactive>:4:12
                  <interactive>:4:16
 
 <interactive>:6:16:
-    Multiple declarations of `A'
+    Multiple declarations of ‛A’
     Declared at: <interactive>:6:12
                  <interactive>:6:16
diff --git a/tests/ghci/scripts/ghci050.stderr b/tests/ghci/scripts/ghci050.stderr
index b2e11a26e..77c552575 100644
--- a/tests/ghci/scripts/ghci050.stderr
+++ b/tests/ghci/scripts/ghci050.stderr
@@ -1,8 +1,8 @@
 
 <interactive>:6:49:
-    Couldn't match expected type `ListableElem (a, a)'
-                with actual type `a'
-      `a' is a rigid type variable bound by
+    Couldn't match expected type ‛ListableElem (a, a)’
+                with actual type ‛a’
+      ‛a’ is a rigid type variable bound by
           the instance declaration at <interactive>:6:10
     Relevant bindings include
       asList :: (a, a) -> [ListableElem (a, a)]
@@ -11,4 +11,4 @@
       b :: a (bound at <interactive>:6:43)
     In the expression: a
     In the expression: [a, b]
-    In an equation for `asList': asList (a, b) = [a, b]
+    In an equation for ‛asList’: asList (a, b) = [a, b]
diff --git a/tests/ghci/scripts/ghci051.stderr b/tests/ghci/scripts/ghci051.stderr
index 130d0012a..aec364766 100644
--- a/tests/ghci/scripts/ghci051.stderr
+++ b/tests/ghci/scripts/ghci051.stderr
@@ -1,7 +1,7 @@
 
 <interactive>:7:9:
-    Couldn't match type `T' with `main::Interactive.T'
+    Couldn't match type ‛T’ with ‛main::Interactive.T’
     Expected type: T'
       Actual type: T
     In the expression: C :: T'
-    In an equation for `c': c = C :: T'
+    In an equation for ‛c’: c = C :: T'
diff --git a/tests/ghci/scripts/ghci052.stderr b/tests/ghci/scripts/ghci052.stderr
index c685a2aaa..2efada534 100644
--- a/tests/ghci/scripts/ghci052.stderr
+++ b/tests/ghci/scripts/ghci052.stderr
@@ -1,27 +1,27 @@
 
 <interactive>:7:4:
-    Couldn't match expected type `main::Interactive.Planet'
-                with actual type `Planet'
-    In the first argument of `pn', namely `Mercury'
+    Couldn't match expected type ‛main::Interactive.Planet’
+                with actual type ‛Planet’
+    In the first argument of ‛pn’, namely ‛Mercury’
     In the expression: pn Mercury
-    In an equation for `it': it = pn Mercury
+    In an equation for ‛it’: it = pn Mercury
 
 <interactive>:8:4:
-    Couldn't match expected type `main::Interactive.Planet'
-                with actual type `Planet'
-    In the first argument of `pn', namely `Venus'
+    Couldn't match expected type ‛main::Interactive.Planet’
+                with actual type ‛Planet’
+    In the first argument of ‛pn’, namely ‛Venus’
     In the expression: pn Venus
-    In an equation for `it': it = pn Venus
+    In an equation for ‛it’: it = pn Venus
 
 <interactive>:9:4:
-    Couldn't match expected type `main::Interactive.Planet'
-                with actual type `Planet'
-    In the first argument of `pn', namely `Mars'
+    Couldn't match expected type ‛main::Interactive.Planet’
+                with actual type ‛Planet’
+    In the first argument of ‛pn’, namely ‛Mars’
     In the expression: pn Mars
-    In an equation for `it': it = pn Mars
+    In an equation for ‛it’: it = pn Mars
 
 <interactive>:11:44:
-    Couldn't match expected type `Planet'
-                with actual type `main::Interactive.Planet'
+    Couldn't match expected type ‛Planet’
+                with actual type ‛main::Interactive.Planet’
     In the pattern: Earth
-    In an equation for `pn': pn Earth = "E"
+    In an equation for ‛pn’: pn Earth = "E"
diff --git a/tests/ghci/scripts/ghci053.stderr b/tests/ghci/scripts/ghci053.stderr
index e08ad91e2..f97df8f63 100644
--- a/tests/ghci/scripts/ghci053.stderr
+++ b/tests/ghci/scripts/ghci053.stderr
@@ -1,14 +1,14 @@
 
 <interactive>:8:12:
-    Couldn't match expected type `main::Interactive.Planet'
-                with actual type `Planet'
-    In the second argument of `(==)', namely `Mercury'
+    Couldn't match expected type ‛main::Interactive.Planet’
+                with actual type ‛Planet’
+    In the second argument of ‛(==)’, namely ‛Mercury’
     In the expression: mercury == Mercury
-    In an equation for `it': it = mercury == Mercury
+    In an equation for ‛it’: it = mercury == Mercury
 
 <interactive>:10:10:
-    Couldn't match expected type `Planet'
-                with actual type `main::Interactive.Planet'
-    In the second argument of `(==)', namely `Earth'
+    Couldn't match expected type ‛Planet’
+                with actual type ‛main::Interactive.Planet’
+    In the second argument of ‛(==)’, namely ‛Earth’
     In the expression: Venus == Earth
-    In an equation for `it': it = Venus == Earth
+    In an equation for ‛it’: it = Venus == Earth
diff --git a/tests/ghci/scripts/ghci057.stderr b/tests/ghci/scripts/ghci057.stderr
index 623bfb3c3..22d051457 100644
--- a/tests/ghci/scripts/ghci057.stderr
+++ b/tests/ghci/scripts/ghci057.stderr
@@ -1,17 +1,17 @@
-
-<interactive>:5:1:
-    Illegal generalised algebraic data declaration for `T'
-      (Use -XGADTs to allow GADTs)
-    In the data declaration for `T'
-
-ghci057.hs:3:3:
-    Data constructor `C' has existential type variables, a context, or a specialised result type
-      (Use -XExistentialQuantification or -XGADTs to allow this)
-    In the definition of data constructor `C'
-    In the data declaration for `T'
-
-ghci057.hs:3:3:
-    Data constructor `C' has existential type variables, a context, or a specialised result type
-      (Use -XExistentialQuantification or -XGADTs to allow this)
-    In the definition of data constructor `C'
-    In the data declaration for `T'
+
+<interactive>:5:1:
+    Illegal generalised algebraic data declaration for ‛T’
+      (Use -XGADTs to allow GADTs)
+    In the data declaration for ‛T’
+
+ghci057.hs:3:3:
+    Data constructor ‛C’ has existential type variables, a context, or a specialised result type
+      (Use -XExistentialQuantification or -XGADTs to allow this)
+    In the definition of data constructor ‛C’
+    In the data declaration for ‛T’
+
+ghci057.hs:3:3:
+    Data constructor ‛C’ has existential type variables, a context, or a specialised result type
+      (Use -XExistentialQuantification or -XGADTs to allow this)
+    In the definition of data constructor ‛C’
+    In the data declaration for ‛T’
diff --git a/tests/haddock/haddock_examples/haddock.Test.stderr b/tests/haddock/haddock_examples/haddock.Test.stderr
index 74956de41..37a2565a4 100644
--- a/tests/haddock/haddock_examples/haddock.Test.stderr
+++ b/tests/haddock/haddock_examples/haddock.Test.stderr
@@ -157,10 +157,10 @@ m = undefined
 
 
 
-Test.hs:32:9: Warning: `p' is exported by `p' and `R(..)'
+Test.hs:32:9: Warning: ‛p’ is exported by ‛p’ and ‛R(..)’
 
-Test.hs:32:12: Warning: `q' is exported by `q' and `R(..)'
+Test.hs:32:12: Warning: ‛q’ is exported by ‛q’ and ‛R(..)’
 
-Test.hs:32:15: Warning: `u' is exported by `u' and `R(..)'
+Test.hs:32:15: Warning: ‛u’ is exported by ‛u’ and ‛R(..)’
 
-Test.hs:38:9: Warning: `a' is exported by `a' and `C(a, b)'
+Test.hs:38:9: Warning: ‛a’ is exported by ‛a’ and ‛C(a, b)’
diff --git a/tests/indexed-types/should_compile/Class3.stderr b/tests/indexed-types/should_compile/Class3.stderr
index 4c72a425f..6c0746074 100644
--- a/tests/indexed-types/should_compile/Class3.stderr
+++ b/tests/indexed-types/should_compile/Class3.stderr
@@ -1,4 +1,4 @@
 
-Class3.hs:7:10:
-    Warning: No explicit method or default declaration for `foo'
-    In the instance declaration for `C ()'
+Class3.hs:7:10: Warning:
+    No explicit method or default declaration for ‛foo’
+    In the instance declaration for ‛C ()’
diff --git a/tests/indexed-types/should_compile/Simple14.stderr b/tests/indexed-types/should_compile/Simple14.stderr
index 1665ccae8..3c761c302 100644
--- a/tests/indexed-types/should_compile/Simple14.stderr
+++ b/tests/indexed-types/should_compile/Simple14.stderr
@@ -1,18 +1,18 @@
 
 Simple14.hs:17:19:
-    Couldn't match type `z0' with `n'
-      `z0' is untouchable
+    Couldn't match type ‛z0’ with ‛n’
+      ‛z0’ is untouchable
         inside the constraints (Maybe m ~ Maybe n)
         bound by a type expected by the context:
                    Maybe m ~ Maybe n => EQ_ z0 z0
         at Simple14.hs:17:12-33
-      `n' is a rigid type variable bound by
+      ‛n’ is a rigid type variable bound by
           the type signature for foo :: EQ_ (Maybe m) (Maybe n)
           at Simple14.hs:16:17
     Expected type: EQ_ z0 z0
       Actual type: EQ_ m n
     Relevant bindings include
       foo :: EQ_ (Maybe m) (Maybe n) (bound at Simple14.hs:17:1)
-    In the second argument of `eqE', namely `(eqI :: EQ_ m n)'
-    In the first argument of `ntI', namely `(`eqE` (eqI :: EQ_ m n))'
+    In the second argument of ‛eqE’, namely ‛(eqI :: EQ_ m n)’
+    In the first argument of ‛ntI’, namely ‛(`eqE` (eqI :: EQ_ m n))’
     In the expression: ntI (`eqE` (eqI :: EQ_ m n))
diff --git a/tests/indexed-types/should_compile/Simple2.stderr b/tests/indexed-types/should_compile/Simple2.stderr
index ef05fb3e2..e68afd80d 100644
--- a/tests/indexed-types/should_compile/Simple2.stderr
+++ b/tests/indexed-types/should_compile/Simple2.stderr
@@ -1,40 +1,40 @@
 
-Simple2.hs:21:1:
-    Warning: No explicit associated type or default declaration for `S3n'
-    In the instance declaration for `C3 Char'
+Simple2.hs:21:1: Warning:
+    No explicit associated type or default declaration for ‛S3n’
+    In the instance declaration for ‛C3 Char’
 
-Simple2.hs:21:10:
-    Warning: No explicit method or default declaration for `foo3n'
-    In the instance declaration for `C3 Char'
+Simple2.hs:21:10: Warning:
+    No explicit method or default declaration for ‛foo3n’
+    In the instance declaration for ‛C3 Char’
 
-Simple2.hs:21:10:
-    Warning: No explicit method or default declaration for `bar3n'
-    In the instance declaration for `C3 Char'
+Simple2.hs:21:10: Warning:
+    No explicit method or default declaration for ‛bar3n’
+    In the instance declaration for ‛C3 Char’
 
-Simple2.hs:29:1:
-    Warning: No explicit associated type or default declaration for `S3n'
-    In the instance declaration for `C3 Bool'
+Simple2.hs:29:1: Warning:
+    No explicit associated type or default declaration for ‛S3n’
+    In the instance declaration for ‛C3 Bool’
 
-Simple2.hs:29:10:
-    Warning: No explicit method or default declaration for `foo3n'
-    In the instance declaration for `C3 Bool'
+Simple2.hs:29:10: Warning:
+    No explicit method or default declaration for ‛foo3n’
+    In the instance declaration for ‛C3 Bool’
 
-Simple2.hs:29:10:
-    Warning: No explicit method or default declaration for `bar3n'
-    In the instance declaration for `C3 Bool'
+Simple2.hs:29:10: Warning:
+    No explicit method or default declaration for ‛bar3n’
+    In the instance declaration for ‛C3 Bool’
 
-Simple2.hs:39:1:
-    Warning: No explicit associated type or default declaration for `S3'
-    In the instance declaration for `C3 Float'
+Simple2.hs:39:1: Warning:
+    No explicit associated type or default declaration for ‛S3’
+    In the instance declaration for ‛C3 Float’
 
-Simple2.hs:39:1:
-    Warning: No explicit associated type or default declaration for `S3n'
-    In the instance declaration for `C3 Float'
+Simple2.hs:39:1: Warning:
+    No explicit associated type or default declaration for ‛S3n’
+    In the instance declaration for ‛C3 Float’
 
-Simple2.hs:39:10:
-    Warning: No explicit method or default declaration for `foo3n'
-    In the instance declaration for `C3 Float'
+Simple2.hs:39:10: Warning:
+    No explicit method or default declaration for ‛foo3n’
+    In the instance declaration for ‛C3 Float’
 
-Simple2.hs:39:10:
-    Warning: No explicit method or default declaration for `bar3n'
-    In the instance declaration for `C3 Float'
+Simple2.hs:39:10: Warning:
+    No explicit method or default declaration for ‛bar3n’
+    In the instance declaration for ‛C3 Float’
diff --git a/tests/indexed-types/should_fail/DerivUnsatFam.stderr b/tests/indexed-types/should_fail/DerivUnsatFam.stderr
index 63c126214..dbcb4f03c 100644
--- a/tests/indexed-types/should_fail/DerivUnsatFam.stderr
+++ b/tests/indexed-types/should_fail/DerivUnsatFam.stderr
@@ -1,5 +1,5 @@
-
-DerivUnsatFam.hs:8:1:
-    Can't make a derived instance of `Functor T':
-      Unsaturated data family application
-    In the stand-alone deriving instance for `Functor T'
+
+DerivUnsatFam.hs:8:1:
+    Can't make a derived instance of ‛Functor T’:
+      Unsaturated data family application
+    In the stand-alone deriving instance for ‛Functor T’
diff --git a/tests/indexed-types/should_fail/ExtraTcsUntch.stderr b/tests/indexed-types/should_fail/ExtraTcsUntch.stderr
index 428d4b968..4b7532c96 100644
--- a/tests/indexed-types/should_fail/ExtraTcsUntch.stderr
+++ b/tests/indexed-types/should_fail/ExtraTcsUntch.stderr
@@ -1,6 +1,6 @@
 
 ExtraTcsUntch.hs:24:53:
-    Could not deduce (C [t] [a]) arising from a use of `op'
+    Could not deduce (C [t] [a]) arising from a use of ‛op’
     from the context (F Int ~ [[t]])
       bound by the inferred type of
                f :: F Int ~ [[t]] => [t] -> ((), ((), ()))
diff --git a/tests/indexed-types/should_fail/GADTwrong1.stderr b/tests/indexed-types/should_fail/GADTwrong1.stderr
index b61af24a6..aa6eedc88 100644
--- a/tests/indexed-types/should_fail/GADTwrong1.stderr
+++ b/tests/indexed-types/should_fail/GADTwrong1.stderr
@@ -1,21 +1,21 @@
-
-GADTwrong1.hs:12:19:
-    Could not deduce (a1 ~ b)
-    from the context (() ~ Const a1)
-      bound by a pattern with constructor
-                 T :: forall a. a -> T (Const a),
-               in a case alternative
-      at GADTwrong1.hs:12:12-14
-      `a1' is a rigid type variable bound by
-           a pattern with constructor
-             T :: forall a. a -> T (Const a),
-           in a case alternative
-           at GADTwrong1.hs:12:12
-      `b' is a rigid type variable bound by
-          the type signature for coerce :: a -> b at GADTwrong1.hs:10:20
-    Relevant bindings include
-      coerce :: a -> b (bound at GADTwrong1.hs:11:1)
-      y :: a1 (bound at GADTwrong1.hs:12:14)
-    In the expression: y
-    In a case alternative: T y -> y
-    In the expression: case T x :: T (Const b) of { T y -> y }
+
+GADTwrong1.hs:12:19:
+    Could not deduce (a1 ~ b)
+    from the context (() ~ Const a1)
+      bound by a pattern with constructor
+                 T :: forall a. a -> T (Const a),
+               in a case alternative
+      at GADTwrong1.hs:12:12-14
+      ‛a1’ is a rigid type variable bound by
+           a pattern with constructor
+             T :: forall a. a -> T (Const a),
+           in a case alternative
+           at GADTwrong1.hs:12:12
+      ‛b’ is a rigid type variable bound by
+          the type signature for coerce :: a -> b at GADTwrong1.hs:10:20
+    Relevant bindings include
+      coerce :: a -> b (bound at GADTwrong1.hs:11:1)
+      y :: a1 (bound at GADTwrong1.hs:12:14)
+    In the expression: y
+    In a case alternative: T y -> y
+    In the expression: case T x :: T (Const b) of { T y -> y }
diff --git a/tests/indexed-types/should_fail/NoMatchErr.stderr b/tests/indexed-types/should_fail/NoMatchErr.stderr
index 0176ffe2e..7f43b5db4 100644
--- a/tests/indexed-types/should_fail/NoMatchErr.stderr
+++ b/tests/indexed-types/should_fail/NoMatchErr.stderr
@@ -1,13 +1,13 @@
-
-NoMatchErr.hs:19:7:
-    Could not deduce (Memo d0 ~ Memo d)
-    from the context (Fun d)
-      bound by the type signature for f :: Fun d => Memo d a -> Memo d a
-      at NoMatchErr.hs:19:7-37
-    NB: `Memo' is a type function, and may not be injective
-    The type variable `d0' is ambiguous
-    Expected type: Memo d a -> Memo d a
-      Actual type: Memo d0 a -> Memo d0 a
-    In the ambiguity check for:
-      forall d a. Fun d => Memo d a -> Memo d a
-    In the type signature for `f': f :: Fun d => Memo d a -> Memo d a
+
+NoMatchErr.hs:19:7:
+    Could not deduce (Memo d0 ~ Memo d)
+    from the context (Fun d)
+      bound by the type signature for f :: Fun d => Memo d a -> Memo d a
+      at NoMatchErr.hs:19:7-37
+    NB: ‛Memo’ is a type function, and may not be injective
+    The type variable ‛d0’ is ambiguous
+    Expected type: Memo d a -> Memo d a
+      Actual type: Memo d0 a -> Memo d0 a
+    In the ambiguity check for:
+      forall d a. Fun d => Memo d a -> Memo d a
+    In the type signature for ‛f’: f :: Fun d => Memo d a -> Memo d a
diff --git a/tests/indexed-types/should_fail/NotRelaxedExamples.stderr b/tests/indexed-types/should_fail/NotRelaxedExamples.stderr
index d08570a06..e56025a90 100644
--- a/tests/indexed-types/should_fail/NotRelaxedExamples.stderr
+++ b/tests/indexed-types/should_fail/NotRelaxedExamples.stderr
@@ -1,18 +1,18 @@
-
-NotRelaxedExamples.hs:9:15:
-    Nested type family application
-      in the type family application: F1 (F1 Char)
-    (Use -XUndecidableInstances to permit this)
-    In the type instance declaration for `F1'
-
-NotRelaxedExamples.hs:10:15:
-    Application is no smaller than the instance head
-      in the type family application: F2 [x]
-    (Use -XUndecidableInstances to permit this)
-    In the type instance declaration for `F2'
-
-NotRelaxedExamples.hs:11:15:
-    Application is no smaller than the instance head
-      in the type family application: F3 [Char]
-    (Use -XUndecidableInstances to permit this)
-    In the type instance declaration for `F3'
+
+NotRelaxedExamples.hs:9:15:
+    Nested type family application
+      in the type family application: F1 (F1 Char)
+    (Use -XUndecidableInstances to permit this)
+    In the type instance declaration for ‛F1’
+
+NotRelaxedExamples.hs:10:15:
+    Application is no smaller than the instance head
+      in the type family application: F2 [x]
+    (Use -XUndecidableInstances to permit this)
+    In the type instance declaration for ‛F2’
+
+NotRelaxedExamples.hs:11:15:
+    Application is no smaller than the instance head
+      in the type family application: F3 [Char]
+    (Use -XUndecidableInstances to permit this)
+    In the type instance declaration for ‛F3’
diff --git a/tests/indexed-types/should_fail/Overlap10.stderr b/tests/indexed-types/should_fail/Overlap10.stderr
index 63fa4d9c3..342cbe4bc 100644
--- a/tests/indexed-types/should_fail/Overlap10.stderr
+++ b/tests/indexed-types/should_fail/Overlap10.stderr
@@ -1,8 +1,8 @@
-
-Overlap10.hs:11:7:
-    Couldn't match expected type `F a Bool' with actual type `Bool'
-    Relevant bindings include
-      g :: a -> F a Bool (bound at Overlap10.hs:11:1)
-      x :: a (bound at Overlap10.hs:11:3)
-    In the expression: False
-    In an equation for `g': g x = False
+
+Overlap10.hs:11:7:
+    Couldn't match expected type ‛F a Bool’ with actual type ‛Bool’
+    Relevant bindings include
+      g :: a -> F a Bool (bound at Overlap10.hs:11:1)
+      x :: a (bound at Overlap10.hs:11:3)
+    In the expression: False
+    In an equation for ‛g’: g x = False
diff --git a/tests/indexed-types/should_fail/Overlap11.stderr b/tests/indexed-types/should_fail/Overlap11.stderr
index 929ce3460..476ae6c2f 100644
--- a/tests/indexed-types/should_fail/Overlap11.stderr
+++ b/tests/indexed-types/should_fail/Overlap11.stderr
@@ -1,8 +1,8 @@
-
-Overlap11.hs:11:8:
-    Couldn't match expected type `F a Int' with actual type `Int'
-    Relevant bindings include
-      g :: a -> F a Int (bound at Overlap11.hs:11:1)
-      x :: a (bound at Overlap11.hs:11:3)
-    In the expression: (5 :: Int)
-    In an equation for `g': g x = (5 :: Int)
+
+Overlap11.hs:11:8:
+    Couldn't match expected type ‛F a Int’ with actual type ‛Int’
+    Relevant bindings include
+      g :: a -> F a Int (bound at Overlap11.hs:11:1)
+      x :: a (bound at Overlap11.hs:11:3)
+    In the expression: (5 :: Int)
+    In an equation for ‛g’: g x = (5 :: Int)
diff --git a/tests/indexed-types/should_fail/Overlap5.stderr b/tests/indexed-types/should_fail/Overlap5.stderr
index 329d410fd..0413002ab 100644
--- a/tests/indexed-types/should_fail/Overlap5.stderr
+++ b/tests/indexed-types/should_fail/Overlap5.stderr
@@ -1,7 +1,7 @@
 
 Overlap5.hs:16:7:
-    Couldn't match type `x' with `And x 'True'
-      `x' is a rigid type variable bound by
+    Couldn't match type ‛x’ with ‛And x 'True’
+      ‛x’ is a rigid type variable bound by
           the type signature for
             g :: Proxy Bool x -> Proxy Bool (And x 'True)
           at Overlap5.hs:15:6
@@ -12,11 +12,11 @@ Overlap5.hs:16:7:
         (bound at Overlap5.hs:16:1)
       x :: Proxy Bool x (bound at Overlap5.hs:16:3)
     In the expression: x
-    In an equation for `g': g x = x
+    In an equation for ‛g’: g x = x
 
 Overlap5.hs:19:7:
-    Couldn't match type `x' with `And x x'
-      `x' is a rigid type variable bound by
+    Couldn't match type ‛x’ with ‛And x x’
+      ‛x’ is a rigid type variable bound by
           the type signature for h :: Proxy Bool x -> Proxy Bool (And x x)
           at Overlap5.hs:18:6
     Expected type: Proxy Bool (And x x)
@@ -26,4 +26,4 @@ Overlap5.hs:19:7:
         (bound at Overlap5.hs:19:1)
       x :: Proxy Bool x (bound at Overlap5.hs:19:3)
     In the expression: x
-    In an equation for `h': h x = x
+    In an equation for ‛h’: h x = x
diff --git a/tests/indexed-types/should_fail/Overlap6.stderr b/tests/indexed-types/should_fail/Overlap6.stderr
index 8149e2d92..c59a1ab72 100644
--- a/tests/indexed-types/should_fail/Overlap6.stderr
+++ b/tests/indexed-types/should_fail/Overlap6.stderr
@@ -1,7 +1,7 @@
 
 Overlap6.hs:16:7:
-    Couldn't match type `x' with `And x 'True'
-      `x' is a rigid type variable bound by
+    Couldn't match type ‛x’ with ‛And x 'True’
+      ‛x’ is a rigid type variable bound by
           the type signature for
             g :: Proxy Bool x -> Proxy Bool (And x 'True)
           at Overlap6.hs:15:6
@@ -12,4 +12,4 @@ Overlap6.hs:16:7:
         (bound at Overlap6.hs:16:1)
       x :: Proxy Bool x (bound at Overlap6.hs:16:3)
     In the expression: x
-    In an equation for `g': g x = x
+    In an equation for ‛g’: g x = x
diff --git a/tests/indexed-types/should_fail/Overlap9.stderr b/tests/indexed-types/should_fail/Overlap9.stderr
index d70a76c8e..97c59c2a8 100644
--- a/tests/indexed-types/should_fail/Overlap9.stderr
+++ b/tests/indexed-types/should_fail/Overlap9.stderr
@@ -7,6 +7,6 @@ Overlap9.hs:11:7:
     Relevant bindings include
       g :: a -> F a (bound at Overlap9.hs:11:1)
       x :: a (bound at Overlap9.hs:11:3)
-    In the return type of a call of `length'
+    In the return type of a call of ‛length’
     In the expression: length (show x)
-    In an equation for `g': g x = length (show x)
+    In an equation for ‛g’: g x = length (show x)
diff --git a/tests/indexed-types/should_fail/SimpleFail12.stderr b/tests/indexed-types/should_fail/SimpleFail12.stderr
index 93eabd618..e93b4f4d1 100644
--- a/tests/indexed-types/should_fail/SimpleFail12.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail12.stderr
@@ -1,4 +1,4 @@
-
-SimpleFail12.hs:8:15:
-    Illegal polymorphic or qualified type: forall a. [a]
-    In the type instance declaration for `C'
+
+SimpleFail12.hs:8:15:
+    Illegal polymorphic or qualified type: forall a. [a]
+    In the type instance declaration for ‛C’
diff --git a/tests/indexed-types/should_fail/SimpleFail13.stderr b/tests/indexed-types/should_fail/SimpleFail13.stderr
index a927fec6f..a31dda6b8 100644
--- a/tests/indexed-types/should_fail/SimpleFail13.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail13.stderr
@@ -1,8 +1,8 @@
-
-SimpleFail13.hs:9:1:
-    Illegal type synonym family application in instance: [C a]
-    In the data instance declaration for `D'
-
-SimpleFail13.hs:13:15:
-    Illegal type synonym family application in instance: [C a]
-    In the type instance declaration for `E'
+
+SimpleFail13.hs:9:1:
+    Illegal type synonym family application in instance: [C a]
+    In the data instance declaration for ‛D’
+
+SimpleFail13.hs:13:15:
+    Illegal type synonym family application in instance: [C a]
+    In the type instance declaration for ‛E’
diff --git a/tests/indexed-types/should_fail/SimpleFail14.stderr b/tests/indexed-types/should_fail/SimpleFail14.stderr
index 14f078d59..b6015046f 100644
--- a/tests/indexed-types/should_fail/SimpleFail14.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail14.stderr
@@ -1,6 +1,6 @@
-
-SimpleFail14.hs:5:15:
-    Expected a type, but `a ~ a' has kind `Constraint'
-    In the type `a ~ a'
-    In the definition of data constructor `T'
-    In the data declaration for `T'
+
+SimpleFail14.hs:5:15:
+    Expected a type, but ‛a ~ a’ has kind ‛Constraint’
+    In the type ‛a ~ a’
+    In the definition of data constructor ‛T’
+    In the data declaration for ‛T’
diff --git a/tests/indexed-types/should_fail/SimpleFail15.stderr b/tests/indexed-types/should_fail/SimpleFail15.stderr
index e2b7bba31..d5c1c7fb5 100644
--- a/tests/indexed-types/should_fail/SimpleFail15.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail15.stderr
@@ -2,5 +2,5 @@
 SimpleFail15.hs:5:8:
     Illegal polymorphic or qualified type: a ~ b => t
     Perhaps you intended to use -XRankNTypes or -XRank2Types
-    In the type signature for `foo':
+    In the type signature for ‛foo’:
       foo :: (a, b) -> (a ~ b => t) -> (a, b)
diff --git a/tests/indexed-types/should_fail/SimpleFail16.stderr b/tests/indexed-types/should_fail/SimpleFail16.stderr
index 3ad3cc770..1e50ae1c3 100644
--- a/tests/indexed-types/should_fail/SimpleFail16.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail16.stderr
@@ -1,9 +1,9 @@
-
-SimpleFail16.hs:10:12:
-    Couldn't match expected type `p0 a0' with actual type `F ()'
-    The type variables `p0', `a0' are ambiguous
-    Relevant bindings include
-      bar :: p0 a0 (bound at SimpleFail16.hs:10:1)
-    In the first argument of `foo', namely `(undefined :: F ())'
-    In the expression: foo (undefined :: F ())
-    In an equation for `bar': bar = foo (undefined :: F ())
+
+SimpleFail16.hs:10:12:
+    Couldn't match expected type ‛p0 a0’ with actual type ‛F ()’
+    The type variables ‛p0’, ‛a0’ are ambiguous
+    Relevant bindings include
+      bar :: p0 a0 (bound at SimpleFail16.hs:10:1)
+    In the first argument of ‛foo’, namely ‛(undefined :: F ())’
+    In the expression: foo (undefined :: F ())
+    In an equation for ‛bar’: bar = foo (undefined :: F ())
diff --git a/tests/indexed-types/should_fail/SimpleFail1a.stderr b/tests/indexed-types/should_fail/SimpleFail1a.stderr
index ba950b41f..7108a5ba7 100644
--- a/tests/indexed-types/should_fail/SimpleFail1a.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail1a.stderr
@@ -1,4 +1,4 @@
-
-SimpleFail1a.hs:4:1:
-    Number of parameters must match family declaration; expected 2
-    In the data instance declaration for `T1'
+
+SimpleFail1a.hs:4:1:
+    Number of parameters must match family declaration; expected 2
+    In the data instance declaration for ‛T1’
diff --git a/tests/indexed-types/should_fail/SimpleFail1b.stderr b/tests/indexed-types/should_fail/SimpleFail1b.stderr
index 8becc3e8f..a65a50d2c 100644
--- a/tests/indexed-types/should_fail/SimpleFail1b.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail1b.stderr
@@ -1,4 +1,4 @@
-
-SimpleFail1b.hs:4:1:
-    Number of parameters must match family declaration; expected 2
-    In the data instance declaration for `T1'
+
+SimpleFail1b.hs:4:1:
+    Number of parameters must match family declaration; expected 2
+    In the data instance declaration for ‛T1’
diff --git a/tests/indexed-types/should_fail/SimpleFail2a.stderr b/tests/indexed-types/should_fail/SimpleFail2a.stderr
index c8ac4513d..5d058756a 100644
--- a/tests/indexed-types/should_fail/SimpleFail2a.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail2a.stderr
@@ -1,6 +1,6 @@
 
 SimpleFail2a.hs:11:3:
     Type indexes must match class instance head
-    Found `a' but expected `Int'
-    In the data instance declaration for `Sd'
-    In the instance declaration for `C Int'
+    Found ‛a’ but expected ‛Int’
+    In the data instance declaration for ‛Sd’
+    In the instance declaration for ‛C Int’
diff --git a/tests/indexed-types/should_fail/SimpleFail3a.stderr b/tests/indexed-types/should_fail/SimpleFail3a.stderr
index 164351a01..cdf425131 100644
--- a/tests/indexed-types/should_fail/SimpleFail3a.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail3a.stderr
@@ -1,5 +1,5 @@
-
-SimpleFail3a.hs:10:3:
-    Wrong category of family instance; declaration was for a data type
-    In the type instance declaration for `S1'
-    In the instance declaration for `C1 Int'
+
+SimpleFail3a.hs:10:3:
+    Wrong category of family instance; declaration was for a data type
+    In the type instance declaration for ‛S1’
+    In the instance declaration for ‛C1 Int’
diff --git a/tests/indexed-types/should_fail/SimpleFail4.stderr b/tests/indexed-types/should_fail/SimpleFail4.stderr
index 1eca808bd..b9d99df24 100644
--- a/tests/indexed-types/should_fail/SimpleFail4.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail4.stderr
@@ -1,6 +1,6 @@
 
 SimpleFail4.hs:8:8:
     Type indexes must match class instance head
-    Found `Int' but expected `a'
-    In the type synonym instance default declaration for `S2'
-    In the class declaration for `C2'
+    Found ‛Int’ but expected ‛a’
+    In the type synonym instance default declaration for ‛S2’
+    In the class declaration for ‛C2’
diff --git a/tests/indexed-types/should_fail/SimpleFail5a.stderr b/tests/indexed-types/should_fail/SimpleFail5a.stderr
index 124eb7948..8cadf52b4 100644
--- a/tests/indexed-types/should_fail/SimpleFail5a.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail5a.stderr
@@ -1,7 +1,7 @@
 
 SimpleFail5a.hs:31:11:
-    Couldn't match type `a' with `Int'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛Int’
+      ‛a’ is a rigid type variable bound by
           the type signature for bar3wrong :: S3 a -> a
           at SimpleFail5a.hs:30:14
     Expected type: S3 a
@@ -9,4 +9,4 @@ SimpleFail5a.hs:31:11:
     Relevant bindings include
       bar3wrong :: S3 a -> a (bound at SimpleFail5a.hs:31:1)
     In the pattern: D3Int
-    In an equation for `bar3wrong': bar3wrong D3Int = 1
+    In an equation for ‛bar3wrong’: bar3wrong D3Int = 1
diff --git a/tests/indexed-types/should_fail/SimpleFail5b.stderr b/tests/indexed-types/should_fail/SimpleFail5b.stderr
index bd28918f1..2861582d9 100644
--- a/tests/indexed-types/should_fail/SimpleFail5b.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail5b.stderr
@@ -1,7 +1,7 @@
 
 SimpleFail5b.hs:31:12:
-    Couldn't match type `Char' with `Int'
+    Couldn't match type ‛Char’ with ‛Int’
     Expected type: S3 Int
       Actual type: S3 Char
     In the pattern: D3Char
-    In an equation for bar3wrong': bar3wrong' D3Char = 'a'
+    In an equation for ‛bar3wrong'’: bar3wrong' D3Char = 'a'
diff --git a/tests/indexed-types/should_fail/SimpleFail6.stderr b/tests/indexed-types/should_fail/SimpleFail6.stderr
index 679aaf872..71e9e5666 100644
--- a/tests/indexed-types/should_fail/SimpleFail6.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail6.stderr
@@ -1,5 +1,5 @@
 
 SimpleFail6.hs:7:11:
-    Conflicting definitions for `a'
+    Conflicting definitions for ‛a’
     Bound at: SimpleFail6.hs:7:11
               SimpleFail6.hs:7:13
diff --git a/tests/indexed-types/should_fail/SimpleFail7.stderr b/tests/indexed-types/should_fail/SimpleFail7.stderr
index 59d241344..4778f0dcc 100644
--- a/tests/indexed-types/should_fail/SimpleFail7.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail7.stderr
@@ -1,4 +1,4 @@
-
-SimpleFail7.hs:8:1:
-    Associated type `S5' must be inside a class instance
-    In the data instance declaration for `S5'
+
+SimpleFail7.hs:8:1:
+    Associated type ‛S5’ must be inside a class instance
+    In the data instance declaration for ‛S5’
diff --git a/tests/indexed-types/should_fail/SimpleFail8.stderr b/tests/indexed-types/should_fail/SimpleFail8.stderr
index 421bd53b2..ae25f9da5 100644
--- a/tests/indexed-types/should_fail/SimpleFail8.stderr
+++ b/tests/indexed-types/should_fail/SimpleFail8.stderr
@@ -1,6 +1,6 @@
-
-SimpleFail8.hs:9:8:
-    `Map' is not a (visible) associated type of class `C6'
-
-SimpleFail8.hs:10:8:
-    `S3' is not a (visible) associated type of class `C6'
+
+SimpleFail8.hs:9:8:
+    ‛Map’ is not a (visible) associated type of class ‛C6’
+
+SimpleFail8.hs:10:8:
+    ‛S3’ is not a (visible) associated type of class ‛C6’
diff --git a/tests/indexed-types/should_fail/T1897b.stderr b/tests/indexed-types/should_fail/T1897b.stderr
index 32bb3cff9..5bb6ef165 100644
--- a/tests/indexed-types/should_fail/T1897b.stderr
+++ b/tests/indexed-types/should_fail/T1897b.stderr
@@ -1,14 +1,14 @@
-
-T1897b.hs:16:1:
-    Could not deduce (Depend a0 ~ Depend a)
-    from the context (Bug a)
-      bound by the inferred type for `isValid':
-                 Bug a => [Depend a] -> Bool
-      at T1897b.hs:16:1-41
-    NB: `Depend' is a type function, and may not be injective
-    The type variable `a0' is ambiguous
-    Expected type: [Depend a] -> Bool
-      Actual type: [Depend a0] -> Bool
-    When checking that `isValid'
-      has the inferred type `forall a. Bug a => [Depend a] -> Bool'
-    Probable cause: the inferred type is ambiguous
+
+T1897b.hs:16:1:
+    Could not deduce (Depend a0 ~ Depend a)
+    from the context (Bug a)
+      bound by the inferred type for ‛isValid’:
+                 Bug a => [Depend a] -> Bool
+      at T1897b.hs:16:1-41
+    NB: ‛Depend’ is a type function, and may not be injective
+    The type variable ‛a0’ is ambiguous
+    Expected type: [Depend a] -> Bool
+      Actual type: [Depend a0] -> Bool
+    When checking that ‛isValid’
+      has the inferred type ‛forall a. Bug a => [Depend a] -> Bool’
+    Probable cause: the inferred type is ambiguous
diff --git a/tests/indexed-types/should_fail/T1900.stderr b/tests/indexed-types/should_fail/T1900.stderr
index 6d7eb62e3..08218a2ca 100644
--- a/tests/indexed-types/should_fail/T1900.stderr
+++ b/tests/indexed-types/should_fail/T1900.stderr
@@ -1,13 +1,13 @@
-
-T1900.hs:13:10:
-    Could not deduce (Depend s0 ~ Depend s)
-    from the context (Bug s)
-      bound by the type signature for check :: Bug s => Depend s -> Bool
-      at T1900.hs:13:10-36
-    NB: `Depend' is a type function, and may not be injective
-    The type variable `s0' is ambiguous
-    Expected type: Depend s -> Bool
-      Actual type: Depend s0 -> Bool
-    In the ambiguity check for: forall s. Bug s => Depend s -> Bool
-    In the type signature for `check':
-      check :: Bug s => Depend s -> Bool
+
+T1900.hs:13:10:
+    Could not deduce (Depend s0 ~ Depend s)
+    from the context (Bug s)
+      bound by the type signature for check :: Bug s => Depend s -> Bool
+      at T1900.hs:13:10-36
+    NB: ‛Depend’ is a type function, and may not be injective
+    The type variable ‛s0’ is ambiguous
+    Expected type: Depend s -> Bool
+      Actual type: Depend s0 -> Bool
+    In the ambiguity check for: forall s. Bug s => Depend s -> Bool
+    In the type signature for ‛check’:
+      check :: Bug s => Depend s -> Bool
diff --git a/tests/indexed-types/should_fail/T2157.stderr b/tests/indexed-types/should_fail/T2157.stderr
index 44f0a2436..0f6f272de 100644
--- a/tests/indexed-types/should_fail/T2157.stderr
+++ b/tests/indexed-types/should_fail/T2157.stderr
@@ -1,4 +1,4 @@
-
-T2157.hs:7:15:
-    Type synonym `S' should have 2 arguments, but has been given 1
-    In the type instance declaration for `F'
+
+T2157.hs:7:15:
+    Type synonym ‛S’ should have 2 arguments, but has been given 1
+    In the type instance declaration for ‛F’
diff --git a/tests/indexed-types/should_fail/T2203a.stderr b/tests/indexed-types/should_fail/T2203a.stderr
index cd12f6a7b..67390f298 100644
--- a/tests/indexed-types/should_fail/T2203a.stderr
+++ b/tests/indexed-types/should_fail/T2203a.stderr
@@ -1,5 +1,5 @@
 
 T2203a.hs:13:19:
     Illegal type synonym family application in instance:
-        Either a (TheFoo a)
-    In the instance declaration for `Bar (Either a (TheFoo a))'
+      Either a (TheFoo a)
+    In the instance declaration for ‛Bar (Either a (TheFoo a))’
diff --git a/tests/indexed-types/should_fail/T2239.stderr b/tests/indexed-types/should_fail/T2239.stderr
index 5c0403c6f..b322d9f06 100644
--- a/tests/indexed-types/should_fail/T2239.stderr
+++ b/tests/indexed-types/should_fail/T2239.stderr
@@ -1,28 +1,28 @@
-
-T2239.hs:47:13:
-    Couldn't match type `b -> b'
-                  with `forall b1. MyEq b1 Bool => b1 -> b1'
-    Expected type: (forall b1. MyEq b1 Bool => b1 -> b1) -> b -> b
-      Actual type: (b -> b) -> b -> b
-    In the expression:
-        id ::
-          (forall b. MyEq b Bool => b -> b)
-          -> (forall b. MyEq b Bool => b -> b)
-    In an equation for `complexFD':
-        complexFD
-          = id ::
-              (forall b. MyEq b Bool => b -> b)
-              -> (forall b. MyEq b Bool => b -> b)
-
-T2239.hs:50:13:
-    Couldn't match type `Bool -> Bool'
-                  with `forall b1. b1 ~ Bool => b1 -> b1'
-    Expected type: (forall b1. b1 ~ Bool => b1 -> b1) -> b -> b
-      Actual type: (b -> b) -> b -> b
-    In the expression:
-        id ::
-          (forall b. b ~ Bool => b -> b) -> (forall b. b ~ Bool => b -> b)
-    In an equation for `complexTF':
-        complexTF
-          = id ::
-              (forall b. b ~ Bool => b -> b) -> (forall b. b ~ Bool => b -> b)
+
+T2239.hs:47:13:
+    Couldn't match type ‛b -> b’
+                  with ‛forall b1. MyEq b1 Bool => b1 -> b1’
+    Expected type: (forall b1. MyEq b1 Bool => b1 -> b1) -> b -> b
+      Actual type: (b -> b) -> b -> b
+    In the expression:
+        id ::
+          (forall b. MyEq b Bool => b -> b)
+          -> (forall b. MyEq b Bool => b -> b)
+    In an equation for ‛complexFD’:
+        complexFD
+          = id ::
+              (forall b. MyEq b Bool => b -> b)
+              -> (forall b. MyEq b Bool => b -> b)
+
+T2239.hs:50:13:
+    Couldn't match type ‛Bool -> Bool’
+                  with ‛forall b1. b1 ~ Bool => b1 -> b1’
+    Expected type: (forall b1. b1 ~ Bool => b1 -> b1) -> b -> b
+      Actual type: (b -> b) -> b -> b
+    In the expression:
+        id ::
+          (forall b. b ~ Bool => b -> b) -> (forall b. b ~ Bool => b -> b)
+    In an equation for ‛complexTF’:
+        complexTF
+          = id ::
+              (forall b. b ~ Bool => b -> b) -> (forall b. b ~ Bool => b -> b)
diff --git a/tests/indexed-types/should_fail/T2334A.stderr b/tests/indexed-types/should_fail/T2334A.stderr
index 16ad7b047..ff4e35206 100644
--- a/tests/indexed-types/should_fail/T2334A.stderr
+++ b/tests/indexed-types/should_fail/T2334A.stderr
@@ -1,15 +1,15 @@
 
 T2334A.hs:9:26:
     The constructor of a newtype must have exactly one field
-      but `F' has two
-    In the definition of data constructor `F'
-    In the newtype instance declaration for `F'
+      but ‛F’ has two
+    In the definition of data constructor ‛F’
+    In the newtype instance declaration for ‛F’
 
 T2334A.hs:10:27:
     The constructor of a newtype must have exactly one field
-      but `H' has none
-    In the definition of data constructor `H'
-    In the newtype instance declaration for `F'
+      but ‛H’ has none
+    In the definition of data constructor ‛H’
+    In the newtype instance declaration for ‛F’
 
 T2334A.hs:12:15:
     Conflicting family instance declarations:
diff --git a/tests/indexed-types/should_fail/T2544.stderr b/tests/indexed-types/should_fail/T2544.stderr
index fae7cbf28..33e36a0aa 100644
--- a/tests/indexed-types/should_fail/T2544.stderr
+++ b/tests/indexed-types/should_fail/T2544.stderr
@@ -1,28 +1,28 @@
-
-T2544.hs:15:18:
-    Could not deduce (IxMap i0 ~ IxMap l)
-    from the context (Ix l, Ix r)
-      bound by the instance declaration at T2544.hs:13:10-37
-    NB: `IxMap' is a type function, and may not be injective
-    The type variable `i0' is ambiguous
-    Expected type: IxMap l [Int]
-      Actual type: IxMap i0 [Int]
-    Relevant bindings include
-      empty :: IxMap (l :|: r) [Int] (bound at T2544.hs:15:4)
-    In the first argument of `BiApp', namely `empty'
-    In the expression: BiApp empty empty
-    In an equation for `empty': empty = BiApp empty empty
-
-T2544.hs:15:24:
-    Could not deduce (IxMap i1 ~ IxMap r)
-    from the context (Ix l, Ix r)
-      bound by the instance declaration at T2544.hs:13:10-37
-    NB: `IxMap' is a type function, and may not be injective
-    The type variable `i1' is ambiguous
-    Expected type: IxMap r [Int]
-      Actual type: IxMap i1 [Int]
-    Relevant bindings include
-      empty :: IxMap (l :|: r) [Int] (bound at T2544.hs:15:4)
-    In the second argument of `BiApp', namely `empty'
-    In the expression: BiApp empty empty
-    In an equation for `empty': empty = BiApp empty empty
+
+T2544.hs:15:18:
+    Could not deduce (IxMap i0 ~ IxMap l)
+    from the context (Ix l, Ix r)
+      bound by the instance declaration at T2544.hs:13:10-37
+    NB: ‛IxMap’ is a type function, and may not be injective
+    The type variable ‛i0’ is ambiguous
+    Expected type: IxMap l [Int]
+      Actual type: IxMap i0 [Int]
+    Relevant bindings include
+      empty :: IxMap (l :|: r) [Int] (bound at T2544.hs:15:4)
+    In the first argument of ‛BiApp’, namely ‛empty’
+    In the expression: BiApp empty empty
+    In an equation for ‛empty’: empty = BiApp empty empty
+
+T2544.hs:15:24:
+    Could not deduce (IxMap i1 ~ IxMap r)
+    from the context (Ix l, Ix r)
+      bound by the instance declaration at T2544.hs:13:10-37
+    NB: ‛IxMap’ is a type function, and may not be injective
+    The type variable ‛i1’ is ambiguous
+    Expected type: IxMap r [Int]
+      Actual type: IxMap i1 [Int]
+    Relevant bindings include
+      empty :: IxMap (l :|: r) [Int] (bound at T2544.hs:15:4)
+    In the second argument of ‛BiApp’, namely ‛empty’
+    In the expression: BiApp empty empty
+    In an equation for ‛empty’: empty = BiApp empty empty
diff --git a/tests/indexed-types/should_fail/T2627b.stderr b/tests/indexed-types/should_fail/T2627b.stderr
index 871d455ea..61399d02d 100644
--- a/tests/indexed-types/should_fail/T2627b.stderr
+++ b/tests/indexed-types/should_fail/T2627b.stderr
@@ -1,8 +1,8 @@
-
-T2627b.hs:20:24:
-    Occurs check: cannot construct the infinite type:
-      a0 ~ Dual (Dual a0)
-    The type variable `a0' is ambiguous
-    In the expression: conn undefined undefined
-    In an equation for `conn':
-        conn (Rd k) (Wr a r) = conn undefined undefined
+
+T2627b.hs:20:24:
+    Occurs check: cannot construct the infinite type:
+      a0 ~ Dual (Dual a0)
+    The type variable ‛a0’ is ambiguous
+    In the expression: conn undefined undefined
+    In an equation for ‛conn’:
+        conn (Rd k) (Wr a r) = conn undefined undefined
diff --git a/tests/indexed-types/should_fail/T2664.stderr b/tests/indexed-types/should_fail/T2664.stderr
index f3996d914..4982410ca 100644
--- a/tests/indexed-types/should_fail/T2664.stderr
+++ b/tests/indexed-types/should_fail/T2664.stderr
@@ -1,23 +1,23 @@
-
-T2664.hs:31:52:
-    Could not deduce (b ~ a)
-    from the context (Connect a, Connect b)
-      bound by the instance declaration at T2664.hs:22:10-52
-    or from ((a :*: b) ~ Dual c, c ~ Dual (a :*: b))
-      bound by the type signature for
-                 newPChan :: ((a :*: b) ~ Dual c, c ~ Dual (a :*: b)) =>
-                             IO (PChan (a :*: b), PChan c)
-      at T2664.hs:23:5-12
-      `b' is a rigid type variable bound by
-          the instance declaration at T2664.hs:22:10
-      `a' is a rigid type variable bound by
-          the instance declaration at T2664.hs:22:10
-    Expected type: Dual (Dual a)
-      Actual type: b
-    Relevant bindings include
-      newPChan :: IO (PChan (a :*: b), PChan c) (bound at T2664.hs:23:5)
-      v :: MVar (Either (PChan a) (PChan b)) (bound at T2664.hs:24:9)
-    In the third argument of `pchoose', namely `newPChan'
-    In the first argument of `E', namely `(pchoose Right v newPChan)'
-    In the expression:
-      E (pchoose Right v newPChan) (pchoose Left v newPChan)
+
+T2664.hs:31:52:
+    Could not deduce (b ~ a)
+    from the context (Connect a, Connect b)
+      bound by the instance declaration at T2664.hs:22:10-52
+    or from ((a :*: b) ~ Dual c, c ~ Dual (a :*: b))
+      bound by the type signature for
+                 newPChan :: ((a :*: b) ~ Dual c, c ~ Dual (a :*: b)) =>
+                             IO (PChan (a :*: b), PChan c)
+      at T2664.hs:23:5-12
+      ‛b’ is a rigid type variable bound by
+          the instance declaration at T2664.hs:22:10
+      ‛a’ is a rigid type variable bound by
+          the instance declaration at T2664.hs:22:10
+    Expected type: Dual (Dual a)
+      Actual type: b
+    Relevant bindings include
+      newPChan :: IO (PChan (a :*: b), PChan c) (bound at T2664.hs:23:5)
+      v :: MVar (Either (PChan a) (PChan b)) (bound at T2664.hs:24:9)
+    In the third argument of ‛pchoose’, namely ‛newPChan’
+    In the first argument of ‛E’, namely ‛(pchoose Right v newPChan)’
+    In the expression:
+      E (pchoose Right v newPChan) (pchoose Left v newPChan)
diff --git a/tests/indexed-types/should_fail/T2693.stderr b/tests/indexed-types/should_fail/T2693.stderr
index 4427018fd..8c02ea263 100644
--- a/tests/indexed-types/should_fail/T2693.stderr
+++ b/tests/indexed-types/should_fail/T2693.stderr
@@ -1,43 +1,43 @@
-
-T2693.hs:11:7:
-    Couldn't match expected type `TFn a' with actual type `TFn a0'
-    NB: `TFn' is a type function, and may not be injective
-    The type variable `a0' is ambiguous
-    When checking that `x' has the inferred type `forall a. TFn a'
-    Probable cause: the inferred type is ambiguous
-    In the expression:
-      do { let Just x = ...;
-           let n = fst x + fst x;
-           return () }
-    In an equation for `f':
-        f = do { let Just x = ...;
-                 let n = ...;
-                 return () }
-
-T2693.hs:19:15:
-    Couldn't match expected type `(a2, b0)' with actual type `TFn a3'
-    The type variables `a2', `b0', `a3' are ambiguous
-    Relevant bindings include n :: a2 (bound at T2693.hs:19:7)
-    In the first argument of `fst', namely `x'
-    In the first argument of `(+)', namely `fst x'
-    In the expression: fst x + snd x
-
-T2693.hs:19:23:
-    Couldn't match expected type `(a4, a2)' with actual type `TFn a5'
-    The type variables `a2', `a4', `a5' are ambiguous
-    Relevant bindings include n :: a2 (bound at T2693.hs:19:7)
-    In the first argument of `snd', namely `x'
-    In the second argument of `(+)', namely `snd x'
-    In the expression: fst x + snd x
-
-T2693.hs:29:20:
-    Couldn't match type `TFn a0' with `PVR a1'
-    The type variables `a0', `a1' are ambiguous
-    Expected type: () -> Maybe (PVR a1)
-      Actual type: () -> Maybe (TFn a0)
-    In the first argument of `mapM', namely `g'
-    In a stmt of a 'do' block: pvs <- mapM g undefined
-    In the expression:
-      do { pvs <- mapM g undefined;
-           let n = (map pvrX pvs) `min` (map pvrX pvs);
-           undefined }
+
+T2693.hs:11:7:
+    Couldn't match expected type ‛TFn a’ with actual type ‛TFn a0’
+    NB: ‛TFn’ is a type function, and may not be injective
+    The type variable ‛a0’ is ambiguous
+    When checking that ‛x’ has the inferred type ‛forall a. TFn a’
+    Probable cause: the inferred type is ambiguous
+    In the expression:
+      do { let Just x = ...;
+           let n = fst x + fst x;
+           return () }
+    In an equation for ‛f’:
+        f = do { let Just x = ...;
+                 let n = ...;
+                 return () }
+
+T2693.hs:19:15:
+    Couldn't match expected type ‛(a2, b0)’ with actual type ‛TFn a3’
+    The type variables ‛a2’, ‛b0’, ‛a3’ are ambiguous
+    Relevant bindings include n :: a2 (bound at T2693.hs:19:7)
+    In the first argument of ‛fst’, namely ‛x’
+    In the first argument of ‛(+)’, namely ‛fst x’
+    In the expression: fst x + snd x
+
+T2693.hs:19:23:
+    Couldn't match expected type ‛(a4, a2)’ with actual type ‛TFn a5’
+    The type variables ‛a2’, ‛a4’, ‛a5’ are ambiguous
+    Relevant bindings include n :: a2 (bound at T2693.hs:19:7)
+    In the first argument of ‛snd’, namely ‛x’
+    In the second argument of ‛(+)’, namely ‛snd x’
+    In the expression: fst x + snd x
+
+T2693.hs:29:20:
+    Couldn't match type ‛TFn a0’ with ‛PVR a1’
+    The type variables ‛a0’, ‛a1’ are ambiguous
+    Expected type: () -> Maybe (PVR a1)
+      Actual type: () -> Maybe (TFn a0)
+    In the first argument of ‛mapM’, namely ‛g’
+    In a stmt of a 'do' block: pvs <- mapM g undefined
+    In the expression:
+      do { pvs <- mapM g undefined;
+           let n = (map pvrX pvs) `min` (map pvrX pvs);
+           undefined }
diff --git a/tests/indexed-types/should_fail/T3092.stderr b/tests/indexed-types/should_fail/T3092.stderr
index f45e35580..436db19f8 100644
--- a/tests/indexed-types/should_fail/T3092.stderr
+++ b/tests/indexed-types/should_fail/T3092.stderr
@@ -1,10 +1,10 @@
-
-T3092.hs:5:1:
-    Illegal family instance for `T'
-      (T is not an indexed type family)
-    In the data instance declaration for `T'
-
-T3092.hs:8:1:
-    Illegal family instance for `S'
-      (S is not an indexed type family)
-    In the type instance declaration for `S'
+
+T3092.hs:5:1:
+    Illegal family instance for ‛T’
+      (T is not an indexed type family)
+    In the data instance declaration for ‛T’
+
+T3092.hs:8:1:
+    Illegal family instance for ‛S’
+      (S is not an indexed type family)
+    In the type instance declaration for ‛S’
diff --git a/tests/indexed-types/should_fail/T3330a.stderr b/tests/indexed-types/should_fail/T3330a.stderr
index e44ab4d6f..9c4fedfa4 100644
--- a/tests/indexed-types/should_fail/T3330a.stderr
+++ b/tests/indexed-types/should_fail/T3330a.stderr
@@ -1,8 +1,8 @@
 
 T3330a.hs:19:34:
-    Couldn't match type `ix'
-                  with `r ix1 -> Writer [AnyF ((->) (s0 ix0 -> ix1))] (r'0 ix1)'
-      `ix' is a rigid type variable bound by
+    Couldn't match type ‛ix’
+                  with ‛r ix1 -> Writer [AnyF ((->) (s0 ix0 -> ix1))] (r'0 ix1)’
+      ‛ix’ is a rigid type variable bound by
            the type signature for children :: s ix -> PF s r ix -> [AnyF s]
            at T3330a.hs:18:13
     Expected type: (s0 ix0 -> ix1)
@@ -12,13 +12,13 @@ T3330a.hs:19:34:
       children :: s ix -> PF s r ix -> [AnyF s] (bound at T3330a.hs:19:1)
       p :: s ix (bound at T3330a.hs:19:10)
       x :: PF s r ix (bound at T3330a.hs:19:12)
-    In the first argument of `hmapM', namely `p'
-    In the first argument of `execWriter', namely `(hmapM p collect x)'
+    In the first argument of ‛hmapM’, namely ‛p’
+    In the first argument of ‛execWriter’, namely ‛(hmapM p collect x)’
     In the expression: execWriter (hmapM p collect x)
 
 T3330a.hs:19:34:
-    Couldn't match type `s' with `(->) (s0 ix0 -> ix1)'
-      `s' is a rigid type variable bound by
+    Couldn't match type ‛s’ with ‛(->) (s0 ix0 -> ix1)’
+      ‛s’ is a rigid type variable bound by
           the type signature for children :: s ix -> PF s r ix -> [AnyF s]
           at T3330a.hs:18:13
     Expected type: (s0 ix0 -> ix1)
@@ -28,13 +28,13 @@ T3330a.hs:19:34:
       children :: s ix -> PF s r ix -> [AnyF s] (bound at T3330a.hs:19:1)
       p :: s ix (bound at T3330a.hs:19:10)
       x :: PF s r ix (bound at T3330a.hs:19:12)
-    In the first argument of `hmapM', namely `p'
-    In the first argument of `execWriter', namely `(hmapM p collect x)'
+    In the first argument of ‛hmapM’, namely ‛p’
+    In the first argument of ‛execWriter’, namely ‛(hmapM p collect x)’
     In the expression: execWriter (hmapM p collect x)
 
 T3330a.hs:19:44:
-    Couldn't match type `ix' with `r0 ix0 -> Writer [AnyF s0] (r0 ix0)'
-      `ix' is a rigid type variable bound by
+    Couldn't match type ‛ix’ with ‛r0 ix0 -> Writer [AnyF s0] (r0 ix0)’
+      ‛ix’ is a rigid type variable bound by
            the type signature for children :: s ix -> PF s r ix -> [AnyF s]
            at T3330a.hs:18:13
     Expected type: PF s r (r0 ix0 -> Writer [AnyF s0] (r0 ix0))
@@ -43,6 +43,6 @@ T3330a.hs:19:44:
       children :: s ix -> PF s r ix -> [AnyF s] (bound at T3330a.hs:19:1)
       p :: s ix (bound at T3330a.hs:19:10)
       x :: PF s r ix (bound at T3330a.hs:19:12)
-    In the third argument of `hmapM', namely `x'
-    In the first argument of `execWriter', namely `(hmapM p collect x)'
+    In the third argument of ‛hmapM’, namely ‛x’
+    In the first argument of ‛execWriter’, namely ‛(hmapM p collect x)’
     In the expression: execWriter (hmapM p collect x)
diff --git a/tests/indexed-types/should_fail/T3330c.stderr b/tests/indexed-types/should_fail/T3330c.stderr
index 8c657c811..52d6afe3e 100644
--- a/tests/indexed-types/should_fail/T3330c.stderr
+++ b/tests/indexed-types/should_fail/T3330c.stderr
@@ -1,11 +1,11 @@
 
 T3330c.hs:23:43:
-    Couldn't match kind `*' with `* -> *'
+    Couldn't match kind ‛*’ with ‛* -> *’
     When matching types
       Der ((->) x) :: * -> *
       R :: (* -> *) -> *
     Expected type: Der ((->) x) (f1 x)
       Actual type: R f1
-    In the first argument of `plug', namely `rf'
-    In the first argument of `Inl', namely `(plug rf df x)'
+    In the first argument of ‛plug’, namely ‛rf’
+    In the first argument of ‛Inl’, namely ‛(plug rf df x)’
     In the expression: Inl (plug rf df x)
diff --git a/tests/indexed-types/should_fail/T3440.stderr b/tests/indexed-types/should_fail/T3440.stderr
index b9f49fa0b..af8b90fd7 100644
--- a/tests/indexed-types/should_fail/T3440.stderr
+++ b/tests/indexed-types/should_fail/T3440.stderr
@@ -4,14 +4,14 @@ T3440.hs:11:22:
     from the context (Fam a ~ Fam a1)
       bound by a pattern with constructor
                  GADT :: forall a. a -> Fam a -> GADT (Fam a),
-               in an equation for `unwrap'
+               in an equation for ‛unwrap’
       at T3440.hs:11:9-16
-      `a1' is a rigid type variable bound by
+      ‛a1’ is a rigid type variable bound by
            a pattern with constructor
              GADT :: forall a. a -> Fam a -> GADT (Fam a),
-           in an equation for `unwrap'
+           in an equation for ‛unwrap’
            at T3440.hs:11:9
-      `a' is a rigid type variable bound by
+      ‛a’ is a rigid type variable bound by
           the type signature for unwrap :: GADT (Fam a) -> (a, Fam a)
           at T3440.hs:10:11
     Relevant bindings include
@@ -20,4 +20,4 @@ T3440.hs:11:22:
       y :: Fam a1 (bound at T3440.hs:11:16)
     In the expression: x
     In the expression: (x, y)
-    In an equation for `unwrap': unwrap (GADT x y) = (x, y)
+    In an equation for ‛unwrap’: unwrap (GADT x y) = (x, y)
diff --git a/tests/indexed-types/should_fail/T4093a.stderr b/tests/indexed-types/should_fail/T4093a.stderr
index 5a5ce0826..83578248a 100644
--- a/tests/indexed-types/should_fail/T4093a.stderr
+++ b/tests/indexed-types/should_fail/T4093a.stderr
@@ -4,12 +4,12 @@ T4093a.hs:8:8:
     from the context (Foo e ~ Maybe e)
       bound by the type signature for hang :: Foo e ~ Maybe e => Foo e
       at T4093a.hs:7:9-34
-      `e' is a rigid type variable bound by
+      ‛e’ is a rigid type variable bound by
           the type signature for hang :: Foo e ~ Maybe e => Foo e
           at T4093a.hs:7:9
     Expected type: Foo e
       Actual type: Maybe ()
     Relevant bindings include hang :: Foo e (bound at T4093a.hs:8:1)
-    In the return type of a call of `Just'
+    In the return type of a call of ‛Just’
     In the expression: Just ()
-    In an equation for `hang': hang = Just ()
+    In an equation for ‛hang’: hang = Just ()
diff --git a/tests/indexed-types/should_fail/T4093b.stderr b/tests/indexed-types/should_fail/T4093b.stderr
index 67f9b7d92..b80cf634a 100644
--- a/tests/indexed-types/should_fail/T4093b.stderr
+++ b/tests/indexed-types/should_fail/T4093b.stderr
@@ -8,7 +8,7 @@ T4093b.hs:31:13:
                                      EitherCO x (A C C n) (A C O n) ~ A C x n) =>
                                     Block n e x -> A e x n
       at T4093b.hs:(20,3)-(22,26)
-      `e' is a rigid type variable bound by
+      ‛e’ is a rigid type variable bound by
           the type signature for
             blockToNodeList :: (EitherCO e (A C O n) (A O O n) ~ A e O n,
                                 EitherCO x (A C C n) (A C O n) ~ A C x n) =>
@@ -26,8 +26,8 @@ T4093b.hs:31:13:
            -> EitherCO e (A C O n) (A O O n) -> EitherCO e (A C O n) (A O O n)
         (bound at T4093b.hs:31:5)
     In the expression: (JustC n, NothingC)
-    In an equation for `f': f n _ = (JustC n, NothingC)
-    In an equation for `blockToNodeList':
+    In an equation for ‛f’: f n _ = (JustC n, NothingC)
+    In an equation for ‛blockToNodeList’:
         blockToNodeList b
           = foldBlockNodesF (f, l) b z
           where
diff --git a/tests/indexed-types/should_fail/T4099.stderr b/tests/indexed-types/should_fail/T4099.stderr
index 60e379525..312b0b644 100644
--- a/tests/indexed-types/should_fail/T4099.stderr
+++ b/tests/indexed-types/should_fail/T4099.stderr
@@ -1,23 +1,23 @@
-
-T4099.hs:11:30:
-    Couldn't match expected type `T a0' with actual type `T b'
-    NB: `T' is a type function, and may not be injective
-    The type variable `a0' is ambiguous
-    Relevant bindings include
-      bar1 :: b -> T b -> Int (bound at T4099.hs:11:1)
-      a :: b (bound at T4099.hs:11:6)
-      x :: T b (bound at T4099.hs:11:8)
-    In the second argument of `foo', namely `x'
-    In the expression: foo (error "urk") x
-    In an equation for `bar1': bar1 a x = foo (error "urk") x
-
-T4099.hs:14:30:
-    Couldn't match expected type `T a1' with actual type `Maybe b'
-    The type variable `a1' is ambiguous
-    Relevant bindings include
-      bar2 :: b -> Maybe b -> Int (bound at T4099.hs:14:1)
-      a :: b (bound at T4099.hs:14:6)
-      x :: Maybe b (bound at T4099.hs:14:8)
-    In the second argument of `foo', namely `x'
-    In the expression: foo (error "urk") x
-    In an equation for `bar2': bar2 a x = foo (error "urk") x
+
+T4099.hs:11:30:
+    Couldn't match expected type ‛T a0’ with actual type ‛T b’
+    NB: ‛T’ is a type function, and may not be injective
+    The type variable ‛a0’ is ambiguous
+    Relevant bindings include
+      bar1 :: b -> T b -> Int (bound at T4099.hs:11:1)
+      a :: b (bound at T4099.hs:11:6)
+      x :: T b (bound at T4099.hs:11:8)
+    In the second argument of ‛foo’, namely ‛x’
+    In the expression: foo (error "urk") x
+    In an equation for ‛bar1’: bar1 a x = foo (error "urk") x
+
+T4099.hs:14:30:
+    Couldn't match expected type ‛T a1’ with actual type ‛Maybe b’
+    The type variable ‛a1’ is ambiguous
+    Relevant bindings include
+      bar2 :: b -> Maybe b -> Int (bound at T4099.hs:14:1)
+      a :: b (bound at T4099.hs:14:6)
+      x :: Maybe b (bound at T4099.hs:14:8)
+    In the second argument of ‛foo’, namely ‛x’
+    In the expression: foo (error "urk") x
+    In an equation for ‛bar2’: bar2 a x = foo (error "urk") x
diff --git a/tests/indexed-types/should_fail/T4174.stderr b/tests/indexed-types/should_fail/T4174.stderr
index 81fb603dd..5547b2597 100644
--- a/tests/indexed-types/should_fail/T4174.stderr
+++ b/tests/indexed-types/should_fail/T4174.stderr
@@ -1,7 +1,7 @@
 
 T4174.hs:42:12:
-    Couldn't match type `False' with `True'
+    Couldn't match type ‛False’ with ‛True’
     Expected type: True
       Actual type: GHCVersion (WayOf m) :>=: GHC6'10 Minor1
     In the expression: sync_large_objects
-    In an equation for `testcase': testcase = sync_large_objects
+    In an equation for ‛testcase’: testcase = sync_large_objects
diff --git a/tests/indexed-types/should_fail/T4179.stderr b/tests/indexed-types/should_fail/T4179.stderr
index 7236a50c8..8f5ded1ff 100644
--- a/tests/indexed-types/should_fail/T4179.stderr
+++ b/tests/indexed-types/should_fail/T4179.stderr
@@ -7,7 +7,7 @@ T4179.hs:26:16:
                  fCon :: (Functor x, DoC (FCon x)) =>
                          Con x -> A2 (FCon x) -> A3 (FCon x)
       at T4179.hs:25:9-72
-    NB: `A3' is a type function, and may not be injective
+    NB: ‛A3’ is a type function, and may not be injective
     Expected type: x (A2 (FCon x) -> A3 (FCon x))
                    -> A2 (FCon x) -> A3 (FCon x)
       Actual type: x (A2 (FCon x) -> A3 (FCon x))
@@ -16,6 +16,6 @@ T4179.hs:26:16:
     Relevant bindings include
       fCon :: Con x -> A2 (FCon x) -> A3 (FCon x)
         (bound at T4179.hs:26:1)
-    In the first argument of `foldDoC', namely `op'
+    In the first argument of ‛foldDoC’, namely ‛op’
     In the expression: foldDoC op
-    In an equation for `fCon': fCon = foldDoC op
+    In an equation for ‛fCon’: fCon = foldDoC op
diff --git a/tests/indexed-types/should_fail/T4272.stderr b/tests/indexed-types/should_fail/T4272.stderr
index a4e952556..f3dcdbc13 100644
--- a/tests/indexed-types/should_fail/T4272.stderr
+++ b/tests/indexed-types/should_fail/T4272.stderr
@@ -5,7 +5,7 @@ T4272.hs:15:26:
       bound by the type signature for
                  laws :: TermLike a => TermFamily a a -> b
       at T4272.hs:14:9-53
-      `a' is a rigid type variable bound by
+      ‛a’ is a rigid type variable bound by
           the type signature for laws :: TermLike a => TermFamily a a -> b
           at T4272.hs:14:16
     Expected type: TermFamily a (TermFamily a a)
@@ -13,8 +13,8 @@ T4272.hs:15:26:
     Relevant bindings include
       laws :: TermFamily a a -> b (bound at T4272.hs:15:1)
       t :: TermFamily a a (bound at T4272.hs:15:6)
-    In the first argument of `terms', namely
-      `(undefined :: TermFamily a a)'
-    In the second argument of `prune', namely
-      `(terms (undefined :: TermFamily a a))'
+    In the first argument of ‛terms’, namely
+      ‛(undefined :: TermFamily a a)’
+    In the second argument of ‛prune’, namely
+      ‛(terms (undefined :: TermFamily a a))’
     In the expression: prune t (terms (undefined :: TermFamily a a))
diff --git a/tests/indexed-types/should_fail/T4485.stderr b/tests/indexed-types/should_fail/T4485.stderr
index 358886952..bd408824b 100644
--- a/tests/indexed-types/should_fail/T4485.stderr
+++ b/tests/indexed-types/should_fail/T4485.stderr
@@ -1,30 +1,30 @@
-
-T4485.hs:47:15:
-    Overlapping instances for EmbedAsChild
-                                (IdentityT IO) (XMLGenT m0 (XML m0))
-      arising from a use of `asChild'
-    Matching instances:
-      instance [overlap ok] (EmbedAsChild m c, m1 ~ m) =>
-                            EmbedAsChild m (XMLGenT m1 c)
-        -- Defined at T4485.hs:29:10
-      instance [overlap ok] EmbedAsChild
-                              (IdentityT IO) (XMLGenT Identity ())
-        -- Defined at T4485.hs:42:10
-    (The choice depends on the instantiation of `m0'
-     To pick the first instance above, use -XIncoherentInstances
-     when compiling the other instance declarations)
-    In the expression: asChild
-    In the expression: asChild $ (genElement "foo")
-    In an equation for `asChild':
-        asChild b = asChild $ (genElement "foo")
-
-T4485.hs:47:26:
-    No instance for (XMLGen m0) arising from a use of `genElement'
-    The type variable `m0' is ambiguous
-    Note: there is a potential instance available:
-      instance [overlap ok] XMLGen (IdentityT m)
-        -- Defined at T4485.hs:36:10
-    In the second argument of `($)', namely `(genElement "foo")'
-    In the expression: asChild $ (genElement "foo")
-    In an equation for `asChild':
-        asChild b = asChild $ (genElement "foo")
+
+T4485.hs:47:15:
+    Overlapping instances for EmbedAsChild
+                                (IdentityT IO) (XMLGenT m0 (XML m0))
+      arising from a use of ‛asChild’
+    Matching instances:
+      instance [overlap ok] (EmbedAsChild m c, m1 ~ m) =>
+                            EmbedAsChild m (XMLGenT m1 c)
+        -- Defined at T4485.hs:29:10
+      instance [overlap ok] EmbedAsChild
+                              (IdentityT IO) (XMLGenT Identity ())
+        -- Defined at T4485.hs:42:10
+    (The choice depends on the instantiation of ‛m0’
+     To pick the first instance above, use -XIncoherentInstances
+     when compiling the other instance declarations)
+    In the expression: asChild
+    In the expression: asChild $ (genElement "foo")
+    In an equation for ‛asChild’:
+        asChild b = asChild $ (genElement "foo")
+
+T4485.hs:47:26:
+    No instance for (XMLGen m0) arising from a use of ‛genElement’
+    The type variable ‛m0’ is ambiguous
+    Note: there is a potential instance available:
+      instance [overlap ok] XMLGen (IdentityT m)
+        -- Defined at T4485.hs:36:10
+    In the second argument of ‛($)’, namely ‛(genElement "foo")’
+    In the expression: asChild $ (genElement "foo")
+    In an equation for ‛asChild’:
+        asChild b = asChild $ (genElement "foo")
diff --git a/tests/indexed-types/should_fail/T5439.stderr b/tests/indexed-types/should_fail/T5439.stderr
index 7115f3026..4f8340481 100644
--- a/tests/indexed-types/should_fail/T5439.stderr
+++ b/tests/indexed-types/should_fail/T5439.stderr
@@ -1,28 +1,28 @@
-
-T5439.hs:83:28:
-    Couldn't match type `Attempt t0 -> Attempt (HElemOf l0)'
-                  with `Attempt (HElemOf rs)'
-    Expected type: f (Attempt (HNth n0 l0) -> Attempt (HElemOf l0))
-      Actual type: f (Attempt (WaitOpResult (WaitOps rs)))
-    Relevant bindings include
-      registerWaitOp :: WaitOps rs
-                        -> f (Attempt (WaitOpResult (WaitOps rs))) -> IO Bool
-        (bound at T5439.hs:62:3)
-      ops :: WaitOps rs (bound at T5439.hs:62:18)
-      ev :: f (Attempt (WaitOpResult (WaitOps rs)))
-        (bound at T5439.hs:62:22)
-      register :: Bool -> Peano n -> WaitOps (HDrop n rs) -> IO Bool
-        (bound at T5439.hs:65:9)
-    In the first argument of `complete', namely `ev'
-    In the expression: complete ev
-    In a stmt of a 'do' block:
-      c <- complete ev $ inj $ Failure (e :: SomeException)
-
-T5439.hs:83:39:
-    Couldn't match expected type `Peano n0'
-                with actual type `Attempt α0'
-    In the return type of a call of `Failure'
-    In the second argument of `($)', namely
-      `Failure (e :: SomeException)'
-    In the second argument of `($)', namely
-      `inj $ Failure (e :: SomeException)'
+
+T5439.hs:83:28:
+    Couldn't match type ‛Attempt t0 -> Attempt (HElemOf l0)’
+                  with ‛Attempt (HElemOf rs)’
+    Expected type: f (Attempt (HNth n0 l0) -> Attempt (HElemOf l0))
+      Actual type: f (Attempt (WaitOpResult (WaitOps rs)))
+    Relevant bindings include
+      registerWaitOp :: WaitOps rs
+                        -> f (Attempt (WaitOpResult (WaitOps rs))) -> IO Bool
+        (bound at T5439.hs:62:3)
+      ops :: WaitOps rs (bound at T5439.hs:62:18)
+      ev :: f (Attempt (WaitOpResult (WaitOps rs)))
+        (bound at T5439.hs:62:22)
+      register :: Bool -> Peano n -> WaitOps (HDrop n rs) -> IO Bool
+        (bound at T5439.hs:65:9)
+    In the first argument of ‛complete’, namely ‛ev’
+    In the expression: complete ev
+    In a stmt of a 'do' block:
+      c <- complete ev $ inj $ Failure (e :: SomeException)
+
+T5439.hs:83:39:
+    Couldn't match expected type ‛Peano n0’
+                with actual type ‛Attempt α0’
+    In the return type of a call of ‛Failure’
+    In the second argument of ‛($)’, namely
+      ‛Failure (e :: SomeException)’
+    In the second argument of ‛($)’, namely
+      ‛inj $ Failure (e :: SomeException)’
diff --git a/tests/indexed-types/should_fail/T5515.stderr b/tests/indexed-types/should_fail/T5515.stderr
index 535048d88..c3d6b9f66 100644
--- a/tests/indexed-types/should_fail/T5515.stderr
+++ b/tests/indexed-types/should_fail/T5515.stderr
@@ -1,8 +1,8 @@
 
 T5515.hs:9:8:
-    The RHS of an associated type declaration mentions type variable `a'
+    The RHS of an associated type declaration mentions type variable ‛a’
       All such variables must be bound on the LHS
 
 T5515.hs:15:8:
-    The RHS of an associated type declaration mentions type variable `a'
+    The RHS of an associated type declaration mentions type variable ‛a’
       All such variables must be bound on the LHS
diff --git a/tests/indexed-types/should_fail/T5934.stderr b/tests/indexed-types/should_fail/T5934.stderr
index 892589934..d03646760 100644
--- a/tests/indexed-types/should_fail/T5934.stderr
+++ b/tests/indexed-types/should_fail/T5934.stderr
@@ -1,7 +1,7 @@
-
-T5934.hs:12:7:
-    Cannot instantiate unification variable `a0'
-    with a type involving foralls: (forall s. GenST s) -> Int
-      Perhaps you want -XImpredicativeTypes
-    In the expression: 0
-    In an equation for `run': run = 0
+
+T5934.hs:12:7:
+    Cannot instantiate unification variable ‛a0’
+    with a type involving foralls: (forall s. GenST s) -> Int
+      Perhaps you want -XImpredicativeTypes
+    In the expression: 0
+    In an equation for ‛run’: run = 0
diff --git a/tests/indexed-types/should_fail/T6123.stderr b/tests/indexed-types/should_fail/T6123.stderr
index cf8eedda0..4fbdf9bf4 100644
--- a/tests/indexed-types/should_fail/T6123.stderr
+++ b/tests/indexed-types/should_fail/T6123.stderr
@@ -1,7 +1,7 @@
-
-T6123.hs:10:14:
-    Occurs check: cannot construct the infinite type: a0 ~ Id a0
-    The type variable `a0' is ambiguous
-    Relevant bindings include cundefined :: a0 (bound at T6123.hs:10:1)
-    In the expression: cid undefined
-    In an equation for `cundefined': cundefined = cid undefined
+
+T6123.hs:10:14:
+    Occurs check: cannot construct the infinite type: a0 ~ Id a0
+    The type variable ‛a0’ is ambiguous
+    Relevant bindings include cundefined :: a0 (bound at T6123.hs:10:1)
+    In the expression: cid undefined
+    In an equation for ‛cundefined’: cundefined = cid undefined
diff --git a/tests/indexed-types/should_fail/T7010.stderr b/tests/indexed-types/should_fail/T7010.stderr
index 3d059736f..50c4bd0fd 100644
--- a/tests/indexed-types/should_fail/T7010.stderr
+++ b/tests/indexed-types/should_fail/T7010.stderr
@@ -1,8 +1,8 @@
 
 T7010.hs:53:27:
-    Couldn't match type `Serial (IO Float)' with `IO Float'
+    Couldn't match type ‛Serial (IO Float)’ with ‛IO Float’
     Expected type: (Float, ValueTuple Vector)
       Actual type: (Float, ValueTuple Float)
-    In the first argument of `withArgs', namely `plug'
+    In the first argument of ‛withArgs’, namely ‛plug’
     In the expression: withArgs plug
-    In an equation for `filterFormants': filterFormants = withArgs plug
+    In an equation for ‛filterFormants’: filterFormants = withArgs plug
diff --git a/tests/indexed-types/should_fail/T7194.stderr b/tests/indexed-types/should_fail/T7194.stderr
index 385765df6..a575dde33 100644
--- a/tests/indexed-types/should_fail/T7194.stderr
+++ b/tests/indexed-types/should_fail/T7194.stderr
@@ -1,7 +1,7 @@
 
 T7194.hs:18:35:
-    Couldn't match expected type `b0' with actual type `F a'
-      because type variable `a' would escape its scope
+    Couldn't match expected type ‛b0’ with actual type ‛F a’
+      because type variable ‛a’ would escape its scope
     This (rigid, skolem) type variable is bound by
       the type signature for g :: C (F a) => a -> Int
       at T7194.hs:17:23-41
@@ -9,6 +9,6 @@ T7194.hs:18:35:
       x :: b0 (bound at T7194.hs:17:9)
       g :: a -> Int (bound at T7194.hs:18:18)
       y :: a (bound at T7194.hs:18:20)
-    In the return type of a call of `foo'
+    In the return type of a call of ‛foo’
     In the expression: foo y
-    In the first argument of `length', namely `[x, foo y]'
+    In the first argument of ‛length’, namely ‛[x, foo y]’
diff --git a/tests/indexed-types/should_fail/T7354.stderr b/tests/indexed-types/should_fail/T7354.stderr
index d5c0f1ce5..1fb91e4da 100644
--- a/tests/indexed-types/should_fail/T7354.stderr
+++ b/tests/indexed-types/should_fail/T7354.stderr
@@ -6,6 +6,6 @@ T7354.hs:28:11:
       Actual type: Prim [a] a -> a
     Relevant bindings include
       foo :: Prim [a] a -> t (bound at T7354.hs:28:1)
-    In the first argument of `ana', namely `alg'
+    In the first argument of ‛ana’, namely ‛alg’
     In the expression: ana alg
-    In an equation for `foo': foo = ana alg
+    In an equation for ‛foo’: foo = ana alg
diff --git a/tests/indexed-types/should_fail/T7354a.stderr b/tests/indexed-types/should_fail/T7354a.stderr
index 1b66b8797..d05b0f9b6 100644
--- a/tests/indexed-types/should_fail/T7354a.stderr
+++ b/tests/indexed-types/should_fail/T7354a.stderr
@@ -1,7 +1,7 @@
 
 T7354a.hs:5:13:
-    Couldn't match expected type `Base t t' with actual type `()'
+    Couldn't match expected type ‛Base t t’ with actual type ‛()’
     Relevant bindings include foo :: t (bound at T7354a.hs:5:1)
-    In the first argument of `embed', namely `()'
+    In the first argument of ‛embed’, namely ‛()’
     In the expression: embed ()
-    In an equation for `foo': foo = embed ()
+    In an equation for ‛foo’: foo = embed ()
diff --git a/tests/indexed-types/should_fail/T7536.stderr b/tests/indexed-types/should_fail/T7536.stderr
index faea85e91..0c242a902 100644
--- a/tests/indexed-types/should_fail/T7536.stderr
+++ b/tests/indexed-types/should_fail/T7536.stderr
@@ -1,5 +1,5 @@
 
 T7536.hs:8:15:
-    Family instance purports to bind type variable `a'
+    Family instance purports to bind type variable ‛a’
       but the real LHS (expanding synonyms) is: TF Int = ...
-    In the type instance declaration for `TF'
+    In the type instance declaration for ‛TF’
diff --git a/tests/indexed-types/should_fail/TyFamArity1.stderr b/tests/indexed-types/should_fail/TyFamArity1.stderr
index b0076287f..adfcc37a0 100644
--- a/tests/indexed-types/should_fail/TyFamArity1.stderr
+++ b/tests/indexed-types/should_fail/TyFamArity1.stderr
@@ -1,4 +1,4 @@
-
-TyFamArity1.hs:4:15:
-    Number of parameters must match family declaration; expected 2
-    In the type instance declaration for `T'
+
+TyFamArity1.hs:4:15:
+    Number of parameters must match family declaration; expected 2
+    In the type instance declaration for ‛T’
diff --git a/tests/indexed-types/should_fail/TyFamArity2.stderr b/tests/indexed-types/should_fail/TyFamArity2.stderr
index ad71adc7d..d602a2d5e 100644
--- a/tests/indexed-types/should_fail/TyFamArity2.stderr
+++ b/tests/indexed-types/should_fail/TyFamArity2.stderr
@@ -1,4 +1,4 @@
-
-TyFamArity2.hs:4:15:
-    Number of parameters must match family declaration; expected 1
-    In the type instance declaration for `T'
+
+TyFamArity2.hs:4:15:
+    Number of parameters must match family declaration; expected 1
+    In the type instance declaration for ‛T’
diff --git a/tests/indexed-types/should_fail/TyFamUndec.stderr b/tests/indexed-types/should_fail/TyFamUndec.stderr
index 6bb2af771..fef47b534 100644
--- a/tests/indexed-types/should_fail/TyFamUndec.stderr
+++ b/tests/indexed-types/should_fail/TyFamUndec.stderr
@@ -1,18 +1,18 @@
-
-TyFamUndec.hs:6:15:
-    Variable `b' occurs more often than in the instance head
-      in the type family application: T (b, b)
-    (Use -XUndecidableInstances to permit this)
-    In the type instance declaration for `T'
-
-TyFamUndec.hs:7:15:
-    Application is no smaller than the instance head
-      in the type family application: T (a, Maybe b)
-    (Use -XUndecidableInstances to permit this)
-    In the type instance declaration for `T'
-
-TyFamUndec.hs:8:15:
-    Nested type family application
-      in the type family application: T (a, T b)
-    (Use -XUndecidableInstances to permit this)
-    In the type instance declaration for `T'
+
+TyFamUndec.hs:6:15:
+    Variable ‛b’ occurs more often than in the instance head
+      in the type family application: T (b, b)
+    (Use -XUndecidableInstances to permit this)
+    In the type instance declaration for ‛T’
+
+TyFamUndec.hs:7:15:
+    Application is no smaller than the instance head
+      in the type family application: T (a, Maybe b)
+    (Use -XUndecidableInstances to permit this)
+    In the type instance declaration for ‛T’
+
+TyFamUndec.hs:8:15:
+    Nested type family application
+      in the type family application: T (a, T b)
+    (Use -XUndecidableInstances to permit this)
+    In the type instance declaration for ‛T’
diff --git a/tests/mdo/should_fail/mdofail001.stderr b/tests/mdo/should_fail/mdofail001.stderr
index 67929e58e..8d6d86bc9 100644
--- a/tests/mdo/should_fail/mdofail001.stderr
+++ b/tests/mdo/should_fail/mdofail001.stderr
@@ -1,6 +1,6 @@
 
 mdofail001.hs:10:32:
-    No instance for (Num Char) arising from the literal `1'
+    No instance for (Num Char) arising from the literal ‛1’
     In the expression: 1
-    In the first argument of `l', namely `[1, 2, 3]'
+    In the first argument of ‛l’, namely ‛[1, 2, 3]’
     In the expression: l [1, 2, 3]
diff --git a/tests/mdo/should_fail/mdofail002.stderr b/tests/mdo/should_fail/mdofail002.stderr
index a1327c6df..badd7383e 100644
--- a/tests/mdo/should_fail/mdofail002.stderr
+++ b/tests/mdo/should_fail/mdofail002.stderr
@@ -1,5 +1,5 @@
 
 mdofail002.hs:10:9:
-    Conflicting definitions for `x'
+    Conflicting definitions for ‛x’
     Bound at: mdofail002.hs:10:9
               mdofail002.hs:11:9
diff --git a/tests/mdo/should_fail/mdofail003.stderr b/tests/mdo/should_fail/mdofail003.stderr
index e093fe0a7..ccb10dfb8 100644
--- a/tests/mdo/should_fail/mdofail003.stderr
+++ b/tests/mdo/should_fail/mdofail003.stderr
@@ -1,5 +1,5 @@
 
 mdofail003.hs:10:9:
-    Conflicting definitions for `x'
+    Conflicting definitions for ‛x’
     Bound at: mdofail003.hs:10:9
               mdofail003.hs:11:13
diff --git a/tests/module/T414.stderr b/tests/module/T414.stderr
index a5052fb76..b9af6935f 100644
--- a/tests/module/T414.stderr
+++ b/tests/module/T414.stderr
@@ -1,3 +1,3 @@
 
 T414.hs:1:1:
-    The main function `main' is not exported by module `Main'
+    The main function ‛main’ is not exported by module ‛Main’
diff --git a/tests/module/mod1.stderr b/tests/module/mod1.stderr
index e665f8468..51d9e07b1 100644
--- a/tests/module/mod1.stderr
+++ b/tests/module/mod1.stderr
@@ -1,4 +1,4 @@
 
 mod1.hs:3:1:
-    Failed to load interface for `N'
+    Failed to load interface for ‛N’
     Use -v to see a list of the files searched for.
diff --git a/tests/module/mod10.stderr b/tests/module/mod10.stderr
index 5369fa0f8..6cc2caf59 100644
--- a/tests/module/mod10.stderr
+++ b/tests/module/mod10.stderr
@@ -1,2 +1,2 @@
 
-mod10.hs:2:10: Not in scope: type constructor or class `T'
+mod10.hs:2:10: Not in scope: type constructor or class ‛T’
diff --git a/tests/module/mod101.stderr b/tests/module/mod101.stderr
index 662c38e89..306884fa8 100644
--- a/tests/module/mod101.stderr
+++ b/tests/module/mod101.stderr
@@ -1,4 +1,4 @@
 
 mod101.hs:8:5:
-    Not in scope: data constructor `ConB'
-    Perhaps you meant `ConA' (imported from Mod101_AuxB)
+    Not in scope: data constructor ‛ConB’
+    Perhaps you meant ‛ConA’ (imported from Mod101_AuxB)
diff --git a/tests/module/mod102.stderr b/tests/module/mod102.stderr
index 60f7b28ab..a33246f12 100644
--- a/tests/module/mod102.stderr
+++ b/tests/module/mod102.stderr
@@ -1,4 +1,4 @@
 
 mod102.hs:8:5:
-    Not in scope: `methB'
-    Perhaps you meant `methA' (imported from Mod102_AuxB)
+    Not in scope: ‛methB’
+    Perhaps you meant ‛methA’ (imported from Mod102_AuxB)
diff --git a/tests/module/mod110.stderr b/tests/module/mod110.stderr
index e1c2eb1b0..f394f5621 100644
--- a/tests/module/mod110.stderr
+++ b/tests/module/mod110.stderr
@@ -1,7 +1,7 @@
 
 mod110.hs:11:10:
-    Ambiguous occurrence `Eq'
-    It could refer to either `M.Eq', defined at mod110.hs:7:7
-                          or `Prelude.Eq',
-                             imported from `Prelude' at mod110.hs:4:1-14
-                             (and originally defined in `GHC.Classes')
+    Ambiguous occurrence ‛Eq’
+    It could refer to either ‛M.Eq’, defined at mod110.hs:7:7
+                          or ‛Prelude.Eq’,
+                             imported from ‛Prelude’ at mod110.hs:4:1-14
+                             (and originally defined in ‛GHC.Classes’)
diff --git a/tests/module/mod114.stderr b/tests/module/mod114.stderr
index be7202ce0..84131b47f 100644
--- a/tests/module/mod114.stderr
+++ b/tests/module/mod114.stderr
@@ -1,2 +1,2 @@
 
-mod114.hs:3:16: Not in scope: type constructor or class `Stuff'
+mod114.hs:3:16: Not in scope: type constructor or class ‛Stuff’
diff --git a/tests/module/mod116.stderr b/tests/module/mod116.stderr
index c9fb1ded5..c46059c5d 100644
--- a/tests/module/mod116.stderr
+++ b/tests/module/mod116.stderr
@@ -1,2 +1,2 @@
 
-mod116.hs:2:18: Not in scope: type constructor or class `M2'
+mod116.hs:2:18: Not in scope: type constructor or class ‛M2’
diff --git a/tests/module/mod120.stderr b/tests/module/mod120.stderr
index 0d6181e61..2643f9258 100644
--- a/tests/module/mod120.stderr
+++ b/tests/module/mod120.stderr
@@ -1,2 +1,2 @@
 
-mod120.hs:5:5: Not in scope: data constructor `Foo'
+mod120.hs:5:5: Not in scope: data constructor ‛Foo’
diff --git a/tests/module/mod121.stderr b/tests/module/mod121.stderr
index 7c2cf2cc9..16ea4bf62 100644
--- a/tests/module/mod121.stderr
+++ b/tests/module/mod121.stderr
@@ -1,4 +1,4 @@
 
 mod121.hs:5:5:
-    Not in scope: `m2'
-    Perhaps you meant `m1' (imported from Mod121_A)
+    Not in scope: ‛m2’
+    Perhaps you meant ‛m1’ (imported from Mod121_A)
diff --git a/tests/module/mod122.stderr b/tests/module/mod122.stderr
index b65f8e996..45e4f1699 100644
--- a/tests/module/mod122.stderr
+++ b/tests/module/mod122.stderr
@@ -1,2 +1,2 @@
 
-mod122.hs:5:6: Not in scope: type constructor or class `C'
+mod122.hs:5:6: Not in scope: type constructor or class ‛C’
diff --git a/tests/module/mod123.stderr b/tests/module/mod123.stderr
index 91f75483d..b63145485 100644
--- a/tests/module/mod123.stderr
+++ b/tests/module/mod123.stderr
@@ -1,2 +1,2 @@
 
-mod123.hs:5:6: Not in scope: type constructor or class `T'
+mod123.hs:5:6: Not in scope: type constructor or class ‛T’
diff --git a/tests/module/mod124.stderr b/tests/module/mod124.stderr
index 22644aa07..66cad7ee3 100644
--- a/tests/module/mod124.stderr
+++ b/tests/module/mod124.stderr
@@ -1,2 +1,2 @@
 
-mod124.hs:6:6: Not in scope: type constructor or class `T'
+mod124.hs:6:6: Not in scope: type constructor or class ‛T’
diff --git a/tests/module/mod125.stderr b/tests/module/mod125.stderr
index b2f7fa450..9fa21e787 100644
--- a/tests/module/mod125.stderr
+++ b/tests/module/mod125.stderr
@@ -1,2 +1,2 @@
 
-mod125.hs:7:5: Not in scope: data constructor `T'
+mod125.hs:7:5: Not in scope: data constructor ‛T’
diff --git a/tests/module/mod126.stderr b/tests/module/mod126.stderr
index 22243759c..474e6eb49 100644
--- a/tests/module/mod126.stderr
+++ b/tests/module/mod126.stderr
@@ -1,2 +1,2 @@
 
-mod126.hs:7:5: Not in scope: data constructor `T'
+mod126.hs:7:5: Not in scope: data constructor ‛T’
diff --git a/tests/module/mod127.stderr b/tests/module/mod127.stderr
index 5ffb1b71b..b20850336 100644
--- a/tests/module/mod127.stderr
+++ b/tests/module/mod127.stderr
@@ -1,2 +1,2 @@
 
-mod127.hs:6:6: Not in scope: type constructor or class `T'
+mod127.hs:6:6: Not in scope: type constructor or class ‛T’
diff --git a/tests/module/mod128.stderr-ghc b/tests/module/mod128.stderr-ghc
index 18c786404..4363290fb 100644
--- a/tests/module/mod128.stderr-ghc
+++ b/tests/module/mod128.stderr-ghc
@@ -1,2 +1,2 @@
 
-Mod128_A.hs:2:19: Warning: `T' is exported by `T(Con)' and `T'
+Mod128_A.hs:2:19: Warning: ‛T’ is exported by ‛T(Con)’ and ‛T’
diff --git a/tests/module/mod130.stderr b/tests/module/mod130.stderr
index 27d3f8470..bb1aff176 100644
--- a/tests/module/mod130.stderr
+++ b/tests/module/mod130.stderr
@@ -1,2 +1,2 @@
 
-mod130.hs:7:5: Not in scope: `<'
+mod130.hs:7:5: Not in scope: ‛<’
diff --git a/tests/module/mod131.stderr b/tests/module/mod131.stderr
index 15d919046..2b877aaae 100644
--- a/tests/module/mod131.stderr
+++ b/tests/module/mod131.stderr
@@ -1,9 +1,9 @@
 
 mod131.hs:2:27:
-    Conflicting exports for `f':
-       `module Mod131_B' exports `f'
-         imported from `Mod131_B' at mod131.hs:3:17
+    Conflicting exports for ‛f’:
+       ‛module Mod131_B’ exports ‛f’
+         imported from ‛Mod131_B’ at mod131.hs:3:17
          (and originally defined at Mod131_B.hs:3:1)
-       `Mod131_A.f' exports `Mod131_A.f'
-         imported qualified from `Mod131_A' at mod131.hs:4:27
+       ‛Mod131_A.f’ exports ‛Mod131_A.f’
+         imported qualified from ‛Mod131_A’ at mod131.hs:4:27
          (and originally defined at Mod131_A.hs:3:1)
diff --git a/tests/module/mod132.stderr b/tests/module/mod132.stderr
index 8dbf51014..4afecd8f8 100644
--- a/tests/module/mod132.stderr
+++ b/tests/module/mod132.stderr
@@ -1,2 +1,2 @@
 
-mod132.hs:6:7: Not in scope: data constructor `Foo'
+mod132.hs:6:7: Not in scope: data constructor ‛Foo’
diff --git a/tests/module/mod134.stderr b/tests/module/mod134.stderr
index ed8382db6..3270f93b6 100644
--- a/tests/module/mod134.stderr
+++ b/tests/module/mod134.stderr
@@ -1,7 +1,7 @@
 
 mod134.hs:6:19:
-    Not in scope: `Prelude.head'
+    Not in scope: ‛Prelude.head’
     Perhaps you meant one of these:
-      `Prelude.read' (imported from Prelude),
-      `Prelude.reads' (imported from Prelude),
-      `Prelude.snd' (imported from Prelude)
+      ‛Prelude.read’ (imported from Prelude),
+      ‛Prelude.reads’ (imported from Prelude),
+      ‛Prelude.snd’ (imported from Prelude)
diff --git a/tests/module/mod136.stderr b/tests/module/mod136.stderr
index 242d20b3d..2a0feed97 100644
--- a/tests/module/mod136.stderr
+++ b/tests/module/mod136.stderr
@@ -1,6 +1,6 @@
 
 mod136.hs:6:5:
-    Not in scope: `zipWith5'
+    Not in scope: ‛zipWith5’
     Perhaps you meant one of these:
-      `zipWith' (imported from Mod136_A),
-      `zipWith3' (imported from Mod136_A)
+      ‛zipWith’ (imported from Mod136_A),
+      ‛zipWith3’ (imported from Mod136_A)
diff --git a/tests/module/mod138.stderr b/tests/module/mod138.stderr
index 2e8a5190d..5b006ee32 100644
--- a/tests/module/mod138.stderr
+++ b/tests/module/mod138.stderr
@@ -1,2 +1,2 @@
 
-mod138.hs:7:5: Not in scope: `isLatin1'
+mod138.hs:7:5: Not in scope: ‛isLatin1’
diff --git a/tests/module/mod14.stderr-ghc b/tests/module/mod14.stderr-ghc
index be838c388..9eec91d71 100644
--- a/tests/module/mod14.stderr-ghc
+++ b/tests/module/mod14.stderr-ghc
@@ -1,4 +1,3 @@
 
-mod14.hs:2:10:
-    Warning: `m2' is exported by `C(m1, m2, m2, m3)' and `C(m1, m2, m2,
-                                                            m3)'
+mod14.hs:2:10: Warning:
+    ‛m2’ is exported by ‛C(m1, m2, m2, m3)’ and ‛C(m1, m2, m2, m3)’
diff --git a/tests/module/mod142.stderr b/tests/module/mod142.stderr
index fcd7665aa..f31723d02 100644
--- a/tests/module/mod142.stderr
+++ b/tests/module/mod142.stderr
@@ -1,7 +1,7 @@
 
 mod142.hs:2:21:
-    Conflicting exports for `x':
-       `module Mod142_A' exports `Mod142_A.x'
-         imported from `Mod142_A' at mod142.hs:4:1-15
+    Conflicting exports for ‛x’:
+       ‛module Mod142_A’ exports ‛Mod142_A.x’
+         imported from ‛Mod142_A’ at mod142.hs:4:1-15
          (and originally defined at Mod142_A.hs:3:1)
-       `module M' exports `M.x' defined at mod142.hs:6:1
+       ‛module M’ exports ‛M.x’ defined at mod142.hs:6:1
diff --git a/tests/module/mod143.stderr b/tests/module/mod143.stderr
index 15042a21d..cdec14c83 100644
--- a/tests/module/mod143.stderr
+++ b/tests/module/mod143.stderr
@@ -1,7 +1,7 @@
 
 mod143.hs:2:21:
-    Conflicting exports for `Foo':
-       `module Mod143_A' exports `Mod143_A.Foo'
-         imported from `Mod143_A' at mod143.hs:4:1-15
+    Conflicting exports for ‛Foo’:
+       ‛module Mod143_A’ exports ‛Mod143_A.Foo’
+         imported from ‛Mod143_A’ at mod143.hs:4:1-15
          (and originally defined at Mod143_A.hs:3:6-8)
-       `module M' exports `M.Foo' defined at mod143.hs:6:6
+       ‛module M’ exports ‛M.Foo’ defined at mod143.hs:6:6
diff --git a/tests/module/mod144.stderr b/tests/module/mod144.stderr
index 87c49abde..9742a7611 100644
--- a/tests/module/mod144.stderr
+++ b/tests/module/mod144.stderr
@@ -1,7 +1,7 @@
 
 mod144.hs:2:27:
-    Conflicting exports for `Bar':
-       `module Mod144_A' exports `Mod144_A.Bar'
-         imported from `Mod144_A' at mod144.hs:4:1-15
-       `module M' exports `M.Bar' defined at mod144.hs:6:13
+    Conflicting exports for ‛Bar’:
+       ‛module Mod144_A’ exports ‛Mod144_A.Bar’
+         imported from ‛Mod144_A’ at mod144.hs:4:1-15
+       ‛module M’ exports ‛M.Bar’ defined at mod144.hs:6:13
 exit(1)
diff --git a/tests/module/mod145.stderr b/tests/module/mod145.stderr
index fcbf0b673..37109b395 100644
--- a/tests/module/mod145.stderr
+++ b/tests/module/mod145.stderr
@@ -1,7 +1,7 @@
 
 mod145.hs:2:30:
-    Conflicting exports for `m1':
-       `module Mod145_A' exports `Mod145_A.m1'
-         imported from `Mod145_A' at mod145.hs:4:1-15
+    Conflicting exports for ‛m1’:
+       ‛module Mod145_A’ exports ‛Mod145_A.m1’
+         imported from ‛Mod145_A’ at mod145.hs:4:1-15
          (and originally defined at Mod145_A.hs:4:3-4)
-       `module Mod145' exports `Mod145.m1' defined at mod145.hs:7:3
+       ‛module Mod145’ exports ‛Mod145.m1’ defined at mod145.hs:7:3
diff --git a/tests/module/mod146.stderr b/tests/module/mod146.stderr
index ef99dc3ca..160c76c11 100644
--- a/tests/module/mod146.stderr
+++ b/tests/module/mod146.stderr
@@ -1,7 +1,7 @@
 
 mod146.hs:2:30:
-    Conflicting exports for `m1':
-       `module Mod145_A' exports `Mod145_A.m1'
-         imported from `Mod145_A' at mod146.hs:4:1-15
-       `module Mod146' exports `Mod146.m1' defined at mod146.hs:7:3
+    Conflicting exports for ‛m1’:
+       ‛module Mod145_A’ exports ‛Mod145_A.m1’
+         imported from ‛Mod145_A’ at mod146.hs:4:1-15
+       ‛module Mod146’ exports ‛Mod146.m1’ defined at mod146.hs:7:3
 exit(1)
diff --git a/tests/module/mod147.stderr b/tests/module/mod147.stderr
index b3bbf7661..f57f2d8ad 100644
--- a/tests/module/mod147.stderr
+++ b/tests/module/mod147.stderr
@@ -1,2 +1,2 @@
 
-mod147.hs:6:5: Not in scope: data constructor `D'
+mod147.hs:6:5: Not in scope: data constructor ‛D’
diff --git a/tests/module/mod150.stderr b/tests/module/mod150.stderr
index 8ddd68694..e1748d772 100644
--- a/tests/module/mod150.stderr
+++ b/tests/module/mod150.stderr
@@ -1,7 +1,7 @@
 
 mod150.hs:2:20:
-    Conflicting exports for `id':
-       `module Prelude' exports `Prelude.id'
-         imported from `Prelude' at mod150.hs:2:8
-         (and originally defined in `GHC.Base')
-       `module M' exports `M.id' defined at mod150.hs:2:42
+    Conflicting exports for ‛id’:
+       ‛module Prelude’ exports ‛Prelude.id’
+         imported from ‛Prelude’ at mod150.hs:2:8
+         (and originally defined in ‛GHC.Base’)
+       ‛module M’ exports ‛M.id’ defined at mod150.hs:2:42
diff --git a/tests/module/mod151.stderr b/tests/module/mod151.stderr
index 3206da9de..505fdb8c4 100644
--- a/tests/module/mod151.stderr
+++ b/tests/module/mod151.stderr
@@ -1,7 +1,7 @@
 
 mod151.hs:2:20:
-    Ambiguous occurrence `id'
-    It could refer to either `M.id', defined at mod151.hs:2:30
-                          or `Prelude.id',
-                             imported from `Prelude' at mod151.hs:2:8
-                             (and originally defined in `GHC.Base')
+    Ambiguous occurrence ‛id’
+    It could refer to either ‛M.id’, defined at mod151.hs:2:30
+                          or ‛Prelude.id’,
+                             imported from ‛Prelude’ at mod151.hs:2:8
+                             (and originally defined in ‛GHC.Base’)
diff --git a/tests/module/mod152.stderr b/tests/module/mod152.stderr
index 1ad302287..e385e1e6e 100644
--- a/tests/module/mod152.stderr
+++ b/tests/module/mod152.stderr
@@ -1,14 +1,14 @@
 
 mod152.hs:2:26:
-    Ambiguous occurrence `id'
-    It could refer to either `M.id', defined at mod152.hs:2:36
-                          or `Prelude.id',
-                             imported from `Prelude' at mod152.hs:2:8
-                             (and originally defined in `GHC.Base')
+    Ambiguous occurrence ‛id’
+    It could refer to either ‛M.id’, defined at mod152.hs:2:36
+                          or ‛Prelude.id’,
+                             imported from ‛Prelude’ at mod152.hs:2:8
+                             (and originally defined in ‛GHC.Base’)
 
 mod152.hs:2:26:
-    Conflicting exports for `id':
-       `module Prelude' exports `Prelude.id'
-         imported from `Prelude' at mod152.hs:2:8
-         (and originally defined in `GHC.Base')
-       `id' exports `M.id' defined at mod152.hs:2:36
+    Conflicting exports for ‛id’:
+       ‛module Prelude’ exports ‛Prelude.id’
+         imported from ‛Prelude’ at mod152.hs:2:8
+         (and originally defined in ‛GHC.Base’)
+       ‛id’ exports ‛M.id’ defined at mod152.hs:2:36
diff --git a/tests/module/mod153.stderr b/tests/module/mod153.stderr
index da4751b7b..79532da84 100644
--- a/tests/module/mod153.stderr
+++ b/tests/module/mod153.stderr
@@ -1,7 +1,7 @@
 
 mod153.hs:2:11:
-    Ambiguous occurrence `id'
-    It could refer to either `M.id', defined at mod153.hs:2:21
-                          or `Prelude.id',
-                             imported from `Prelude' at mod153.hs:2:8
-                             (and originally defined in `GHC.Base')
+    Ambiguous occurrence ‛id’
+    It could refer to either ‛M.id’, defined at mod153.hs:2:21
+                          or ‛Prelude.id’,
+                             imported from ‛Prelude’ at mod153.hs:2:8
+                             (and originally defined in ‛GHC.Base’)
diff --git a/tests/module/mod155.stderr b/tests/module/mod155.stderr
index 889e9772c..8c0266297 100644
--- a/tests/module/mod155.stderr
+++ b/tests/module/mod155.stderr
@@ -1,7 +1,7 @@
 
 mod155.hs:2:10:
-    Conflicting exports for `id':
-       `module M' exports `M.id'
-         imported from `Prelude' at mod155.hs:4:1-19
-         (and originally defined in `GHC.Base')
-       `module M' exports `M.id' defined at mod155.hs:5:1
+    Conflicting exports for ‛id’:
+       ‛module M’ exports ‛M.id’
+         imported from ‛Prelude’ at mod155.hs:4:1-19
+         (and originally defined in ‛GHC.Base’)
+       ‛module M’ exports ‛M.id’ defined at mod155.hs:5:1
diff --git a/tests/module/mod158.stderr b/tests/module/mod158.stderr
index 7f6c7d7e8..412c05c1b 100644
--- a/tests/module/mod158.stderr
+++ b/tests/module/mod158.stderr
@@ -1,3 +1,3 @@
 
-mod158.hs:12:5: Not in scope: data constructor `C'
+mod158.hs:12:5: Not in scope: data constructor ‛C’
 exit(1)
diff --git a/tests/module/mod160.stderr b/tests/module/mod160.stderr
index c2dbd5647..1a27420f6 100644
--- a/tests/module/mod160.stderr
+++ b/tests/module/mod160.stderr
@@ -1,6 +1,6 @@
 
 mod160.hs:12:5:
-    Not in scope: `m3'
+    Not in scope: ‛m3’
     Perhaps you meant one of these:
-      `m1' (imported from Mod159_D), `m2' (imported from Mod159_D)
+      ‛m1’ (imported from Mod159_D), ‛m2’ (imported from Mod159_D)
 exit(1)
diff --git a/tests/module/mod161.stderr b/tests/module/mod161.stderr
index 1272093ea..f5dc9fd37 100644
--- a/tests/module/mod161.stderr
+++ b/tests/module/mod161.stderr
@@ -1,2 +1,2 @@
 
-mod161.hs:2:12: Not in scope: `bar'
+mod161.hs:2:12: Not in scope: ‛bar’
diff --git a/tests/module/mod164.stderr b/tests/module/mod164.stderr
index 5f18adc02..e6ebc70bc 100644
--- a/tests/module/mod164.stderr
+++ b/tests/module/mod164.stderr
@@ -1,9 +1,9 @@
 
 mod164.hs:9:5:
-    Ambiguous occurrence `D1'
-    It could refer to either `Mod164_A.D1',
-                             imported from `Mod164_A' at mod164.hs:4:1-15
+    Ambiguous occurrence ‛D1’
+    It could refer to either ‛Mod164_A.D1’,
+                             imported from ‛Mod164_A’ at mod164.hs:4:1-15
                              (and originally defined at Mod164_A.hs:3:10-11)
-                          or `Mod164_B.D1',
-                             imported from `Mod164_B' at mod164.hs:5:1-15
+                          or ‛Mod164_B.D1’,
+                             imported from ‛Mod164_B’ at mod164.hs:5:1-15
                              (and originally defined at Mod164_B.hs:3:10-11)
diff --git a/tests/module/mod165.stderr b/tests/module/mod165.stderr
index 293eb993c..334ad0c7f 100644
--- a/tests/module/mod165.stderr
+++ b/tests/module/mod165.stderr
@@ -1,7 +1,7 @@
 
 mod165.hs:9:5:
-    Ambiguous occurrence `A.D1'
-    It could refer to either `A.D1',
-                             imported from `Mod164_A' at mod165.hs:4:1-20
-                          or `A.D1', imported from `Mod164_B' at mod165.hs:5:1-20
+    Ambiguous occurrence ‛A.D1’
+    It could refer to either ‛A.D1’,
+                             imported from ‛Mod164_A’ at mod165.hs:4:1-20
+                          or ‛A.D1’, imported from ‛Mod164_B’ at mod165.hs:5:1-20
 exit(1)
diff --git a/tests/module/mod17.stderr b/tests/module/mod17.stderr
index 119263796..3a911609d 100644
--- a/tests/module/mod17.stderr
+++ b/tests/module/mod17.stderr
@@ -1,4 +1,4 @@
 
 mod17.hs:2:10:
-    The export item `C(m1, m2, m3, Left)'
+    The export item ‛C(m1, m2, m3, Left)’
     attempts to export constructors or class methods that are not visible here
diff --git a/tests/module/mod174.stderr b/tests/module/mod174.stderr
index 6ef2e753d..020f94208 100644
--- a/tests/module/mod174.stderr
+++ b/tests/module/mod174.stderr
@@ -1,3 +1,3 @@
 
 mod174.hs:1:1:
-    The main function `main' is not exported by module `Main'
+    The main function ‛main’ is not exported by module ‛Main’
diff --git a/tests/module/mod176.stderr b/tests/module/mod176.stderr
index 7301324a9..4dcd689a8 100644
--- a/tests/module/mod176.stderr
+++ b/tests/module/mod176.stderr
@@ -1,4 +1,4 @@
 
-mod176.hs:4:1:
-    Warning: The import of `return, Monad'
-             from module `Control.Monad' is redundant
+mod176.hs:4:1: Warning:
+    The import of ‛return, Monad’
+    from module ‛Control.Monad’ is redundant
diff --git a/tests/module/mod177.stderr b/tests/module/mod177.stderr
index 1dc7c5c6a..fe82c6456 100644
--- a/tests/module/mod177.stderr
+++ b/tests/module/mod177.stderr
@@ -1,5 +1,5 @@
 
-mod177.hs:4:1:
-    Warning: The import of `Data.Maybe' is redundant
-               except perhaps to import instances from `Data.Maybe'
-             To import instances alone, use: import Data.Maybe()
+mod177.hs:4:1: Warning:
+    The import of ‛Data.Maybe’ is redundant
+      except perhaps to import instances from ‛Data.Maybe’
+    To import instances alone, use: import Data.Maybe()
diff --git a/tests/module/mod178.stderr b/tests/module/mod178.stderr
index 3edd9a406..755324b58 100644
--- a/tests/module/mod178.stderr
+++ b/tests/module/mod178.stderr
@@ -1,5 +1,5 @@
 
 Mod178_2.hs:1:1:
     File name does not match module name:
-    Saw: `Main'
-    Expected: `Mod178_2'
+    Saw: ‛Main’
+    Expected: ‛Mod178_2’
diff --git a/tests/module/mod18.stderr b/tests/module/mod18.stderr
index 5f8ba3457..1ef381f90 100644
--- a/tests/module/mod18.stderr
+++ b/tests/module/mod18.stderr
@@ -1,5 +1,5 @@
 
 mod18.hs:3:6:
-    Multiple declarations of `T'
+    Multiple declarations of ‛T’
     Declared at: mod18.hs:2:6
                  mod18.hs:3:6
diff --git a/tests/module/mod180.stderr b/tests/module/mod180.stderr
index 2790d92a3..2647f2ada 100644
--- a/tests/module/mod180.stderr
+++ b/tests/module/mod180.stderr
@@ -1,5 +1,5 @@
 
 mod180.hs:8:5:
-    Couldn't match expected type `T' with actual type `main:Mod180_A.T'
+    Couldn't match expected type ‛T’ with actual type ‛main:Mod180_A.T’
     In the expression: x
-    In an equation for `z': z = x
+    In an equation for ‛z’: z = x
diff --git a/tests/module/mod19.stderr b/tests/module/mod19.stderr
index 9178ceba4..fd2f5f319 100644
--- a/tests/module/mod19.stderr
+++ b/tests/module/mod19.stderr
@@ -1,10 +1,10 @@
 
 mod19.hs:3:7:
-    Multiple declarations of `C'
+    Multiple declarations of ‛C’
     Declared at: mod19.hs:2:7
                  mod19.hs:3:7
 
 mod19.hs:3:17:
-    Multiple declarations of `m'
+    Multiple declarations of ‛m’
     Declared at: mod19.hs:2:17
                  mod19.hs:3:17
diff --git a/tests/module/mod2.stderr b/tests/module/mod2.stderr
index e928ab3b1..c98e3f5ce 100644
--- a/tests/module/mod2.stderr
+++ b/tests/module/mod2.stderr
@@ -1,4 +1,4 @@
 
 mod2.hs:3:1:
-    Failed to load interface for `N'
+    Failed to load interface for ‛N’
     Use -v to see a list of the files searched for.
diff --git a/tests/module/mod20.stderr b/tests/module/mod20.stderr
index 123564201..eb92e4a02 100644
--- a/tests/module/mod20.stderr
+++ b/tests/module/mod20.stderr
@@ -1,5 +1,5 @@
 
 mod20.hs:3:18:
-    Multiple declarations of `m'
+    Multiple declarations of ‛m’
     Declared at: mod20.hs:2:18
                  mod20.hs:3:18
diff --git a/tests/module/mod21.stderr b/tests/module/mod21.stderr
index b5a86c074..34620a6bd 100644
--- a/tests/module/mod21.stderr
+++ b/tests/module/mod21.stderr
@@ -1,5 +1,5 @@
 
 mod21.hs:3:6:
-    Multiple declarations of `T'
+    Multiple declarations of ‛T’
     Declared at: mod21.hs:2:6
                  mod21.hs:3:6
diff --git a/tests/module/mod22.stderr b/tests/module/mod22.stderr
index 786043d4f..0e0580936 100644
--- a/tests/module/mod22.stderr
+++ b/tests/module/mod22.stderr
@@ -1,5 +1,5 @@
 
 mod22.hs:3:11:
-    Multiple declarations of `K'
+    Multiple declarations of ‛K’
     Declared at: mod22.hs:2:11
                  mod22.hs:3:11
diff --git a/tests/module/mod23.stderr b/tests/module/mod23.stderr
index 3085cfff3..77f37d3c2 100644
--- a/tests/module/mod23.stderr
+++ b/tests/module/mod23.stderr
@@ -1,5 +1,5 @@
 
 mod23.hs:3:8:
-    Conflicting definitions for `a'
+    Conflicting definitions for ‛a’
     Bound at: mod23.hs:3:8
               mod23.hs:3:10
diff --git a/tests/module/mod24.stderr b/tests/module/mod24.stderr
index 12ed89e59..9f2bb5479 100644
--- a/tests/module/mod24.stderr
+++ b/tests/module/mod24.stderr
@@ -1,5 +1,5 @@
 
 mod24.hs:3:8:
-    Conflicting definitions for `a'
+    Conflicting definitions for ‛a’
     Bound at: mod24.hs:3:8
               mod24.hs:3:10
diff --git a/tests/module/mod25.stderr b/tests/module/mod25.stderr
index 49a15454a..6d8fd0349 100644
--- a/tests/module/mod25.stderr
+++ b/tests/module/mod25.stderr
@@ -1,2 +1,2 @@
 
-mod25.hs:3:16: Not in scope: type variable `b'
+mod25.hs:3:16: Not in scope: type variable ‛b’
diff --git a/tests/module/mod26.stderr b/tests/module/mod26.stderr
index 914f879d6..0ee82dc57 100644
--- a/tests/module/mod26.stderr
+++ b/tests/module/mod26.stderr
@@ -1,2 +1,2 @@
 
-mod26.hs:3:21: Not in scope: type variable `b'
+mod26.hs:3:21: Not in scope: type variable ‛b’
diff --git a/tests/module/mod29.stderr b/tests/module/mod29.stderr
index ba62a734f..2abdd7d1d 100644
--- a/tests/module/mod29.stderr
+++ b/tests/module/mod29.stderr
@@ -1,2 +1,2 @@
 
-mod29.hs:6:12: Not in scope: type constructor or class `Char'
+mod29.hs:6:12: Not in scope: type constructor or class ‛Char’
diff --git a/tests/module/mod3.stderr b/tests/module/mod3.stderr
index 2b0cae95f..f07a431b4 100644
--- a/tests/module/mod3.stderr
+++ b/tests/module/mod3.stderr
@@ -1,4 +1,4 @@
 
 mod3.hs:2:10:
-    The export item `T(K1)'
+    The export item ‛T(K1)’
     attempts to export constructors or class methods that are not visible here
diff --git a/tests/module/mod36.stderr b/tests/module/mod36.stderr
index 9d6b97bfa..6ec42d92b 100644
--- a/tests/module/mod36.stderr
+++ b/tests/module/mod36.stderr
@@ -1,2 +1,2 @@
 
-mod36.hs:5:5: Not in scope: `const'
+mod36.hs:5:5: Not in scope: ‛const’
diff --git a/tests/module/mod38.stderr b/tests/module/mod38.stderr
index b04dd77f4..7c5f27704 100644
--- a/tests/module/mod38.stderr
+++ b/tests/module/mod38.stderr
@@ -1,5 +1,5 @@
 
 mod38.hs:4:7:
-    Multiple declarations of `C'
+    Multiple declarations of ‛C’
     Declared at: mod38.hs:3:6
                  mod38.hs:4:7
diff --git a/tests/module/mod4.stderr b/tests/module/mod4.stderr
index 84d7cfa19..38ea462fd 100644
--- a/tests/module/mod4.stderr
+++ b/tests/module/mod4.stderr
@@ -1,4 +1,4 @@
 
 mod4.hs:2:10:
-    The export item `T(K1, K2)'
+    The export item ‛T(K1, K2)’
     attempts to export constructors or class methods that are not visible here
diff --git a/tests/module/mod40.stderr b/tests/module/mod40.stderr
index ed77e80f8..aa641e4d8 100644
--- a/tests/module/mod40.stderr
+++ b/tests/module/mod40.stderr
@@ -1,8 +1,8 @@
 
 mod40.hs:3:1:
     Cycle in class declaration (via superclasses): C1 -> C2 -> C1
-    In the class declaration for `C1'
+    In the class declaration for ‛C1’
 
 mod40.hs:4:1:
     Cycle in class declaration (via superclasses): C2 -> C1 -> C2
-    In the class declaration for `C2'
+    In the class declaration for ‛C2’
diff --git a/tests/module/mod41.stderr b/tests/module/mod41.stderr
index 5ec4355fb..921fc9594 100644
--- a/tests/module/mod41.stderr
+++ b/tests/module/mod41.stderr
@@ -1,8 +1,8 @@
 
 mod41.hs:3:18:
-    Illegal instance declaration for `Eq (Either a a)'
+    Illegal instance declaration for ‛Eq (Either a a)’
       (All instance types must be of the form (T a1 ... an)
        where a1 ... an are *distinct type variables*,
        and each type variable appears at most once in the instance head.
        Use -XFlexibleInstances if you want to disable this.)
-    In the instance declaration for `Eq (Either a a)'
+    In the instance declaration for ‛Eq (Either a a)’
diff --git a/tests/module/mod42.stderr b/tests/module/mod42.stderr
index 319f42ba0..8fd553feb 100644
--- a/tests/module/mod42.stderr
+++ b/tests/module/mod42.stderr
@@ -1,8 +1,8 @@
 
 mod42.hs:3:10:
-    Illegal instance declaration for `Eq a'
+    Illegal instance declaration for ‛Eq a’
       (All instance types must be of the form (T a1 ... an)
        where a1 ... an are *distinct type variables*,
        and each type variable appears at most once in the instance head.
        Use -XFlexibleInstances if you want to disable this.)
-    In the instance declaration for `Eq a'
+    In the instance declaration for ‛Eq a’
diff --git a/tests/module/mod43.stderr b/tests/module/mod43.stderr
index 7fc4da0b8..5630a4ae5 100644
--- a/tests/module/mod43.stderr
+++ b/tests/module/mod43.stderr
@@ -1,7 +1,7 @@
 
 mod43.hs:3:10:
-    Illegal instance declaration for `Eq String'
-        (All instance types must be of the form (T t1 ... tn)
-         where T is not a synonym.
-         Use -XTypeSynonymInstances if you want to disable this.)
-    In the instance declaration for `Eq String'
+    Illegal instance declaration for ‛Eq String’
+      (All instance types must be of the form (T t1 ... tn)
+       where T is not a synonym.
+       Use -XTypeSynonymInstances if you want to disable this.)
+    In the instance declaration for ‛Eq String’
diff --git a/tests/module/mod45.stderr b/tests/module/mod45.stderr
index 8aadf22b1..2673763cb 100644
--- a/tests/module/mod45.stderr
+++ b/tests/module/mod45.stderr
@@ -3,4 +3,4 @@ mod45.hs:5:11:
     Illegal type signature in instance declaration:
       (==) :: T -> T -> Bool
     (Use -XInstanceSigs to allow this)
-    In the instance declaration for `Eq T'
+    In the instance declaration for ‛Eq T’
diff --git a/tests/module/mod46.stderr b/tests/module/mod46.stderr
index c4c820326..516215c67 100644
--- a/tests/module/mod46.stderr
+++ b/tests/module/mod46.stderr
@@ -2,4 +2,4 @@
 mod46.hs:4:10:
     No instance for (Eq T)
       arising from the superclasses of an instance declaration
-    In the instance declaration for `Ord T'
+    In the instance declaration for ‛Ord T’
diff --git a/tests/module/mod47.stderr b/tests/module/mod47.stderr
index 1b8fd0b41..44aba9217 100644
--- a/tests/module/mod47.stderr
+++ b/tests/module/mod47.stderr
@@ -6,4 +6,4 @@ mod47.hs:6:10:
       bound by the instance declaration at mod47.hs:6:10-34
     Possible fix:
       add (Num a) to the context of the instance declaration
-    In the instance declaration for `Bar [a]'
+    In the instance declaration for ‛Bar [a]’
diff --git a/tests/module/mod49.stderr b/tests/module/mod49.stderr
index f08b36e0c..f0fca3e7a 100644
--- a/tests/module/mod49.stderr
+++ b/tests/module/mod49.stderr
@@ -1,2 +1,2 @@
 
-mod49.hs:5:3: `y' is not a (visible) method of class `C'
+mod49.hs:5:3: ‛y’ is not a (visible) method of class ‛C’
diff --git a/tests/module/mod5.stderr-ghc b/tests/module/mod5.stderr-ghc
index 7992560ca..b48307ab3 100644
--- a/tests/module/mod5.stderr-ghc
+++ b/tests/module/mod5.stderr-ghc
@@ -1,3 +1,3 @@
 
-mod5.hs:2:10:
-    Warning: `K1' is exported by `T(K1, K1)' and `T(K1, K1)'
+mod5.hs:2:10: Warning:
+    ‛K1’ is exported by ‛T(K1, K1)’ and ‛T(K1, K1)’
diff --git a/tests/module/mod50.stderr b/tests/module/mod50.stderr
index 9357f7a2d..453f2f2da 100644
--- a/tests/module/mod50.stderr
+++ b/tests/module/mod50.stderr
@@ -1,2 +1,2 @@
 
-mod50.hs:3:22: Not in scope: type constructor or class `Foo'
+mod50.hs:3:22: Not in scope: type constructor or class ‛Foo’
diff --git a/tests/module/mod53.stderr b/tests/module/mod53.stderr
index 2e142a5bf..4129d3995 100644
--- a/tests/module/mod53.stderr
+++ b/tests/module/mod53.stderr
@@ -1,5 +1,5 @@
-
-mod53.hs:4:22:
-    Can't make a derived instance of `C T':
-      `C' is not a derivable class
-    In the data declaration for `T'
+
+mod53.hs:4:22:
+    Can't make a derived instance of ‛C T’:
+      ‛C’ is not a derivable class
+    In the data declaration for ‛T’
diff --git a/tests/module/mod55.stderr b/tests/module/mod55.stderr
index 9db5ea55c..a1f388f33 100644
--- a/tests/module/mod55.stderr
+++ b/tests/module/mod55.stderr
@@ -1,6 +1,6 @@
-
-mod55.hs:3:26:
-    Can't make a derived instance of `Enum T':
-      `T' must be an enumeration type
-      (an enumeration consists of one or more nullary, non-GADT constructors)
-    In the data declaration for `T'
+
+mod55.hs:3:26:
+    Can't make a derived instance of ‛Enum T’:
+      ‛T’ must be an enumeration type
+      (an enumeration consists of one or more nullary, non-GADT constructors)
+    In the data declaration for ‛T’
diff --git a/tests/module/mod56.stderr b/tests/module/mod56.stderr
index db194406e..44560cb76 100644
--- a/tests/module/mod56.stderr
+++ b/tests/module/mod56.stderr
@@ -1,8 +1,8 @@
-
-mod56.hs:4:39:
-    Can't make a derived instance of `Ix T':
-      `T' must be an enumeration type
-      (an enumeration consists of one or more nullary, non-GADT constructors)
-        or
-      `T' must have precisely one constructor
-    In the data declaration for `T'
+
+mod56.hs:4:39:
+    Can't make a derived instance of ‛Ix T’:
+      ‛T’ must be an enumeration type
+      (an enumeration consists of one or more nullary, non-GADT constructors)
+        or
+      ‛T’ must have precisely one constructor
+    In the data declaration for ‛T’
diff --git a/tests/module/mod59.stderr b/tests/module/mod59.stderr
index c08db2a55..26e74034c 100644
--- a/tests/module/mod59.stderr
+++ b/tests/module/mod59.stderr
@@ -1,2 +1,2 @@
 
-mod59.hs:3:3: Not in scope: data constructor `K'
+mod59.hs:3:3: Not in scope: data constructor ‛K’
diff --git a/tests/module/mod60.stderr b/tests/module/mod60.stderr
index f363cb933..b25ee48b1 100644
--- a/tests/module/mod60.stderr
+++ b/tests/module/mod60.stderr
@@ -1,5 +1,5 @@
 
 mod60.hs:3:4:
-    Constructor `Left' should have 1 argument, but has been given none
+    Constructor ‛Left’ should have 1 argument, but has been given none
     In the pattern: Left
-    In an equation for `f': f (Left) = error "foo"
+    In an equation for ‛f’: f (Left) = error "foo"
diff --git a/tests/module/mod61.stderr b/tests/module/mod61.stderr
index 3ac493743..e96817f65 100644
--- a/tests/module/mod61.stderr
+++ b/tests/module/mod61.stderr
@@ -1,4 +1,4 @@
 
 mod61.hs:3:11:
     Precedence parsing error
-        cannot mix `==' [infix 4] and `==' [infix 4] in the same infix expression
+        cannot mix ‛==’ [infix 4] and ‛==’ [infix 4] in the same infix expression
diff --git a/tests/module/mod62.stderr b/tests/module/mod62.stderr
index d435dbd6b..cac9a6f32 100644
--- a/tests/module/mod62.stderr
+++ b/tests/module/mod62.stderr
@@ -2,5 +2,5 @@
 mod62.hs:3:9: Qualified name in binding position: M.y
 
 mod62.hs:3:22:
-    Not in scope: `M.y'
-    Perhaps you meant `M.x' (line 3)
+    Not in scope: ‛M.y’
+    Perhaps you meant ‛M.x’ (line 3)
diff --git a/tests/module/mod63.stderr b/tests/module/mod63.stderr
index a4745b2e4..3a6097336 100644
--- a/tests/module/mod63.stderr
+++ b/tests/module/mod63.stderr
@@ -1,5 +1,5 @@
 
 mod63.hs:3:1:
-    Equations for `f' have different numbers of arguments
+    Equations for ‛f’ have different numbers of arguments
       mod63.hs:3:1-8
       mod63.hs:4:1-11
diff --git a/tests/module/mod66.stderr b/tests/module/mod66.stderr
index a1bf5a2af..b5fc83fa5 100644
--- a/tests/module/mod66.stderr
+++ b/tests/module/mod66.stderr
@@ -1,5 +1,5 @@
 
 mod66.hs:5:1:
-    Multiple declarations of `f'
+    Multiple declarations of ‛f’
     Declared at: mod66.hs:3:1
                  mod66.hs:5:1
diff --git a/tests/module/mod67.stderr b/tests/module/mod67.stderr
index 2c2323b83..a46c8ab03 100644
--- a/tests/module/mod67.stderr
+++ b/tests/module/mod67.stderr
@@ -1,3 +1,3 @@
 
 mod67.hs:3:1:
-    The type signature for `f' lacks an accompanying binding
+    The type signature for ‛f’ lacks an accompanying binding
diff --git a/tests/module/mod68.stderr b/tests/module/mod68.stderr
index f8490a06b..0d46be073 100644
--- a/tests/module/mod68.stderr
+++ b/tests/module/mod68.stderr
@@ -1,5 +1,5 @@
-
-mod68.hs:4:1:
-    Duplicate type signatures for `f'
-    at mod68.hs:3:1
-       mod68.hs:4:1
+
+mod68.hs:4:1:
+    Duplicate type signatures for ‛f’
+    at mod68.hs:3:1
+       mod68.hs:4:1
diff --git a/tests/module/mod7.stderr b/tests/module/mod7.stderr
index f9119cd78..5a446d387 100644
--- a/tests/module/mod7.stderr
+++ b/tests/module/mod7.stderr
@@ -1,2 +1,2 @@
 
-mod7.hs:2:10: Not in scope: type constructor or class `T'
+mod7.hs:2:10: Not in scope: type constructor or class ‛T’
diff --git a/tests/module/mod72.stderr b/tests/module/mod72.stderr
index 7f047d802..b3ff8a9b3 100644
--- a/tests/module/mod72.stderr
+++ b/tests/module/mod72.stderr
@@ -1,2 +1,2 @@
 
-mod72.hs:3:7: Not in scope: `g'
+mod72.hs:3:7: Not in scope: ‛g’
diff --git a/tests/module/mod73.stderr b/tests/module/mod73.stderr
index f1234514b..de2397638 100644
--- a/tests/module/mod73.stderr
+++ b/tests/module/mod73.stderr
@@ -1,7 +1,7 @@
 
 mod73.hs:3:7:
-    Not in scope: `Prelude.g'
+    Not in scope: ‛Prelude.g’
     Perhaps you meant one of these:
-      `Prelude.id' (imported from Prelude),
-      `Prelude.log' (imported from Prelude),
-      `Prelude.pi' (imported from Prelude)
+      ‛Prelude.id’ (imported from Prelude),
+      ‛Prelude.log’ (imported from Prelude),
+      ‛Prelude.pi’ (imported from Prelude)
diff --git a/tests/module/mod74.stderr b/tests/module/mod74.stderr
index b4d417bac..89d12d495 100644
--- a/tests/module/mod74.stderr
+++ b/tests/module/mod74.stderr
@@ -1,2 +1,2 @@
 
-mod74.hs:3:7: Not in scope: `N.g'
+mod74.hs:3:7: Not in scope: ‛N.g’
diff --git a/tests/module/mod77.stderr b/tests/module/mod77.stderr
index 0cb4920e3..1d05d71a0 100644
--- a/tests/module/mod77.stderr
+++ b/tests/module/mod77.stderr
@@ -1,3 +1,3 @@
 
 mod77.hs:3:7:
-    The fixity signature for `$$$' lacks an accompanying binding
+    The fixity signature for ‛$$$’ lacks an accompanying binding
diff --git a/tests/module/mod79.stderr b/tests/module/mod79.stderr
index f8a185725..329e47625 100644
--- a/tests/module/mod79.stderr
+++ b/tests/module/mod79.stderr
@@ -1,2 +1,2 @@
 
-mod79.hs:3:16: Module `Prelude' does not export `C'
+mod79.hs:3:16: Module ‛Prelude’ does not export ‛C’
diff --git a/tests/module/mod80.stderr b/tests/module/mod80.stderr
index c56caf0ae..7908ede6e 100644
--- a/tests/module/mod80.stderr
+++ b/tests/module/mod80.stderr
@@ -1,2 +1,2 @@
 
-mod80.hs:3:16: Module `Prelude' does not export `f'
+mod80.hs:3:16: Module ‛Prelude’ does not export ‛f’
diff --git a/tests/module/mod81.stderr b/tests/module/mod81.stderr
index d3f0d5c42..b3c31ddd3 100644
--- a/tests/module/mod81.stderr
+++ b/tests/module/mod81.stderr
@@ -1,3 +1,3 @@
 
 mod81.hs:3:16:
-    Module `Prelude' does not export `Either(Left, Right, Foo)'
+    Module ‛Prelude’ does not export ‛Either(Left, Right, Foo)’
diff --git a/tests/module/mod87.stderr b/tests/module/mod87.stderr
index 1536679aa..99ad6bf35 100644
--- a/tests/module/mod87.stderr
+++ b/tests/module/mod87.stderr
@@ -1,2 +1,2 @@
 
-mod87.hs:4:5: Not in scope: data constructor `Left'
+mod87.hs:4:5: Not in scope: data constructor ‛Left’
diff --git a/tests/module/mod88.stderr b/tests/module/mod88.stderr
index f166c864c..707ad693e 100644
--- a/tests/module/mod88.stderr
+++ b/tests/module/mod88.stderr
@@ -1,2 +1,2 @@
 
-mod88.hs:5:5: Not in scope: data constructor `Prelude.Left'
+mod88.hs:5:5: Not in scope: data constructor ‛Prelude.Left’
diff --git a/tests/module/mod89.stderr b/tests/module/mod89.stderr
index c4eb78e42..653c93a81 100644
--- a/tests/module/mod89.stderr
+++ b/tests/module/mod89.stderr
@@ -1,2 +1,2 @@
 
-mod89.hs:3:16: Module `Prelude' does not export `map(..)'
+mod89.hs:3:16: Module ‛Prelude’ does not export ‛map(..)’
diff --git a/tests/module/mod9.stderr b/tests/module/mod9.stderr
index 19bec80bb..deee729ba 100644
--- a/tests/module/mod9.stderr
+++ b/tests/module/mod9.stderr
@@ -1,2 +1,2 @@
 
-mod9.hs:2:10: Not in scope: type constructor or class `T'
+mod9.hs:2:10: Not in scope: type constructor or class ‛T’
diff --git a/tests/module/mod90.stderr b/tests/module/mod90.stderr
index 7cc0b108e..050b53c02 100644
--- a/tests/module/mod90.stderr
+++ b/tests/module/mod90.stderr
@@ -1,8 +1,8 @@
 
 mod90.hs:3:16:
-    In module `Prelude':
-      `Left' is a data constructor of `Either'
+    In module ‛Prelude’:
+      ‛Left’ is a data constructor of ‛Either’
     To import it use
-      `import' Prelude( Either( Left ) )
+      ‛import’ Prelude( Either( Left ) )
     or
-      `import' Prelude( Either(..) )
+      ‛import’ Prelude( Either(..) )
diff --git a/tests/module/mod91.stderr b/tests/module/mod91.stderr
index 5d7d6e1df..0324f48a0 100644
--- a/tests/module/mod91.stderr
+++ b/tests/module/mod91.stderr
@@ -1,3 +1,3 @@
 
 mod91.hs:3:16:
-    Module `Prelude' does not export `Eq((==), (/=), eq)'
+    Module ‛Prelude’ does not export ‛Eq((==), (/=), eq)’
diff --git a/tests/module/mod97.stderr b/tests/module/mod97.stderr
index fea2306c1..03891bc17 100644
--- a/tests/module/mod97.stderr
+++ b/tests/module/mod97.stderr
@@ -1,2 +1,2 @@
 
-mod97.hs:4:9: Not in scope: `=='
+mod97.hs:4:9: Not in scope: ‛==’
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr
index a08985f88..cc1082c7d 100644
--- a/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr
@@ -1,36 +1,36 @@
 
 overloadedlistsfail01.hs:5:8:
-    No instance for (Show a0) arising from a use of `print'
-    The type variable `a0' is ambiguous
+    No instance for (Show a0) arising from a use of ‛print’
+    The type variable ‛a0’ is ambiguous
     Note: there are several potential instances:
-      instance Show Double -- Defined in `GHC.Float'
-      instance Show Float -- Defined in `GHC.Float'
+      instance Show Double -- Defined in ‛GHC.Float’
+      instance Show Float -- Defined in ‛GHC.Float’
       instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
+        -- Defined in ‛GHC.Real’
       ...plus 23 others
     In the expression: print [1]
-    In an equation for `main': main = 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
+    The type variable ‛a0’ is ambiguous
     Note: there is a potential instance available:
-      instance GHC.Exts.IsList [a] -- Defined in `GHC.Exts'
-    In the first argument of `print', namely `[1]'
+      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]
+    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
+      arising from the literal ‛1’
+    The type variable ‛a0’ is ambiguous
     Note: there are several potential instances:
-      instance Num Double -- Defined in `GHC.Float'
-      instance Num Float -- Defined in `GHC.Float'
+      instance Num Double -- Defined in ‛GHC.Float’
+      instance Num Float -- Defined in ‛GHC.Float’
       instance Integral a => Num (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
+        -- Defined in ‛GHC.Real’
       ...plus three others
     In the expression: 1
-    In the first argument of `print', namely `[1]'
+    In the first argument of ‛print’, namely ‛[1]’
     In the expression: print [1]
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr
index 49e6b9ee9..62f8a0e0b 100644
--- a/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail02.stderr
@@ -3,11 +3,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]
+    In an equation for ‛test’: test = [7]
 
 overloadedlistsfail02.hs:6:9:
     No instance for (Num (GHC.Exts.Item Foo))
-      arising from the literal `7'
+      arising from the literal ‛7’
     In the expression: 7
     In the expression: [7]
-    In an equation for `test': test = [7]
+    In an equation for ‛test’: test = [7]
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail03.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail03.stderr
index 099d79f23..cd8cbff03 100644
--- a/tests/overloadedlists/should_fail/overloadedlistsfail03.stderr
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail03.stderr
@@ -1,9 +1,6 @@
 
 overloadedlistsfail03.hs:3:27:
-    Couldn't match expected type `Char' with actual type `[Char]'
+    Couldn't match expected type ‛Char’ with actual type ‛[Char]’
     In the expression: "b"
-    In the first argument of `length', namely `['a', "b"]'
-    In the first argument of `print', namely `(length ['a', "b"])'
-
-
-
+    In the first argument of ‛length’, namely ‛['a', "b"]’
+    In the first argument of ‛print’, namely ‛(length ['a', "b"])’
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail04.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail04.stderr
index cfa051997..145c6cd1f 100644
--- a/tests/overloadedlists/should_fail/overloadedlistsfail04.stderr
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail04.stderr
@@ -1,12 +1,8 @@
 
 overloadedlistsfail04.hs:3:15:
     No instance for (Enum [Char])
-      arising from the arithmetic sequence `"a" .. "b"'
-    In the first argument of `print', namely
-      `(["a" .. "b"] :: [String])'
+      arising from the arithmetic sequence ‛"a" .. "b"’
+    In the first argument of ‛print’, namely
+      ‛(["a" .. "b"] :: [String])’
     In the expression: print (["a" .. "b"] :: [String])
-    In an equation for `main': main = print (["a" .. "b"] :: [String])
-
-
-
-
+    In an equation for ‛main’: main = print (["a" .. "b"] :: [String])
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail05.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail05.stderr
index 6e4d3dbd0..131294b13 100644
--- a/tests/overloadedlists/should_fail/overloadedlistsfail05.stderr
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail05.stderr
@@ -1,7 +1,7 @@
 
 overloadedlistsfail05.hs:3:29:
-    Couldn't match expected type `Char' with actual type `Int'
+    Couldn't match expected type ‛Char’ with actual type ‛Int’
     In the expression: (10 :: Int)
-    In the first argument of `length', namely `['a' .. (10 :: Int)]'
-    In the first argument of `print', namely
-      `(length ['a' .. (10 :: Int)])'
+    In the first argument of ‛length’, namely ‛['a' .. (10 :: Int)]’
+    In the first argument of ‛print’, namely
+      ‛(length ['a' .. (10 :: Int)])’
diff --git a/tests/overloadedlists/should_fail/overloadedlistsfail06.stderr b/tests/overloadedlists/should_fail/overloadedlistsfail06.stderr
index 2cd0c3fa1..239465670 100644
--- a/tests/overloadedlists/should_fail/overloadedlistsfail06.stderr
+++ b/tests/overloadedlists/should_fail/overloadedlistsfail06.stderr
@@ -1,7 +1,4 @@
 
-overloadedlistsfail06.hs:3:3:
-    Not in scope: `toList'
-
-overloadedlistsfail06.hs:3:8:
-    Not in scope: `fromListN'
+overloadedlistsfail06.hs:3:3: Not in scope: ‛toList’
 
+overloadedlistsfail06.hs:3:8: Not in scope: ‛fromListN’
diff --git a/tests/parser/should_compile/T2245.stderr b/tests/parser/should_compile/T2245.stderr
index 527957a93..edfa53333 100644
--- a/tests/parser/should_compile/T2245.stderr
+++ b/tests/parser/should_compile/T2245.stderr
@@ -1,34 +1,34 @@
 
-T2245.hs:4:10:
-    Warning: No explicit method or default declaration for `+'
-    In the instance declaration for `Num T'
+T2245.hs:4:10: Warning:
+    No explicit method or default declaration for ‛+’
+    In the instance declaration for ‛Num T’
 
-T2245.hs:4:10:
-    Warning: No explicit method or default declaration for `*'
-    In the instance declaration for `Num T'
+T2245.hs:4:10: Warning:
+    No explicit method or default declaration for ‛*’
+    In the instance declaration for ‛Num T’
 
-T2245.hs:4:10:
-    Warning: No explicit method or default declaration for `abs'
-    In the instance declaration for `Num T'
+T2245.hs:4:10: Warning:
+    No explicit method or default declaration for ‛abs’
+    In the instance declaration for ‛Num T’
 
-T2245.hs:4:10:
-    Warning: No explicit method or default declaration for `signum'
-    In the instance declaration for `Num T'
+T2245.hs:4:10: Warning:
+    No explicit method or default declaration for ‛signum’
+    In the instance declaration for ‛Num T’
 
-T2245.hs:4:10:
-    Warning: No explicit method or default declaration for `fromInteger'
-    In the instance declaration for `Num T'
+T2245.hs:4:10: Warning:
+    No explicit method or default declaration for ‛fromInteger’
+    In the instance declaration for ‛Num T’
 
-T2245.hs:5:10:
-    Warning: No explicit method or default declaration for `fromRational'
-    In the instance declaration for `Fractional T'
+T2245.hs:5:10: Warning:
+    No explicit method or default declaration for ‛fromRational’
+    In the instance declaration for ‛Fractional T’
 
-T2245.hs:7:29:
-    Warning: Defaulting the following constraint(s) to type `T'
-               (Fractional b0)
-                 arising from the literal `1e400' at T2245.hs:7:29-33
-               (Ord b0) arising from a use of `<' at T2245.hs:7:27
-               (Read b0) arising from a use of `read' at T2245.hs:7:38-41
-    In the second argument of `(<)', namely `1e400'
-    In the first argument of `(.)', namely `(< 1e400)'
-    In the second argument of `(.)', namely `(< 1e400) . read'
+T2245.hs:7:29: Warning:
+    Defaulting the following constraint(s) to type ‛T’
+      (Fractional b0)
+        arising from the literal ‛1e400’ at T2245.hs:7:29-33
+      (Ord b0) arising from a use of ‛<’ at T2245.hs:7:27
+      (Read b0) arising from a use of ‛read’ at T2245.hs:7:38-41
+    In the second argument of ‛(<)’, namely ‛1e400’
+    In the first argument of ‛(.)’, namely ‛(< 1e400)’
+    In the second argument of ‛(.)’, namely ‛(< 1e400) . read’
diff --git a/tests/parser/should_compile/T3303.stderr b/tests/parser/should_compile/T3303.stderr
index c2ae0c60f..685448f2c 100644
--- a/tests/parser/should_compile/T3303.stderr
+++ b/tests/parser/should_compile/T3303.stderr
@@ -1,6 +1,6 @@
 
 T3303.hs:7:7: Warning:
-    In the use of `foo' (imported from T3303A):
+    In the use of ‛foo’ (imported from T3303A):
     Deprecated: "This is a multi-line
                  deprecation message
                  for foo"
diff --git a/tests/parser/should_compile/read014.stderr-ghc b/tests/parser/should_compile/read014.stderr-ghc
index b1d9b8125..9b49aaf56 100644
--- a/tests/parser/should_compile/read014.stderr-ghc
+++ b/tests/parser/should_compile/read014.stderr-ghc
@@ -1,28 +1,28 @@
 
-read014.hs:4:1:
-    Warning: Top-level binding with no type signature:
-               ng1 :: forall t a. Num a => t -> a -> a
+read014.hs:4:1: Warning:
+    Top-level binding with no type signature:
+      ng1 :: forall t a. Num a => t -> a -> a
 
-read014.hs:4:5: Warning: Defined but not used: `x'
+read014.hs:4:5: Warning: Defined but not used: ‛x’
 
-read014.hs:6:10:
-    Warning: No explicit method or default declaration for `+'
-    In the instance declaration for `Num (a, b)'
+read014.hs:6:10: Warning:
+    No explicit method or default declaration for ‛+’
+    In the instance declaration for ‛Num (a, b)’
 
-read014.hs:6:10:
-    Warning: No explicit method or default declaration for `*'
-    In the instance declaration for `Num (a, b)'
+read014.hs:6:10: Warning:
+    No explicit method or default declaration for ‛*’
+    In the instance declaration for ‛Num (a, b)’
 
-read014.hs:6:10:
-    Warning: No explicit method or default declaration for `abs'
-    In the instance declaration for `Num (a, b)'
+read014.hs:6:10: Warning:
+    No explicit method or default declaration for ‛abs’
+    In the instance declaration for ‛Num (a, b)’
 
-read014.hs:6:10:
-    Warning: No explicit method or default declaration for `signum'
-    In the instance declaration for `Num (a, b)'
+read014.hs:6:10: Warning:
+    No explicit method or default declaration for ‛signum’
+    In the instance declaration for ‛Num (a, b)’
 
-read014.hs:6:10:
-    Warning: No explicit method or default declaration for `fromInteger'
-    In the instance declaration for `Num (a, b)'
+read014.hs:6:10: Warning:
+    No explicit method or default declaration for ‛fromInteger’
+    In the instance declaration for ‛Num (a, b)’
 
-read014.hs:8:53: Warning: Defined but not used: `x'
+read014.hs:8:53: Warning: Defined but not used: ‛x’
diff --git a/tests/parser/should_fail/T3811d.stderr b/tests/parser/should_fail/T3811d.stderr
index 28d08548c..ddffea00f 100644
--- a/tests/parser/should_fail/T3811d.stderr
+++ b/tests/parser/should_fail/T3811d.stderr
@@ -1,4 +1,4 @@
-
-T3811d.hs:6:11:
-    Unexpected type `D Char' where type variable expected
-    In the declaration of `C b (D Char) b'
+
+T3811d.hs:6:11:
+    Unexpected type ‛D Char’ where type variable expected
+    In the declaration of ‛C b (D Char) b’
diff --git a/tests/parser/should_fail/readFail001.stderr b/tests/parser/should_fail/readFail001.stderr
index f146ae562..aba4ec239 100644
--- a/tests/parser/should_fail/readFail001.stderr
+++ b/tests/parser/should_fail/readFail001.stderr
@@ -1,26 +1,26 @@
 
 readFail001.hs:25:11:
-    The fixity signature for `+#' lacks an accompanying binding
+    The fixity signature for ‛+#’ lacks an accompanying binding
 
 readFail001.hs:38:32:
-    Not in scope: type constructor or class `Leaf'
+    Not in scope: type constructor or class ‛Leaf’
     A data constructor of that name is in scope; did you mean -XDataKinds?
 
 readFail001.hs:38:41:
-    Not in scope: type constructor or class `Leaf'
+    Not in scope: type constructor or class ‛Leaf’
     A data constructor of that name is in scope; did you mean -XDataKinds?
 
-readFail001.hs:87:11: Not in scope: `x'
+readFail001.hs:87:11: Not in scope: ‛x’
 
-readFail001.hs:88:19: Not in scope: `x'
+readFail001.hs:88:19: Not in scope: ‛x’
 
-readFail001.hs:94:19: Not in scope: `isSpace'
+readFail001.hs:94:19: Not in scope: ‛isSpace’
 
-readFail001.hs:95:13: Not in scope: `foo'
+readFail001.hs:95:13: Not in scope: ‛foo’
 
-readFail001.hs:107:30: Not in scope: data constructor `Foo'
+readFail001.hs:107:30: Not in scope: data constructor ‛Foo’
 
-readFail001.hs:107:42: Not in scope: data constructor `Bar'
+readFail001.hs:107:42: Not in scope: data constructor ‛Bar’
 
 readFail001.hs:112:23:
-    Not in scope: type constructor or class `Foo'
+    Not in scope: type constructor or class ‛Foo’
diff --git a/tests/parser/should_fail/readFail008.stderr b/tests/parser/should_fail/readFail008.stderr
index a40ce01da..a2701740b 100644
--- a/tests/parser/should_fail/readFail008.stderr
+++ b/tests/parser/should_fail/readFail008.stderr
@@ -1,6 +1,6 @@
 
 readFail008.hs:5:15:
     A newtype constructor cannot have a strictness annotation,
-      but `T' does
-    In the definition of data constructor `T'
-    In the newtype declaration for `N'
+      but ‛T’ does
+    In the definition of data constructor ‛T’
+    In the newtype declaration for ‛N’
diff --git a/tests/parser/should_fail/readFail016.stderr b/tests/parser/should_fail/readFail016.stderr
index 620d8505a..87f3d2c65 100644
--- a/tests/parser/should_fail/readFail016.stderr
+++ b/tests/parser/should_fail/readFail016.stderr
@@ -1,4 +1,4 @@
 
 readFail016.hs:7:1:
     Precedence parsing error
-        cannot mix `|-' [infix 6] and `:' [infixr 5] in the same infix expression
+        cannot mix ‛|-’ [infix 6] and ‛:’ [infixr 5] in the same infix expression
diff --git a/tests/parser/should_fail/readFail021.stderr b/tests/parser/should_fail/readFail021.stderr
index a3f5e7b3f..ed55c0df7 100644
--- a/tests/parser/should_fail/readFail021.stderr
+++ b/tests/parser/should_fail/readFail021.stderr
@@ -1,2 +1,3 @@
 
-readFail021.hs:1:1: The function `main' is not defined in module `Main'
+readFail021.hs:1:1:
+    The function ‛main’ is not defined in module ‛Main’
diff --git a/tests/parser/should_fail/readFail023.stderr b/tests/parser/should_fail/readFail023.stderr
index e1b6ceb83..c31dc4e99 100644
--- a/tests/parser/should_fail/readFail023.stderr
+++ b/tests/parser/should_fail/readFail023.stderr
@@ -1,6 +1,6 @@
 
 readFail023.hs:9:5:
-    The operator `**' [infixl 7] of a section
+    The operator ‛**’ [infixl 7] of a section
         must have lower precedence than that of the operand,
           namely prefix `-' [infixl 6]
-        in the section: `- 3 **'
+        in the section: ‛- 3 **’
diff --git a/tests/parser/should_fail/readFail025.stderr b/tests/parser/should_fail/readFail025.stderr
index 24e83e712..0d74f8633 100644
--- a/tests/parser/should_fail/readFail025.stderr
+++ b/tests/parser/should_fail/readFail025.stderr
@@ -1,4 +1,4 @@
-
-readFail025.hs:5:8:
-    Unexpected type `String' where type variable expected
-    In the declaration of `T String'
+
+readFail025.hs:5:8:
+    Unexpected type ‛String’ where type variable expected
+    In the declaration of ‛T String’
diff --git a/tests/parser/should_fail/readFail035.stderr b/tests/parser/should_fail/readFail035.stderr
index f0489b45e..9e3a64a06 100644
--- a/tests/parser/should_fail/readFail035.stderr
+++ b/tests/parser/should_fail/readFail035.stderr
@@ -1,4 +1,4 @@
-
-readFail035.hs:6:1:
-    `Foo' has no constructors (-XEmptyDataDecls permits this)
-    In the data declaration for `Foo'
+
+readFail035.hs:6:1:
+    ‛Foo’ has no constructors (-XEmptyDataDecls permits this)
+    In the data declaration for ‛Foo’
diff --git a/tests/parser/should_fail/readFail036.stderr b/tests/parser/should_fail/readFail036.stderr
index 088f0a997..9360e6242 100644
--- a/tests/parser/should_fail/readFail036.stderr
+++ b/tests/parser/should_fail/readFail036.stderr
@@ -1,5 +1,5 @@
 
 readFail036.hs:4:16:
-    Illegal kind signature: `*'
+    Illegal kind signature: ‛*’
       Perhaps you intended to use -XKindSignatures
-    In the data type declaration for `Foo'
+    In the data type declaration for ‛Foo’
diff --git a/tests/parser/should_fail/readFail037.stderr b/tests/parser/should_fail/readFail037.stderr
index 4c900d66b..a9c9ff7ad 100644
--- a/tests/parser/should_fail/readFail037.stderr
+++ b/tests/parser/should_fail/readFail037.stderr
@@ -1,5 +1,5 @@
 
 readFail037.hs:4:1:
-    Too many parameters for class `Foo'
+    Too many parameters for class ‛Foo’
     (Use -XMultiParamTypeClasses to allow multi-parameter classes)
-    In the class declaration for `Foo'
+    In the class declaration for ‛Foo’
diff --git a/tests/parser/should_fail/readFail039.stderr b/tests/parser/should_fail/readFail039.stderr
index 1c7cb6b97..d0e27526f 100644
--- a/tests/parser/should_fail/readFail039.stderr
+++ b/tests/parser/should_fail/readFail039.stderr
@@ -1,6 +1,6 @@
-
-readFail039.hs:8:14:
-    Can't make a derived instance of `C Foo':
-      `C' is not a derivable class
-      Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension
-    In the newtype declaration for `Foo'
+
+readFail039.hs:8:14:
+    Can't make a derived instance of ‛C Foo’:
+      ‛C’ is not a derivable class
+      Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension
+    In the newtype declaration for ‛Foo’
diff --git a/tests/parser/should_fail/readFail041.stderr b/tests/parser/should_fail/readFail041.stderr
index fbe49b115..14903b5b2 100644
--- a/tests/parser/should_fail/readFail041.stderr
+++ b/tests/parser/should_fail/readFail041.stderr
@@ -1,5 +1,5 @@
 
 readFail041.hs:6:1:
-    Fundeps in class `Foo'
+    Fundeps in class ‛Foo’
     (Use -XFunctionalDependencies to allow fundeps)
-    In the class declaration for `Foo'
+    In the class declaration for ‛Foo’
diff --git a/tests/parser/should_fail/readFail042.stderr b/tests/parser/should_fail/readFail042.stderr
index 8fbb9bf1f..9941cb633 100644
--- a/tests/parser/should_fail/readFail042.stderr
+++ b/tests/parser/should_fail/readFail042.stderr
@@ -7,6 +7,6 @@ readFail042.hs:11:9:
     Unexpected transform statement in a list comprehension
     Use -XTransformListComp
 
-readFail042.hs:11:23: Not in scope: `by'
+readFail042.hs:11:23: Not in scope: ‛by’
 
-readFail042.hs:11:26: Not in scope: `x'
+readFail042.hs:11:26: Not in scope: ‛x’
diff --git a/tests/parser/should_fail/readFail043.stderr b/tests/parser/should_fail/readFail043.stderr
index b132bef95..72981ed3f 100644
--- a/tests/parser/should_fail/readFail043.stderr
+++ b/tests/parser/should_fail/readFail043.stderr
@@ -3,24 +3,24 @@ readFail043.hs:10:9:
     Unexpected transform statement in a list comprehension
     Use -XTransformListComp
 
-readFail043.hs:10:20: Not in scope: `by'
+readFail043.hs:10:20: Not in scope: ‛by’
 
-readFail043.hs:10:23: Not in scope: `x'
+readFail043.hs:10:23: Not in scope: ‛x’
 
-readFail043.hs:10:25: Not in scope: `using'
+readFail043.hs:10:25: Not in scope: ‛using’
 
 readFail043.hs:11:9:
     Unexpected transform statement in a list comprehension
     Use -XTransformListComp
 
-readFail043.hs:11:20: Not in scope: `by'
+readFail043.hs:11:20: Not in scope: ‛by’
 
-readFail043.hs:11:23: Not in scope: `x'
+readFail043.hs:11:23: Not in scope: ‛x’
 
-readFail043.hs:11:25: Not in scope: `using'
+readFail043.hs:11:25: Not in scope: ‛using’
 
 readFail043.hs:12:9:
     Unexpected transform statement in a list comprehension
     Use -XTransformListComp
 
-readFail043.hs:12:20: Not in scope: `using'
+readFail043.hs:12:20: Not in scope: ‛using’
diff --git a/tests/parser/should_fail/readFail046.stderr b/tests/parser/should_fail/readFail046.stderr
index a303d7798..072fe530f 100644
--- a/tests/parser/should_fail/readFail046.stderr
+++ b/tests/parser/should_fail/readFail046.stderr
@@ -1,4 +1,4 @@
 
 readFail046.hs:1:14:
     Unsupported extension: ExistientialQuantification
-    Perhaps you meant `ExistentialQuantification' or `NoExistentialQuantification'
+    Perhaps you meant ‛ExistentialQuantification’ or ‛NoExistentialQuantification’
diff --git a/tests/parser/unicode/T2302.stderr b/tests/parser/unicode/T2302.stderr
index 9718423be..0557a731d 100644
--- a/tests/parser/unicode/T2302.stderr
+++ b/tests/parser/unicode/T2302.stderr
@@ -1,2 +1,2 @@
 
-T2302.hs:1:5: Not in scope: data constructor `À'
+T2302.hs:1:5: Not in scope: data constructor ‛À’
diff --git a/tests/perf/compiler/parsing001.stderr b/tests/perf/compiler/parsing001.stderr
index b42ab6cb2..fe5939628 100644
--- a/tests/perf/compiler/parsing001.stderr
+++ b/tests/perf/compiler/parsing001.stderr
@@ -1,4 +1,4 @@
 
 parsing001.hs:3:1:
-    Failed to load interface for `Wibble'
+    Failed to load interface for ‛Wibble’
     Use -v to see a list of the files searched for.
diff --git a/tests/plugins/plugins03.stderr b/tests/plugins/plugins03.stderr
index f3fbc8e9f..24feee818 100644
--- a/tests/plugins/plugins03.stderr
+++ b/tests/plugins/plugins03.stderr
@@ -1 +1,2 @@
-<command line>: Could not find module `Simple.NonExistantPlugin' Use -v to see a list of the files searched for.
+<command line>: Could not find module ‛Simple.NonExistantPlugin’
+Use -v to see a list of the files searched for.
diff --git a/tests/plugins/plugins04.stderr b/tests/plugins/plugins04.stderr
index add1e60d0..13f94e439 100644
--- a/tests/plugins/plugins04.stderr
+++ b/tests/plugins/plugins04.stderr
@@ -1,2 +1,2 @@
 Module imports form a cycle:
-  module `HomePackagePlugin' (./HomePackagePlugin.hs) imports itself
+  module ‛HomePackagePlugin’ (./HomePackagePlugin.hs) imports itself
diff --git a/tests/polykinds/PolyKinds02.stderr b/tests/polykinds/PolyKinds02.stderr
index 60e00d5c9..8fd49c815 100644
--- a/tests/polykinds/PolyKinds02.stderr
+++ b/tests/polykinds/PolyKinds02.stderr
@@ -1,5 +1,5 @@
 
 PolyKinds02.hs:13:16:
-    The second argument of `Vec' should have kind `Nat',
-      but `Nat' has kind `*'
-    In the type signature for `vec': vec :: Vec Nat Nat
+    The second argument of ‛Vec’ should have kind ‛Nat’,
+      but ‛Nat’ has kind ‛*’
+    In the type signature for ‛vec’: vec :: Vec Nat Nat
diff --git a/tests/polykinds/PolyKinds04.stderr b/tests/polykinds/PolyKinds04.stderr
index 2796b1a89..1ffdf3910 100644
--- a/tests/polykinds/PolyKinds04.stderr
+++ b/tests/polykinds/PolyKinds04.stderr
@@ -1,8 +1,8 @@
 
 PolyKinds04.hs:5:16:
-    Expecting one more argument to `Maybe'
-    The first argument of `A' should have kind `*',
-      but `Maybe' has kind `* -> *'
-    In the type `A Maybe'
-    In the definition of data constructor `B1'
-    In the data declaration for `B'
+    Expecting one more argument to ‛Maybe’
+    The first argument of ‛A’ should have kind ‛*’,
+      but ‛Maybe’ has kind ‛* -> *’
+    In the type ‛A Maybe’
+    In the definition of data constructor ‛B1’
+    In the data declaration for ‛B’
diff --git a/tests/polykinds/PolyKinds06.stderr b/tests/polykinds/PolyKinds06.stderr
index 0d0baca84..fc1700f31 100644
--- a/tests/polykinds/PolyKinds06.stderr
+++ b/tests/polykinds/PolyKinds06.stderr
@@ -1,5 +1,5 @@
-
-PolyKinds06.hs:9:11:
-    Type constructor `A' cannot be used here
-      (it is defined and used in the same recursive group)
-    In the kind `A -> *'
+
+PolyKinds06.hs:9:11:
+    Type constructor ‛A’ cannot be used here
+      (it is defined and used in the same recursive group)
+    In the kind ‛A -> *’
diff --git a/tests/polykinds/PolyKinds07.stderr b/tests/polykinds/PolyKinds07.stderr
index 29930179c..761f13aeb 100644
--- a/tests/polykinds/PolyKinds07.stderr
+++ b/tests/polykinds/PolyKinds07.stderr
@@ -1,7 +1,7 @@
-
-PolyKinds07.hs:10:11:
-    Data constructor `A1' cannot be used here
-      (it is defined and used in the same recursive group)
-    In the type `B A1'
-    In the definition of data constructor `B1'
-    In the data declaration for `B'
+
+PolyKinds07.hs:10:11:
+    Data constructor ‛A1’ cannot be used here
+      (it is defined and used in the same recursive group)
+    In the type ‛B A1’
+    In the definition of data constructor ‛B1’
+    In the data declaration for ‛B’
diff --git a/tests/polykinds/T5716.stderr b/tests/polykinds/T5716.stderr
index 165f32bd7..f32e604c2 100644
--- a/tests/polykinds/T5716.stderr
+++ b/tests/polykinds/T5716.stderr
@@ -1,4 +1,4 @@
-
-T5716.hs:13:11:
-    `U' of kind `*' is not promotable
-    In the kind `U -> *'
+
+T5716.hs:13:11:
+    ‛U’ of kind ‛*’ is not promotable
+    In the kind ‛U -> *’
diff --git a/tests/polykinds/T5716a.stderr b/tests/polykinds/T5716a.stderr
index 4b10729cd..e21d44667 100644
--- a/tests/polykinds/T5716a.stderr
+++ b/tests/polykinds/T5716a.stderr
@@ -1,7 +1,7 @@
-
-T5716a.hs:10:27:
-    Data constructor `Bar' cannot be used here
-      (it comes from a data family instance)
-    In the type `Bar a'
-    In the definition of data constructor `Bar'
-    In the data instance declaration for `DF'
+
+T5716a.hs:10:27:
+    Data constructor ‛Bar’ cannot be used here
+      (it comes from a data family instance)
+    In the type ‛Bar a’
+    In the definition of data constructor ‛Bar’
+    In the data instance declaration for ‛DF’
diff --git a/tests/polykinds/T6021.stderr b/tests/polykinds/T6021.stderr
index f164f78ed..706729113 100644
--- a/tests/polykinds/T6021.stderr
+++ b/tests/polykinds/T6021.stderr
@@ -1,4 +1,4 @@
-
-T6021.hs:5:10:
-    Kind variable also used as type variable: `b'
-    In an instance declaration
+
+T6021.hs:5:10:
+    Kind variable also used as type variable: ‛b’
+    In an instance declaration
diff --git a/tests/polykinds/T6039.stderr b/tests/polykinds/T6039.stderr
index 7620c3adf..20b947b86 100644
--- a/tests/polykinds/T6039.stderr
+++ b/tests/polykinds/T6039.stderr
@@ -1,4 +1,4 @@
 
 T6039.hs:5:14:
-    Kind variable `j' cannot appear in a function position
-    In the kind `j k'
+    Kind variable ‛j’ cannot appear in a function position
+    In the kind ‛j k’
diff --git a/tests/polykinds/T6054.stderr b/tests/polykinds/T6054.stderr
index bc034d313..5fb7f6daa 100644
--- a/tests/polykinds/T6054.stderr
+++ b/tests/polykinds/T6054.stderr
@@ -2,8 +2,8 @@
 T6054.hs:7:14:
     No instance for (Bar () '() a0)
       arising from an expression type signature
-    In the first argument of `print', namely
-      `(Proxy :: Bar () a => Proxy a)'
+    In the first argument of ‛print’, namely
+      ‛(Proxy :: Bar () a => Proxy a)’
     In the expression: print (Proxy :: Bar () a => Proxy a)
-    In an equation for `foo':
+    In an equation for ‛foo’:
         foo = print (Proxy :: Bar () a => Proxy a)
diff --git a/tests/polykinds/T6129.stderr b/tests/polykinds/T6129.stderr
index 10db12ef4..9b8d66f20 100644
--- a/tests/polykinds/T6129.stderr
+++ b/tests/polykinds/T6129.stderr
@@ -1,7 +1,7 @@
-
-T6129.hs:12:11:
-    Data constructor `DInt' cannot be used here
-      (it comes from a data family instance)
-    In the type `X DInt'
-    In the definition of data constructor `X1'
-    In the data declaration for `X'
+
+T6129.hs:12:11:
+    Data constructor ‛DInt’ cannot be used here
+      (it comes from a data family instance)
+    In the type ‛X DInt’
+    In the definition of data constructor ‛X1’
+    In the data declaration for ‛X’
diff --git a/tests/polykinds/T7053.stderr b/tests/polykinds/T7053.stderr
index ab8579789..f5c3efc4f 100644
--- a/tests/polykinds/T7053.stderr
+++ b/tests/polykinds/T7053.stderr
@@ -1,8 +1,8 @@
-
-T7053.hs:6:52:
-    Kind occurs check
-    The first argument of `a' should have kind `k0',
-      but `b' has kind `k0 -> k1'
-    In the type `TypeRep (a b)'
-    In the definition of data constructor `TyApp'
-    In the data declaration for `TypeRep'
+
+T7053.hs:6:52:
+    Kind occurs check
+    The first argument of ‛a’ should have kind ‛k0’,
+      but ‛b’ has kind ‛k0 -> k1’
+    In the type ‛TypeRep (a b)’
+    In the definition of data constructor ‛TyApp’
+    In the data declaration for ‛TypeRep’
diff --git a/tests/polykinds/T7151.stderr b/tests/polykinds/T7151.stderr
index ed98ddc0d..bdefa666d 100644
--- a/tests/polykinds/T7151.stderr
+++ b/tests/polykinds/T7151.stderr
@@ -1,4 +1,4 @@
 
 T7151.hs:3:12:
-    Illegal type: '[Int, String]
+    Illegal type: ‛'[Int, String]’
       Perhaps you intended to use -XDataKinds
diff --git a/tests/polykinds/T7224.stderr b/tests/polykinds/T7224.stderr
index c1508e9b7..1ae01218a 100644
--- a/tests/polykinds/T7224.stderr
+++ b/tests/polykinds/T7224.stderr
@@ -1,5 +1,5 @@
 
 T7224.hs:6:19:
-    Kind variable `i' used as a type
-    In the type `a -> m i i a'
-    In the class declaration for PMonad'
+    Kind variable ‛i’ used as a type
+    In the type ‛a -> m i i a’
+    In the class declaration for ‛PMonad'’
diff --git a/tests/polykinds/T7230.stderr b/tests/polykinds/T7230.stderr
index 3bcccee8f..34695d0e0 100644
--- a/tests/polykinds/T7230.stderr
+++ b/tests/polykinds/T7230.stderr
@@ -10,13 +10,13 @@ T7230.hs:48:32:
       bound by a pattern with constructor
                  SCons :: forall (k :: BOX) (x :: k) (xs :: [k]).
                           Sing k x -> Sing [k] xs -> Sing [k] ((':) k x xs),
-               in an equation for `crash'
+               in an equation for ‛crash’
       at T7230.hs:48:8-27
     or from (xs1 ~ (':) Nat x1 xs2)
       bound by a pattern with constructor
                  SCons :: forall (k :: BOX) (x :: k) (xs :: [k]).
                           Sing k x -> Sing [k] xs -> Sing [k] ((':) k x xs),
-               in an equation for `crash'
+               in an equation for ‛crash’
       at T7230.hs:48:17-26
     Expected type: SBool (Increasing xs)
       Actual type: SBool (x :<<= x1)
@@ -24,5 +24,5 @@ T7230.hs:48:32:
       x :: Sing Nat x (bound at T7230.hs:48:14)
       y :: Sing Nat x1 (bound at T7230.hs:48:23)
     In the expression: x %:<<= y
-    In an equation for `crash':
+    In an equation for ‛crash’:
         crash (SCons x (SCons y xs)) = x %:<<= y
diff --git a/tests/polykinds/T7278.stderr b/tests/polykinds/T7278.stderr
index 96f8dd718..a242e5aaf 100644
--- a/tests/polykinds/T7278.stderr
+++ b/tests/polykinds/T7278.stderr
@@ -1,5 +1,5 @@
 
 T7278.hs:8:43:
-    `t' is applied to too many type arguments
-    In the type signature for `f':
+    ‛t’ is applied to too many type arguments
+    In the type signature for ‛f’:
       f :: C (t :: k) (TF t) => TF t p1 p0 -> t p1 p0
diff --git a/tests/polykinds/T7328.stderr b/tests/polykinds/T7328.stderr
index 6151c5ae4..54508c077 100644
--- a/tests/polykinds/T7328.stderr
+++ b/tests/polykinds/T7328.stderr
@@ -1,7 +1,7 @@
 
 T7328.hs:8:34:
     Kind occurs check
-    The first argument of `Foo' should have kind `k0',
-      but `f' has kind `k1 -> k0'
-    In the type `a ~ f i => Proxy (Foo f)'
-    In the class declaration for `Foo'
+    The first argument of ‛Foo’ should have kind ‛k0’,
+      but ‛f’ has kind ‛k1 -> k0’
+    In the type ‛a ~ f i => Proxy (Foo f)’
+    In the class declaration for ‛Foo’
diff --git a/tests/polykinds/T7341.stderr b/tests/polykinds/T7341.stderr
index da9ae7f70..36ab4eaaf 100644
--- a/tests/polykinds/T7341.stderr
+++ b/tests/polykinds/T7341.stderr
@@ -1,6 +1,6 @@
-
-T7341.hs:11:12:
-    Expecting one more argument to `[]'
-    The first argument of `C' should have kind `*',
-      but `[]' has kind `* -> *'
-    In the instance declaration for `C []'
+
+T7341.hs:11:12:
+    Expecting one more argument to ‛[]’
+    The first argument of ‛C’ should have kind ‛*’,
+      but ‛[]’ has kind ‛* -> *’
+    In the instance declaration for ‛C []’
diff --git a/tests/polykinds/T7404.stderr b/tests/polykinds/T7404.stderr
index 561cc24b0..a228e0c1b 100644
--- a/tests/polykinds/T7404.stderr
+++ b/tests/polykinds/T7404.stderr
@@ -1,4 +1,4 @@
 
 T7404.hs:4:1:
-    Kind variable also used as type variable: `x'
-    In the declaration for type family `Foo'
+    Kind variable also used as type variable: ‛x’
+    In the declaration for type family ‛Foo’
diff --git a/tests/polykinds/T7433.stderr b/tests/polykinds/T7433.stderr
index 8f80b9e67..6cb69630e 100644
--- a/tests/polykinds/T7433.stderr
+++ b/tests/polykinds/T7433.stderr
@@ -1,6 +1,6 @@
 
 T7433.hs:2:10:
-    Data constructor `Z' cannot be used here
+    Data constructor ‛Z’ cannot be used here
       (Perhaps you intended to use -XDataKinds)
-    In the type `Z'
-    In the type declaration for `T'
+    In the type ‛Z’
+    In the type declaration for ‛T’
diff --git a/tests/polykinds/T7438.stderr b/tests/polykinds/T7438.stderr
index 8a1af96fe..aaa4daf01 100644
--- a/tests/polykinds/T7438.stderr
+++ b/tests/polykinds/T7438.stderr
@@ -1,20 +1,20 @@
 
 T7438.hs:6:14:
-    Couldn't match expected type `t1' with actual type `t'
-      `t' is untouchable
+    Couldn't match expected type ‛t1’ with actual type ‛t’
+      ‛t’ is untouchable
         inside the constraints (t2 ~ t3)
         bound by a pattern with constructor
                    Nil :: forall (k :: BOX) (a :: k). Thrist k a a,
-                 in an equation for `go'
+                 in an equation for ‛go’
         at T7438.hs:6:4-6
-      `t' is a rigid type variable bound by
+      ‛t’ is a rigid type variable bound by
           the inferred type of go :: Thrist k t2 t3 -> t -> t1
           at T7438.hs:6:1
-      `t1' is a rigid type variable bound by
+      ‛t1’ is a rigid type variable bound by
            the inferred type of go :: Thrist k t2 t3 -> t -> t1
            at T7438.hs:6:1
     Relevant bindings include
       go :: Thrist k t2 t3 -> t -> t1 (bound at T7438.hs:6:1)
       acc :: t (bound at T7438.hs:6:8)
     In the expression: acc
-    In an equation for `go': go Nil acc = acc
+    In an equation for ‛go’: go Nil acc = acc
diff --git a/tests/polykinds/T7594.stderr b/tests/polykinds/T7594.stderr
index 85a927dec..c813a65e8 100644
--- a/tests/polykinds/T7594.stderr
+++ b/tests/polykinds/T7594.stderr
@@ -1,16 +1,16 @@
 
 T7594.hs:25:11:
-    Couldn't match type `b' with `IO ()'
-      `b' is untouchable
+    Couldn't match type ‛b’ with ‛IO ()’
+      ‛b’ is untouchable
         inside the constraints ((:&:) Show Real a)
         bound by a type expected by the context:
                    (:&:) Show Real a => a -> b
         at T7594.hs:25:7-17
-      `b' is a rigid type variable bound by
+      ‛b’ is a rigid type variable bound by
           the inferred type of bar :: b at T7594.hs:25:1
     Expected type: a -> b
       Actual type: a -> IO ()
     Relevant bindings include bar :: b (bound at T7594.hs:25:1)
-    In the first argument of `app', namely `print'
+    In the first argument of ‛app’, namely ‛print’
     In the expression: app print q
-    In an equation for `bar': bar = app print q
+    In an equation for ‛bar’: bar = app print q
diff --git a/tests/programs/hs-boot/hs-boot.stderr b/tests/programs/hs-boot/hs-boot.stderr
index 99de1b67f..b171e1b54 100644
--- a/tests/programs/hs-boot/hs-boot.stderr
+++ b/tests/programs/hs-boot/hs-boot.stderr
@@ -1,2 +1,2 @@
 
-B.hs:5:23: Warning: {-# SOURCE #-} unnecessary in import of  `A'
+B.hs:5:23: Warning: {-# SOURCE #-} unnecessary in import of  ‛A’
diff --git a/tests/quasiquotation/T3953.stderr b/tests/quasiquotation/T3953.stderr
index da6f2dceb..bd2b0fed5 100644
--- a/tests/quasiquotation/T3953.stderr
+++ b/tests/quasiquotation/T3953.stderr
@@ -1,2 +1,2 @@
 
-T3953.hs:5:7: Not in scope: `notDefinedHere'
+T3953.hs:5:7: Not in scope: ‛notDefinedHere’
diff --git a/tests/rebindable/rebindable6.stderr b/tests/rebindable/rebindable6.stderr
index a12cef09f..e36e38d05 100644
--- a/tests/rebindable/rebindable6.stderr
+++ b/tests/rebindable/rebindable6.stderr
@@ -1,67 +1,67 @@
-
-rebindable6.hs:106:17:
-    No instance for (HasSeq (IO a -> t0 -> IO b))
-      arising from a do statement
-    The type variable `t0' is ambiguous
-    Relevant bindings include
-      test_do :: IO a -> IO (Maybe b) -> IO b
-        (bound at rebindable6.hs:104:9)
-      f :: IO a (bound at rebindable6.hs:104:17)
-      g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
-    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 (HasBind (IO (Maybe b) -> (Maybe b -> t1) -> t0))
-      arising from a do statement
-    The type variables `t0', `t1' are ambiguous
-    Relevant bindings include
-      test_do :: IO a -> IO (Maybe b) -> IO b
-        (bound at rebindable6.hs:104:9)
-      g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
-    Note: there is a potential instance available:
-      instance HasBind (IO a -> (a -> IO b) -> IO b)
-        -- Defined at rebindable6.hs:47: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))
-      arising from a use of `return'
-    The type variable `t1' is ambiguous
-    Relevant bindings include
-      test_do :: IO a -> IO (Maybe b) -> IO b
-        (bound at rebindable6.hs:104:9)
-      g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
-      b :: b (bound at rebindable6.hs:107:23)
-    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))
+      arising from a do statement
+    The type variable ‛t0’ is ambiguous
+    Relevant bindings include
+      test_do :: IO a -> IO (Maybe b) -> IO b
+        (bound at rebindable6.hs:104:9)
+      f :: IO a (bound at rebindable6.hs:104:17)
+      g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
+    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 (HasBind (IO (Maybe b) -> (Maybe b -> t1) -> t0))
+      arising from a do statement
+    The type variables ‛t0’, ‛t1’ are ambiguous
+    Relevant bindings include
+      test_do :: IO a -> IO (Maybe b) -> IO b
+        (bound at rebindable6.hs:104:9)
+      g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
+    Note: there is a potential instance available:
+      instance HasBind (IO a -> (a -> IO b) -> IO b)
+        -- Defined at rebindable6.hs:47: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))
+      arising from a use of ‛return’
+    The type variable ‛t1’ is ambiguous
+    Relevant bindings include
+      test_do :: IO a -> IO (Maybe b) -> IO b
+        (bound at rebindable6.hs:104:9)
+      g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
+      b :: b (bound at rebindable6.hs:107:23)
+    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/tests/rename/prog002/rename.prog002.stderr b/tests/rename/prog002/rename.prog002.stderr
index 31b672b53..3d488acb5 100644
--- a/tests/rename/prog002/rename.prog002.stderr
+++ b/tests/rename/prog002/rename.prog002.stderr
@@ -1,2 +1,2 @@
 
-rnfail037.hs:8:7: Not in scope: data constructor `Rn037Help.C'
+rnfail037.hs:8:7: Not in scope: data constructor ‛Rn037Help.C’
diff --git a/tests/rename/prog003/rename.prog003.stderr b/tests/rename/prog003/rename.prog003.stderr
index 49c264cae..42cc924be 100644
--- a/tests/rename/prog003/rename.prog003.stderr
+++ b/tests/rename/prog003/rename.prog003.stderr
@@ -1,2 +1,2 @@
 
-B.hs:4:6: Not in scope: type constructor or class `Class'
+B.hs:4:6: Not in scope: type constructor or class ‛Class’
diff --git a/tests/rename/should_compile/T1789.stderr b/tests/rename/should_compile/T1789.stderr
index dc9a79493..3fd1f1a03 100644
--- a/tests/rename/should_compile/T1789.stderr
+++ b/tests/rename/should_compile/T1789.stderr
@@ -1,12 +1,12 @@
 
-T1789.hs:6:1:
-    Warning: The module `Prelude' does not have an explicit import list
+T1789.hs:6:1: Warning:
+    The module ‛Prelude’ does not have an explicit import list
 
-T1789.hs:7:1:
-    Warning: The module `Data.Map' does not have an explicit import list
+T1789.hs:7:1: Warning:
+    The module ‛Data.Map’ does not have an explicit import list
 
-T1789.hs:9:1:
-    Warning: The import item `Maybe(..)' does not have an explicit import list
+T1789.hs:9:1: Warning:
+    The import item ‛Maybe(..)’ does not have an explicit import list
 
-T1789.hs:10:1:
-    Warning: The module `Data.Maybe' does not have an explicit import list
+T1789.hs:10:1: Warning:
+    The module ‛Data.Maybe’ does not have an explicit import list
diff --git a/tests/rename/should_compile/T1972.stderr b/tests/rename/should_compile/T1972.stderr
index 610e50940..1cb78fbc2 100644
--- a/tests/rename/should_compile/T1972.stderr
+++ b/tests/rename/should_compile/T1972.stderr
@@ -1,11 +1,11 @@
 
-T1972.hs:12:3:
-    Warning: This binding for `name' shadows the existing binding
-               defined at T1972.hs:9:19
+T1972.hs:12:3: Warning:
+    This binding for ‛name’ shadows the existing binding
+      defined at T1972.hs:9:19
 
-T1972.hs:14:3:
-    Warning: This binding for `mapAccumL' shadows the existing bindings
-               defined at T1972.hs:16:1
-               imported from `Data.List' at T1972.hs:7:1-16
+T1972.hs:14:3: Warning:
+    This binding for ‛mapAccumL’ shadows the existing bindings
+      defined at T1972.hs:16:1
+      imported from ‛Data.List’ at T1972.hs:7:1-16
 
-T1972.hs:20:10: Warning: Defined but not used: `c'
+T1972.hs:20:10: Warning: Defined but not used: ‛c’
diff --git a/tests/rename/should_compile/T3262.stderr-ghc b/tests/rename/should_compile/T3262.stderr-ghc
index 4e730efa8..b3250fd5a 100644
--- a/tests/rename/should_compile/T3262.stderr-ghc
+++ b/tests/rename/should_compile/T3262.stderr-ghc
@@ -1,8 +1,8 @@
 
-T3262.hs:12:11:
-    Warning: This binding for `not_ignored' shadows the existing binding
-               bound at T3262.hs:11:11
+T3262.hs:12:11: Warning:
+    This binding for ‛not_ignored’ shadows the existing binding
+      bound at T3262.hs:11:11
 
-T3262.hs:20:15:
-    Warning: This binding for `not_ignored' shadows the existing binding
-               bound at T3262.hs:19:15
+T3262.hs:20:15: Warning:
+    This binding for ‛not_ignored’ shadows the existing binding
+      bound at T3262.hs:19:15
diff --git a/tests/rename/should_compile/T3371.stderr b/tests/rename/should_compile/T3371.stderr
index b354d9d3d..944739e45 100644
--- a/tests/rename/should_compile/T3371.stderr
+++ b/tests/rename/should_compile/T3371.stderr
@@ -1,2 +1,2 @@
 
-T3371.hs:10:14: Warning: Defined but not used: `a'
+T3371.hs:10:14: Warning: Defined but not used: ‛a’
diff --git a/tests/rename/should_compile/T3449.stderr b/tests/rename/should_compile/T3449.stderr
index da36d2446..32ddc6f35 100644
--- a/tests/rename/should_compile/T3449.stderr
+++ b/tests/rename/should_compile/T3449.stderr
@@ -1,2 +1,2 @@
 
-T3449.hs-boot:8:1: Warning: Defined but not used: `unused'
+T3449.hs-boot:8:1: Warning: Defined but not used: ‛unused’
diff --git a/tests/rename/should_compile/T3823.stderr b/tests/rename/should_compile/T3823.stderr
index 0eb823455..90e3c864e 100644
--- a/tests/rename/should_compile/T3823.stderr
+++ b/tests/rename/should_compile/T3823.stderr
@@ -1,6 +1,6 @@
 
 T3823B.hs:8:7:
-    Couldn't match expected type `A' with actual type `Bool'
-    In the first argument of `y', namely `a'
+    Couldn't match expected type ‛A’ with actual type ‛Bool’
+    In the first argument of ‛y’, namely ‛a’
     In the expression: y a
-    In an equation for `b': b = y a
+    In an equation for ‛b’: b = y a
diff --git a/tests/rename/should_compile/T4489.stderr b/tests/rename/should_compile/T4489.stderr
index 8cd400a72..5fd076ee4 100644
--- a/tests/rename/should_compile/T4489.stderr
+++ b/tests/rename/should_compile/T4489.stderr
@@ -1,6 +1,6 @@
-
-T4489.hs:4:1:
-    Warning: The module `Data.Maybe' does not have an explicit import list
-
-T4489.hs:5:1:
-    Warning: The import item `Maybe(..)' does not have an explicit import list
+
+T4489.hs:4:1: Warning:
+    The module ‛Data.Maybe’ does not have an explicit import list
+
+T4489.hs:5:1: Warning:
+    The import item ‛Maybe(..)’ does not have an explicit import list
diff --git a/tests/rename/should_compile/T5331.stderr b/tests/rename/should_compile/T5331.stderr
index e18c657e3..e78dd64da 100644
--- a/tests/rename/should_compile/T5331.stderr
+++ b/tests/rename/should_compile/T5331.stderr
@@ -1,13 +1,13 @@
-
-T5331.hs:8:17:
-    Warning: Unused quantified type variable `a'
-             In the definition of data constructor `S1'
-
-T5331.hs:11:16:
-    Warning: Unused quantified type variable `a'
-             In the definition of data constructor `W1'
-
-T5331.hs:13:13:
-    Warning: Unused quantified type variable `a'
-             In the type `forall a. Int'
-             In the type signature for `f'
+
+T5331.hs:8:17: Warning:
+    Unused quantified type variable ‛a’
+    In the definition of data constructor ‛S1’
+
+T5331.hs:11:16: Warning:
+    Unused quantified type variable ‛a’
+    In the definition of data constructor ‛W1’
+
+T5331.hs:13:13: Warning:
+    Unused quantified type variable ‛a’
+    In the type ‛forall a. Int’
+    In the type signature for ‛f’
diff --git a/tests/rename/should_compile/T5334.stderr b/tests/rename/should_compile/T5334.stderr
index de906b9dd..298538633 100644
--- a/tests/rename/should_compile/T5334.stderr
+++ b/tests/rename/should_compile/T5334.stderr
@@ -1,13 +1,13 @@
 
-T5334.hs:7:5:
-    Warning: Fields of `T' not initialised: b
+T5334.hs:7:5: Warning:
+    Fields of ‛T’ not initialised: b
     In the expression: T {..}
-    In an equation for `t':
+    In an equation for ‛t’:
         t = T {..}
           where
               a = 1
 
-T5334.hs:14:5:
-    Warning: Fields of `S' not initialised: y
+T5334.hs:14:5: Warning:
+    Fields of ‛S’ not initialised: y
     In the expression: S {x = 1}
-    In an equation for `s': s = S {x = 1}
+    In an equation for ‛s’: s = S {x = 1}
diff --git a/tests/rename/should_compile/T5867.stderr b/tests/rename/should_compile/T5867.stderr
index 35941c841..0ada9be52 100644
--- a/tests/rename/should_compile/T5867.stderr
+++ b/tests/rename/should_compile/T5867.stderr
@@ -1,8 +1,8 @@
 
 T5867.hs:4:7: Warning:
-    In the use of `f' (imported from T5867a):
+    In the use of ‛f’ (imported from T5867a):
     Deprecated: "Don't use f!"
 
 T5867.hs:5:7: Warning:
-    In the use of `f' (imported from T5867a):
+    In the use of ‛f’ (imported from T5867a):
     Deprecated: "Don't use f!"
diff --git a/tests/rename/should_compile/T7145b.stderr b/tests/rename/should_compile/T7145b.stderr
index 35e233d9c..f24d02954 100644
--- a/tests/rename/should_compile/T7145b.stderr
+++ b/tests/rename/should_compile/T7145b.stderr
@@ -1,2 +1,2 @@
 
-T7145b.hs:6:1: Warning: Defined but not used: `pure'
+T7145b.hs:6:1: Warning: Defined but not used: ‛pure’
diff --git a/tests/rename/should_compile/T7167.stderr b/tests/rename/should_compile/T7167.stderr
index 0607529f1..cddbbfe74 100644
--- a/tests/rename/should_compile/T7167.stderr
+++ b/tests/rename/should_compile/T7167.stderr
@@ -1,2 +1,2 @@
 
-T7167.hs:5:1: Warning: Module `Data.List' does not export `foo'
+T7167.hs:5:1: Warning: Module ‛Data.List’ does not export ‛foo’
diff --git a/tests/rename/should_compile/T7336.stderr b/tests/rename/should_compile/T7336.stderr
index bd51e730b..0610b13e2 100644
--- a/tests/rename/should_compile/T7336.stderr
+++ b/tests/rename/should_compile/T7336.stderr
@@ -1,3 +1,3 @@
-
-T7336.hs:3:10: Warning:
-    Defined but not used: data constructor `MkU'
+
+T7336.hs:3:10: Warning:
+    Defined but not used: data constructor ‛MkU’
diff --git a/tests/rename/should_compile/mc10.stderr-ghc b/tests/rename/should_compile/mc10.stderr-ghc
index 585bfa452..56a21b870 100644
--- a/tests/rename/should_compile/mc10.stderr-ghc
+++ b/tests/rename/should_compile/mc10.stderr-ghc
@@ -1,2 +1,2 @@
 
-mc10.hs:14:11: Warning: Defined but not used: `y'
+mc10.hs:14:11: Warning: Defined but not used: ‛y’
diff --git a/tests/rename/should_compile/rn037.stderr-ghc b/tests/rename/should_compile/rn037.stderr-ghc
index 64b604f9b..ad171a426 100644
--- a/tests/rename/should_compile/rn037.stderr-ghc
+++ b/tests/rename/should_compile/rn037.stderr-ghc
@@ -1,5 +1,5 @@
 
-rn037.hs:3:1:
-    Warning: The import of `Data.List' is redundant
-               except perhaps to import instances from `Data.List'
-             To import instances alone, use: import Data.List()
+rn037.hs:3:1: Warning:
+    The import of ‛Data.List’ is redundant
+      except perhaps to import instances from ‛Data.List’
+    To import instances alone, use: import Data.List()
diff --git a/tests/rename/should_compile/rn039.stderr-ghc b/tests/rename/should_compile/rn039.stderr-ghc
index 51adb6fa8..2b87c367e 100644
--- a/tests/rename/should_compile/rn039.stderr-ghc
+++ b/tests/rename/should_compile/rn039.stderr-ghc
@@ -1,5 +1,5 @@
 
-rn039.hs:6:16:
-    Warning: This binding for `-' shadows the existing binding
-               imported from `Prelude' at rn039.hs:2:8-20
-               (and originally defined in `GHC.Num')
+rn039.hs:6:16: Warning:
+    This binding for ‛-’ shadows the existing binding
+      imported from ‛Prelude’ at rn039.hs:2:8-20
+      (and originally defined in ‛GHC.Num’)
diff --git a/tests/rename/should_compile/rn040.stderr-ghc b/tests/rename/should_compile/rn040.stderr-ghc
index 5de9d0c1c..f5802287b 100644
--- a/tests/rename/should_compile/rn040.stderr-ghc
+++ b/tests/rename/should_compile/rn040.stderr-ghc
@@ -1,4 +1,4 @@
 
-rn040.hs:6:12: Warning: Defined but not used: `y'
+rn040.hs:6:12: Warning: Defined but not used: ‛y’
 
-rn040.hs:8:8: Warning: Defined but not used: `w'
+rn040.hs:8:8: Warning: Defined but not used: ‛w’
diff --git a/tests/rename/should_compile/rn041.stderr-ghc b/tests/rename/should_compile/rn041.stderr-ghc
index da94a0985..fbf27899a 100644
--- a/tests/rename/should_compile/rn041.stderr-ghc
+++ b/tests/rename/should_compile/rn041.stderr-ghc
@@ -1,6 +1,6 @@
 
-rn041.hs:7:1: Warning: Defined but not used: `f'
+rn041.hs:7:1: Warning: Defined but not used: ‛f’
 
-rn041.hs:9:1: Warning: Defined but not used: `g'
+rn041.hs:9:1: Warning: Defined but not used: ‛g’
 
-rn041.hs:10:1: Warning: Defined but not used: `h'
+rn041.hs:10:1: Warning: Defined but not used: ‛h’
diff --git a/tests/rename/should_compile/rn046.stderr-ghc b/tests/rename/should_compile/rn046.stderr-ghc
index ebde8af37..433537613 100644
--- a/tests/rename/should_compile/rn046.stderr-ghc
+++ b/tests/rename/should_compile/rn046.stderr-ghc
@@ -1,8 +1,8 @@
 
-rn046.hs:2:1:
-    Warning: The import of `Data.List' is redundant
-               except perhaps to import instances from `Data.List'
-             To import instances alone, use: import Data.List()
+rn046.hs:2:1: Warning:
+    The import of ‛Data.List’ is redundant
+      except perhaps to import instances from ‛Data.List’
+    To import instances alone, use: import Data.List()
 
-rn046.hs:3:1:
-    Warning: The import of `ord' from module `Data.Char' is redundant
+rn046.hs:3:1: Warning:
+    The import of ‛ord’ from module ‛Data.Char’ is redundant
diff --git a/tests/rename/should_compile/rn047.stderr-ghc b/tests/rename/should_compile/rn047.stderr-ghc
index 8b9614cb1..588237d26 100644
--- a/tests/rename/should_compile/rn047.stderr-ghc
+++ b/tests/rename/should_compile/rn047.stderr-ghc
@@ -1,2 +1,2 @@
 
-rn047.hs:12:11: Warning: Defined but not used: `y'
+rn047.hs:12:11: Warning: Defined but not used: ‛y’
diff --git a/tests/rename/should_compile/rn050.stderr b/tests/rename/should_compile/rn050.stderr
index 4eb19d696..2554787a4 100644
--- a/tests/rename/should_compile/rn050.stderr
+++ b/tests/rename/should_compile/rn050.stderr
@@ -1,8 +1,8 @@
 
 rn050.hs:13:7: Warning:
-    In the use of `op' (imported from Rn050_A):
+    In the use of ‛op’ (imported from Rn050_A):
     Deprecated: "Use bop instead"
 
 rn050.hs:13:10: Warning:
-    In the use of data constructor `C' (imported from Rn050_A):
+    In the use of data constructor ‛C’ (imported from Rn050_A):
     Deprecated: "Use D instead"
diff --git a/tests/rename/should_compile/rn063.stderr b/tests/rename/should_compile/rn063.stderr
index c437dd3c6..635ef98bd 100644
--- a/tests/rename/should_compile/rn063.stderr
+++ b/tests/rename/should_compile/rn063.stderr
@@ -1,4 +1,4 @@
 
-rn063.hs:10:9: Warning: Defined but not used: `x'
+rn063.hs:10:9: Warning: Defined but not used: ‛x’
 
-rn063.hs:13:9: Warning: Defined but not used: `y'
+rn063.hs:13:9: Warning: Defined but not used: ‛y’
diff --git a/tests/rename/should_compile/rn064.stderr b/tests/rename/should_compile/rn064.stderr
index f23a96bb5..6ca77eaf2 100644
--- a/tests/rename/should_compile/rn064.stderr
+++ b/tests/rename/should_compile/rn064.stderr
@@ -1,4 +1,4 @@
 
-rn064.hs:13:12:
-    Warning: This binding for `r' shadows the existing binding
-               bound at rn064.hs:15:9
+rn064.hs:13:12: Warning:
+    This binding for ‛r’ shadows the existing binding
+      bound at rn064.hs:15:9
diff --git a/tests/rename/should_compile/rn066.stderr b/tests/rename/should_compile/rn066.stderr
index 3d38aa9f2..52e82e9e7 100644
--- a/tests/rename/should_compile/rn066.stderr
+++ b/tests/rename/should_compile/rn066.stderr
@@ -1,8 +1,8 @@
 
 rn066.hs:13:7: Warning:
-    In the use of `op' (imported from Rn066_A):
+    In the use of ‛op’ (imported from Rn066_A):
     "Is that really a good idea?"
 
 rn066.hs:13:10: Warning:
-    In the use of data constructor `C' (imported from Rn066_A):
+    In the use of data constructor ‛C’ (imported from Rn066_A):
     "Are you sure you want to do that?"
diff --git a/tests/rename/should_fail/T1595a.stderr b/tests/rename/should_fail/T1595a.stderr
index 3c9adca7f..f7dd8113f 100644
--- a/tests/rename/should_fail/T1595a.stderr
+++ b/tests/rename/should_fail/T1595a.stderr
@@ -1,2 +1,2 @@
 
-T1595a.hs:3:20: Not in scope: type constructor or class `Tpyo'
+T1595a.hs:3:20: Not in scope: type constructor or class ‛Tpyo’
diff --git a/tests/rename/should_fail/T2310.stderr b/tests/rename/should_fail/T2310.stderr
index 6500eef1f..a5dd532a0 100644
--- a/tests/rename/should_fail/T2310.stderr
+++ b/tests/rename/should_fail/T2310.stderr
@@ -1,10 +1,10 @@
 
 T2310.hs:5:22:
-    Illegal result type signature `a'
+    Illegal result type signature ‛a’
       Result signatures are no longer supported in pattern matches
     In a lambda abstraction: \ x :: a -> (x :: a)
 
 T2310.hs:5:39:
-    Not in scope: `co'
+    Not in scope: ‛co’
     Perhaps you meant one of these:
-      `c' (line 5), `cos' (imported from Prelude)
+      ‛c’ (line 5), ‛cos’ (imported from Prelude)
diff --git a/tests/rename/should_fail/T2723.stderr b/tests/rename/should_fail/T2723.stderr
index 7ede04165..b34816145 100644
--- a/tests/rename/should_fail/T2723.stderr
+++ b/tests/rename/should_fail/T2723.stderr
@@ -1,4 +1,4 @@
 
-T2723.hs:15:5:
-    Warning: This binding for `field3' shadows the existing binding
-               defined at T2723.hs:7:1
+T2723.hs:15:5: Warning:
+    This binding for ‛field3’ shadows the existing binding
+      defined at T2723.hs:7:1
diff --git a/tests/rename/should_fail/T2901.stderr b/tests/rename/should_fail/T2901.stderr
index 8cf5b2f2b..fedaee632 100644
--- a/tests/rename/should_fail/T2901.stderr
+++ b/tests/rename/should_fail/T2901.stderr
@@ -1,4 +1,4 @@
 
-T2901.hs:6:5: Not in scope: data constructor `F.Foo'
+T2901.hs:6:5: Not in scope: data constructor ‛F.Foo’
 
-T2901.hs:6:13: `F.field' is not a (visible) constructor field name
+T2901.hs:6:13: ‛F.field’ is not a (visible) constructor field name
diff --git a/tests/rename/should_fail/T2993.stderr b/tests/rename/should_fail/T2993.stderr
index 0ba55ddd3..ec6fa1ea2 100644
--- a/tests/rename/should_fail/T2993.stderr
+++ b/tests/rename/should_fail/T2993.stderr
@@ -1,2 +1,2 @@
 
-T2993.hs:7:13: Not in scope: `<$>'
+T2993.hs:7:13: Not in scope: ‛<$>’
diff --git a/tests/rename/should_fail/T3265.stderr b/tests/rename/should_fail/T3265.stderr
index 37642ff16..0a56f4c5d 100644
--- a/tests/rename/should_fail/T3265.stderr
+++ b/tests/rename/should_fail/T3265.stderr
@@ -1,8 +1,8 @@
 
 T3265.hs:7:8:
-    Illegal declaration of a type or class operator `:+:'
+    Illegal declaration of a type or class operator ‛:+:’
       Use -XTypeOperators to declare operators in type and declarations
 
 T3265.hs:9:9:
-    Illegal declaration of a type or class operator `:*:'
+    Illegal declaration of a type or class operator ‛:*:’
       Use -XTypeOperators to declare operators in type and declarations
diff --git a/tests/rename/should_fail/T5211.stderr b/tests/rename/should_fail/T5211.stderr
index b99cc04d9..8dcc5b68b 100644
--- a/tests/rename/should_fail/T5211.stderr
+++ b/tests/rename/should_fail/T5211.stderr
@@ -1,5 +1,5 @@
 
 T5211.hs:5:1: Warning:
-    The qualified import of `Foreign.Storable' is redundant
-      except perhaps to import instances from `Foreign.Storable'
+    The qualified import of ‛Foreign.Storable’ is redundant
+      except perhaps to import instances from ‛Foreign.Storable’
     To import instances alone, use: import Foreign.Storable()
diff --git a/tests/rename/should_fail/T5281.stderr b/tests/rename/should_fail/T5281.stderr
index 3fa7670bb..99ad47b58 100644
--- a/tests/rename/should_fail/T5281.stderr
+++ b/tests/rename/should_fail/T5281.stderr
@@ -1,4 +1,4 @@
 
 T5281.hs:6:5: Warning:
-    In the use of `deprec' (imported from T5281A):
+    In the use of ‛deprec’ (imported from T5281A):
     Deprecated: "This is deprecated"
diff --git a/tests/rename/should_fail/T5372.stderr b/tests/rename/should_fail/T5372.stderr
index 47e50dc67..667787508 100644
--- a/tests/rename/should_fail/T5372.stderr
+++ b/tests/rename/should_fail/T5372.stderr
@@ -1,6 +1,6 @@
 
 T5372.hs:4:11:
-    Not in scope: data constructor `MkS'
-    Perhaps you meant `T5372a.MkS' (imported from T5372a)
+    Not in scope: data constructor ‛MkS’
+    Perhaps you meant ‛T5372a.MkS’ (imported from T5372a)
 
-T5372.hs:4:17: `x' is not a (visible) constructor field name
+T5372.hs:4:17: ‛x’ is not a (visible) constructor field name
diff --git a/tests/rename/should_fail/T5385.stderr b/tests/rename/should_fail/T5385.stderr
index c3ba1d5e6..2c87a0a47 100644
--- a/tests/rename/should_fail/T5385.stderr
+++ b/tests/rename/should_fail/T5385.stderr
@@ -1,8 +1,8 @@
 
 T5385.hs:3:16:
-    In module `T5385a':
-      `(:::)' is a data constructor of `T'
+    In module ‛T5385a’:
+      ‛(:::)’ is a data constructor of ‛T’
     To import it use
-      `import' T5385a( T( (:::) ) )
+      ‛import’ T5385a( T( (:::) ) )
     or
-      `import' T5385a( T(..) )
+      ‛import’ T5385a( T(..) )
diff --git a/tests/rename/should_fail/T5533.stderr b/tests/rename/should_fail/T5533.stderr
index b46285132..ce13e14e2 100644
--- a/tests/rename/should_fail/T5533.stderr
+++ b/tests/rename/should_fail/T5533.stderr
@@ -1,4 +1,4 @@
 
 T5533.hs:4:1:
-    The type signature for `f2' lacks an accompanying binding
+    The type signature for ‛f2’ lacks an accompanying binding
       (You cannot give a type signature for a record selector or class method)
diff --git a/tests/rename/should_fail/T5589.stderr b/tests/rename/should_fail/T5589.stderr
index 5eaae6436..cf0c0a9a1 100644
--- a/tests/rename/should_fail/T5589.stderr
+++ b/tests/rename/should_fail/T5589.stderr
@@ -1,5 +1,5 @@
-
-T5589.hs:4:1:
-    Duplicate type signatures for `aaa'
-    at T5589.hs:3:6-8
-       T5589.hs:4:1-3
+
+T5589.hs:4:1:
+    Duplicate type signatures for ‛aaa’
+    at T5589.hs:3:6-8
+       T5589.hs:4:1-3
diff --git a/tests/rename/should_fail/T5657.stderr b/tests/rename/should_fail/T5657.stderr
index af6f57e11..17a223d41 100644
--- a/tests/rename/should_fail/T5657.stderr
+++ b/tests/rename/should_fail/T5657.stderr
@@ -1,5 +1,5 @@
 
-T5657.hs:3:8: Not in scope: `LT..'
+T5657.hs:3:8: Not in scope: ‛LT..’
 
 T5657.hs:3:8:
     A section must be enclosed in parentheses thus: (LT.. GT)
diff --git a/tests/rename/should_fail/T5745.stderr b/tests/rename/should_fail/T5745.stderr
index 44994c918..b71e1e205 100644
--- a/tests/rename/should_fail/T5745.stderr
+++ b/tests/rename/should_fail/T5745.stderr
@@ -1,2 +1,2 @@
 
-T5745.hs:5:6: Not in scope: type constructor or class `T'
+T5745.hs:5:6: Not in scope: type constructor or class ‛T’
diff --git a/tests/rename/should_fail/T5892a.stderr b/tests/rename/should_fail/T5892a.stderr
index 1047599b8..a378dc391 100644
--- a/tests/rename/should_fail/T5892a.stderr
+++ b/tests/rename/should_fail/T5892a.stderr
@@ -1,9 +1,9 @@
 
 T5892a.hs:12:8: Warning:
-    Fields of `Version' not initialised: Data.Version.versionTags
+    Fields of ‛Version’ not initialised: Data.Version.versionTags
     In the expression: Version {..}
     In the expression: let versionBranch = [] in Version {..}
-    In an equation for `foo':
+    In an equation for ‛foo’:
         foo (Version {..}) = let versionBranch = ... in Version {..}
 
 <no location info>: 
diff --git a/tests/rename/should_fail/T5892b.stderr b/tests/rename/should_fail/T5892b.stderr
index 10d6c3692..10d1fd139 100644
--- a/tests/rename/should_fail/T5892b.stderr
+++ b/tests/rename/should_fail/T5892b.stderr
@@ -1,4 +1,4 @@
-
-T5892b.hs:11:7:
-    Not in scope: `T5892b.versionTags'
-    Perhaps you meant `T5892b.versionBranch' (line 7)
+
+T5892b.hs:11:7:
+    Not in scope: ‛T5892b.versionTags’
+    Perhaps you meant ‛T5892b.versionBranch’ (line 7)
diff --git a/tests/rename/should_fail/T7164.stderr b/tests/rename/should_fail/T7164.stderr
index a7c23e136..5e27fb876 100644
--- a/tests/rename/should_fail/T7164.stderr
+++ b/tests/rename/should_fail/T7164.stderr
@@ -1,5 +1,5 @@
 
 T7164.hs:8:1:
-    Multiple declarations of `derp'
+    Multiple declarations of ‛derp’
     Declared at: T7164.hs:5:5
                  T7164.hs:8:1
diff --git a/tests/rename/should_fail/T7338.stderr b/tests/rename/should_fail/T7338.stderr
index e2a92d3df..b1e6e5c80 100644
--- a/tests/rename/should_fail/T7338.stderr
+++ b/tests/rename/should_fail/T7338.stderr
@@ -1,6 +1,6 @@
 
 T7338.hs:4:1:
-    Duplicate type signatures for `a'
+    Duplicate type signatures for ‛a’
     at T7338.hs:3:1
        T7338.hs:3:4
        T7338.hs:4:1
diff --git a/tests/rename/should_fail/T7338a.stderr b/tests/rename/should_fail/T7338a.stderr
index 58807dc3b..b4b00a359 100644
--- a/tests/rename/should_fail/T7338a.stderr
+++ b/tests/rename/should_fail/T7338a.stderr
@@ -1,10 +1,10 @@
 
 T7338a.hs:7:4:
-    Duplicate type signatures for `a'
+    Duplicate type signatures for ‛a’
     at T7338a.hs:3:1
        T7338a.hs:7:4
 
 T7338a.hs:10:1:
-    Duplicate type signatures for `c'
+    Duplicate type signatures for ‛c’
     at T7338a.hs:7:1
        T7338a.hs:10:1
diff --git a/tests/rename/should_fail/T7454.stderr b/tests/rename/should_fail/T7454.stderr
index 4f68ca4b9..a8d11886e 100644
--- a/tests/rename/should_fail/T7454.stderr
+++ b/tests/rename/should_fail/T7454.stderr
@@ -1,3 +1,3 @@
 
 T7454.hs:5:1: Warning:
-    The import of `Arrow' from module `Control.Arrow' is redundant
+    The import of ‛Arrow’ from module ‛Control.Arrow’ is redundant
diff --git a/tests/rename/should_fail/mc13.stderr b/tests/rename/should_fail/mc13.stderr
index 82f8dd5f1..3cf06955a 100644
--- a/tests/rename/should_fail/mc13.stderr
+++ b/tests/rename/should_fail/mc13.stderr
@@ -1,2 +1,2 @@
 
-mc13.hs:12:37: Not in scope: `f'
+mc13.hs:12:37: Not in scope: ‛f’
diff --git a/tests/rename/should_fail/mc14.stderr b/tests/rename/should_fail/mc14.stderr
index 1eadb9d4b..28d2ca224 100644
--- a/tests/rename/should_fail/mc14.stderr
+++ b/tests/rename/should_fail/mc14.stderr
@@ -1,2 +1,2 @@
 
-mc14.hs:14:49: Not in scope: `f'
+mc14.hs:14:49: Not in scope: ‛f’
diff --git a/tests/rename/should_fail/rn_dup.stderr b/tests/rename/should_fail/rn_dup.stderr
index e7859ea82..223985f76 100644
--- a/tests/rename/should_fail/rn_dup.stderr
+++ b/tests/rename/should_fail/rn_dup.stderr
@@ -1,22 +1,22 @@
 
 rn_dup.hs:9:10:
-    Multiple declarations of `MkT'
+    Multiple declarations of ‛MkT’
     Declared at: rn_dup.hs:7:10
                  rn_dup.hs:7:16
                  rn_dup.hs:9:10
 
 rn_dup.hs:12:16:
-    Multiple declarations of `rf'
+    Multiple declarations of ‛rf’
     Declared at: rn_dup.hs:11:16
                  rn_dup.hs:11:27
                  rn_dup.hs:12:16
 
 rn_dup.hs:17:8:
-    Multiple declarations of `CT'
+    Multiple declarations of ‛CT’
     Declared at: rn_dup.hs:15:8
                  rn_dup.hs:17:8
 
 rn_dup.hs:18:3:
-    Multiple declarations of `f'
+    Multiple declarations of ‛f’
     Declared at: rn_dup.hs:16:3
                  rn_dup.hs:18:3
diff --git a/tests/rename/should_fail/rnfail001.stderr b/tests/rename/should_fail/rnfail001.stderr
index 5414f93f2..d8baefcb4 100644
--- a/tests/rename/should_fail/rnfail001.stderr
+++ b/tests/rename/should_fail/rnfail001.stderr
@@ -1,6 +1,6 @@
 
 rnfail001.hs:3:3:
-    Conflicting definitions for `x'
+    Conflicting definitions for ‛x’
     Bound at: rnfail001.hs:3:3
               rnfail001.hs:3:5
-    In an equation for `f'
+    In an equation for ‛f’
diff --git a/tests/rename/should_fail/rnfail002.stderr b/tests/rename/should_fail/rnfail002.stderr
index 6f7313774..6c15ef103 100644
--- a/tests/rename/should_fail/rnfail002.stderr
+++ b/tests/rename/should_fail/rnfail002.stderr
@@ -1,5 +1,5 @@
 
 rnfail002.hs:6:1:
-    Multiple declarations of `y'
+    Multiple declarations of ‛y’
     Declared at: rnfail002.hs:5:1
                  rnfail002.hs:6:1
diff --git a/tests/rename/should_fail/rnfail003.stderr b/tests/rename/should_fail/rnfail003.stderr
index aab591141..048233262 100644
--- a/tests/rename/should_fail/rnfail003.stderr
+++ b/tests/rename/should_fail/rnfail003.stderr
@@ -1,5 +1,5 @@
 
 rnfail003.hs:4:1:
-    Multiple declarations of `f'
+    Multiple declarations of ‛f’
     Declared at: rnfail003.hs:2:1
                  rnfail003.hs:4:1
diff --git a/tests/rename/should_fail/rnfail004.stderr b/tests/rename/should_fail/rnfail004.stderr
index edff58cf6..23e22fe28 100644
--- a/tests/rename/should_fail/rnfail004.stderr
+++ b/tests/rename/should_fail/rnfail004.stderr
@@ -1,10 +1,10 @@
 
 rnfail004.hs:6:5:
-    Conflicting definitions for `a'
+    Conflicting definitions for ‛a’
     Bound at: rnfail004.hs:6:5
               rnfail004.hs:7:10
 
 rnfail004.hs:7:6:
-    Conflicting definitions for `b'
+    Conflicting definitions for ‛b’
     Bound at: rnfail004.hs:7:6
               rnfail004.hs:8:8
diff --git a/tests/rename/should_fail/rnfail007.stderr b/tests/rename/should_fail/rnfail007.stderr
index a00dc892d..316e141bd 100644
--- a/tests/rename/should_fail/rnfail007.stderr
+++ b/tests/rename/should_fail/rnfail007.stderr
@@ -1,3 +1,3 @@
 
 rnfail007.hs:1:1:
-    The function `main' is not defined in module `Main'
+    The function ‛main’ is not defined in module ‛Main’
diff --git a/tests/rename/should_fail/rnfail008.stderr b/tests/rename/should_fail/rnfail008.stderr
index 91818fc65..f565d8799 100644
--- a/tests/rename/should_fail/rnfail008.stderr
+++ b/tests/rename/should_fail/rnfail008.stderr
@@ -1,2 +1,2 @@
 
-rnfail008.hs:18:9: `op3' is not a (visible) method of class `K'
+rnfail008.hs:18:9: ‛op3’ is not a (visible) method of class ‛K’
diff --git a/tests/rename/should_fail/rnfail009.stderr b/tests/rename/should_fail/rnfail009.stderr
index 358c17afe..9f5e98ecb 100644
--- a/tests/rename/should_fail/rnfail009.stderr
+++ b/tests/rename/should_fail/rnfail009.stderr
@@ -1,5 +1,5 @@
 
 rnfail009.hs:5:10:
-    Multiple declarations of `A'
+    Multiple declarations of ‛A’
     Declared at: rnfail009.hs:3:10
                  rnfail009.hs:5:10
diff --git a/tests/rename/should_fail/rnfail010.stderr b/tests/rename/should_fail/rnfail010.stderr
index d0e7c835a..d2f7a9385 100644
--- a/tests/rename/should_fail/rnfail010.stderr
+++ b/tests/rename/should_fail/rnfail010.stderr
@@ -1,5 +1,5 @@
 
 rnfail010.hs:6:1:
-    Multiple declarations of `f'
+    Multiple declarations of ‛f’
     Declared at: rnfail010.hs:2:1
                  rnfail010.hs:6:1
diff --git a/tests/rename/should_fail/rnfail011.stderr b/tests/rename/should_fail/rnfail011.stderr
index 7e7d02abf..544455a08 100644
--- a/tests/rename/should_fail/rnfail011.stderr
+++ b/tests/rename/should_fail/rnfail011.stderr
@@ -1,5 +1,5 @@
 
 rnfail011.hs:6:6:
-    Multiple declarations of `A'
+    Multiple declarations of ‛A’
     Declared at: rnfail011.hs:2:6
                  rnfail011.hs:6:6
diff --git a/tests/rename/should_fail/rnfail012.stderr b/tests/rename/should_fail/rnfail012.stderr
index 82dbd3a76..83b1e1d2f 100644
--- a/tests/rename/should_fail/rnfail012.stderr
+++ b/tests/rename/should_fail/rnfail012.stderr
@@ -1,5 +1,5 @@
 
 rnfail012.hs:8:7:
-    Multiple declarations of `A'
+    Multiple declarations of ‛A’
     Declared at: rnfail012.hs:2:7
                  rnfail012.hs:8:7
diff --git a/tests/rename/should_fail/rnfail013.stderr b/tests/rename/should_fail/rnfail013.stderr
index 3ec4f43cb..eebfaa2e0 100644
--- a/tests/rename/should_fail/rnfail013.stderr
+++ b/tests/rename/should_fail/rnfail013.stderr
@@ -1,5 +1,5 @@
 
 rnfail013.hs:7:11:
-    Multiple declarations of `MkT'
+    Multiple declarations of ‛MkT’
     Declared at: rnfail013.hs:5:11
                  rnfail013.hs:7:11
diff --git a/tests/rename/should_fail/rnfail015.stderr b/tests/rename/should_fail/rnfail015.stderr
index dcb54f5b9..999a7acab 100644
--- a/tests/rename/should_fail/rnfail015.stderr
+++ b/tests/rename/should_fail/rnfail015.stderr
@@ -1,5 +1,5 @@
 
 rnfail015.hs:14:9:
-    Multiple declarations of `TokLiteral'
+    Multiple declarations of ‛TokLiteral’
     Declared at: rnfail015.hs:8:9
                  rnfail015.hs:14:9
diff --git a/tests/rename/should_fail/rnfail017.stderr b/tests/rename/should_fail/rnfail017.stderr
index f04b1d099..a89b6be1c 100644
--- a/tests/rename/should_fail/rnfail017.stderr
+++ b/tests/rename/should_fail/rnfail017.stderr
@@ -1,8 +1,8 @@
 
 rnfail017.hs:5:10:
     Precedence parsing error
-        cannot mix `+' [infixl 6] and prefix `-' [infixl 6] in the same infix expression
+        cannot mix ‛+’ [infixl 6] and prefix `-' [infixl 6] in the same infix expression
 
 rnfail017.hs:6:10:
     Precedence parsing error
-        cannot mix `*' [infixl 7] and prefix `-' [infixl 6] in the same infix expression
+        cannot mix ‛*’ [infixl 7] and prefix `-' [infixl 6] in the same infix expression
diff --git a/tests/rename/should_fail/rnfail018.stderr b/tests/rename/should_fail/rnfail018.stderr
index 3bae3eb52..7658b18ba 100644
--- a/tests/rename/should_fail/rnfail018.stderr
+++ b/tests/rename/should_fail/rnfail018.stderr
@@ -1,8 +1,8 @@
 
-rnfail018.hs:12:37: Not in scope: type variable `a'
+rnfail018.hs:12:37: Not in scope: type variable ‛a’
 
-rnfail018.hs:12:42: Not in scope: type variable `m'
+rnfail018.hs:12:42: Not in scope: type variable ‛m’
 
-rnfail018.hs:12:47: Not in scope: type variable `m'
+rnfail018.hs:12:47: Not in scope: type variable ‛m’
 
-rnfail018.hs:12:49: Not in scope: type variable `a'
+rnfail018.hs:12:49: Not in scope: type variable ‛a’
diff --git a/tests/rename/should_fail/rnfail019.stderr b/tests/rename/should_fail/rnfail019.stderr
index f990e2d2c..449da500e 100644
--- a/tests/rename/should_fail/rnfail019.stderr
+++ b/tests/rename/should_fail/rnfail019.stderr
@@ -1,6 +1,6 @@
 
 rnfail019.hs:5:9:
-    The operator `:' [infixr 5] of a section
+    The operator ‛:’ [infixr 5] of a section
         must have lower precedence than that of the operand,
-          namely `:' [infixr 5]
-        in the section: `x : y :'
+          namely ‛:’ [infixr 5]
+        in the section: ‛x : y :’
diff --git a/tests/rename/should_fail/rnfail022.stderr b/tests/rename/should_fail/rnfail022.stderr
index 011d6790d..d443cec99 100644
--- a/tests/rename/should_fail/rnfail022.stderr
+++ b/tests/rename/should_fail/rnfail022.stderr
@@ -1,4 +1,4 @@
 
 rnfail022.hs:8:5:
-    Not in scope: `intersperse'
-    Perhaps you meant `L.intersperse' (imported from Data.List)
+    Not in scope: ‛intersperse’
+    Perhaps you meant ‛L.intersperse’ (imported from Data.List)
diff --git a/tests/rename/should_fail/rnfail023.stderr b/tests/rename/should_fail/rnfail023.stderr
index ec9d81ab7..7fa68c3f1 100644
--- a/tests/rename/should_fail/rnfail023.stderr
+++ b/tests/rename/should_fail/rnfail023.stderr
@@ -1,9 +1,9 @@
 
 rnfail023.hs:7:1:
-    The type signature for `f' lacks an accompanying binding
+    The type signature for ‛f’ lacks an accompanying binding
 
 rnfail023.hs:8:12:
-    The INLINE pragma for `f' lacks an accompanying binding
+    The INLINE pragma for ‛f’ lacks an accompanying binding
 
 rnfail023.hs:14:7:
-    The type signature for `g' lacks an accompanying binding
+    The type signature for ‛g’ lacks an accompanying binding
diff --git a/tests/rename/should_fail/rnfail024.stderr b/tests/rename/should_fail/rnfail024.stderr
index 19b9f3392..f3e6cbe61 100644
--- a/tests/rename/should_fail/rnfail024.stderr
+++ b/tests/rename/should_fail/rnfail024.stderr
@@ -1,6 +1,6 @@
 
 rnfail024.hs:3:1:
-    The type signature for `sig_without_a_defn'
+    The type signature for ‛sig_without_a_defn’
       lacks an accompanying binding
 
-rnfail024.hs:6:5: Not in scope: `sig_without_a_defn'
+rnfail024.hs:6:5: Not in scope: ‛sig_without_a_defn’
diff --git a/tests/rename/should_fail/rnfail025.stderr b/tests/rename/should_fail/rnfail025.stderr
index 4c2e25a07..bdb07ad5c 100644
--- a/tests/rename/should_fail/rnfail025.stderr
+++ b/tests/rename/should_fail/rnfail025.stderr
@@ -1,4 +1,4 @@
 
 rnfail025.hs:3:1:
-    The type signature for `sig_without_a_defn'
+    The type signature for ‛sig_without_a_defn’
       lacks an accompanying binding
diff --git a/tests/rename/should_fail/rnfail026.stderr b/tests/rename/should_fail/rnfail026.stderr
index 3a4ae4922..f082327d5 100644
--- a/tests/rename/should_fail/rnfail026.stderr
+++ b/tests/rename/should_fail/rnfail026.stderr
@@ -1,9 +1,9 @@
 
 rnfail026.hs:16:35:
-    The first argument of `Monad' should have kind `* -> *',
-      but `Set a' has kind `*'
-    In the instance declaration for `Monad (forall a. Eq a => Set a)'
+    The first argument of ‛Monad’ should have kind ‛* -> *’,
+      but ‛Set a’ has kind ‛*’
+    In the instance declaration for ‛Monad (forall a. Eq a => Set a)’
 
 rnfail026.hs:19:10:
     Illegal polymorphic or qualified type: forall a. [a]
-    In the instance declaration for `Eq (forall a. [a])'
+    In the instance declaration for ‛Eq (forall a. [a])’
diff --git a/tests/rename/should_fail/rnfail027.stderr b/tests/rename/should_fail/rnfail027.stderr
index 31214a1a4..062600ac8 100644
--- a/tests/rename/should_fail/rnfail027.stderr
+++ b/tests/rename/should_fail/rnfail027.stderr
@@ -1,3 +1,3 @@
 
 rnfail027.hs:5:10:
-    The fixity signature for `wibble' lacks an accompanying binding
+    The fixity signature for ‛wibble’ lacks an accompanying binding
diff --git a/tests/rename/should_fail/rnfail029.stderr b/tests/rename/should_fail/rnfail029.stderr
index 360a9aac9..671b035c4 100644
--- a/tests/rename/should_fail/rnfail029.stderr
+++ b/tests/rename/should_fail/rnfail029.stderr
@@ -1,8 +1,8 @@
 
 rnfail029.hs:2:36:
-    Conflicting exports for `map':
-       `Data.List.map' exports `Data.List.map'
-         imported qualified from `Data.List' at rnfail029.hs:3:1-26
-         (and originally defined in `GHC.Base')
-       `module ShouldFail' exports `ShouldFail.map'
+    Conflicting exports for ‛map’:
+       ‛Data.List.map’ exports ‛Data.List.map’
+         imported qualified from ‛Data.List’ at rnfail029.hs:3:1-26
+         (and originally defined in ‛GHC.Base’)
+       ‛module ShouldFail’ exports ‛ShouldFail.map’
          defined at rnfail029.hs:4:1
diff --git a/tests/rename/should_fail/rnfail030.stderr b/tests/rename/should_fail/rnfail030.stderr
index 749206a81..cbac79dc4 100644
--- a/tests/rename/should_fail/rnfail030.stderr
+++ b/tests/rename/should_fail/rnfail030.stderr
@@ -1,2 +1,2 @@
 
-rnfail030.hs:2:21: Not in scope: `Data.List.map'
+rnfail030.hs:2:21: Not in scope: ‛Data.List.map’
diff --git a/tests/rename/should_fail/rnfail031.stderr b/tests/rename/should_fail/rnfail031.stderr
index ad04461dc..eee31a2ec 100644
--- a/tests/rename/should_fail/rnfail031.stderr
+++ b/tests/rename/should_fail/rnfail031.stderr
@@ -1,2 +1,2 @@
 
-rnfail031.hs:2:21: Not in scope: `Data.List.map'
+rnfail031.hs:2:21: Not in scope: ‛Data.List.map’
diff --git a/tests/rename/should_fail/rnfail032.stderr b/tests/rename/should_fail/rnfail032.stderr
index ea80202dd..f4cf86597 100644
--- a/tests/rename/should_fail/rnfail032.stderr
+++ b/tests/rename/should_fail/rnfail032.stderr
@@ -1,7 +1,7 @@
 
 rnfail032.hs:2:21:
-    Not in scope: `Data.List.map'
+    Not in scope: ‛Data.List.map’
     Perhaps you meant one of these:
-      `Data.List.zip' (imported from Data.List),
-      `Data.List.sum' (imported from Data.List),
-      `Data.List.all' (imported from Data.List)
+      ‛Data.List.zip’ (imported from Data.List),
+      ‛Data.List.sum’ (imported from Data.List),
+      ‛Data.List.all’ (imported from Data.List)
diff --git a/tests/rename/should_fail/rnfail033.stderr b/tests/rename/should_fail/rnfail033.stderr
index c9abd0f87..4a2e76222 100644
--- a/tests/rename/should_fail/rnfail033.stderr
+++ b/tests/rename/should_fail/rnfail033.stderr
@@ -1,7 +1,7 @@
 
 rnfail033.hs:2:21:
-    Not in scope: `Data.List.map'
+    Not in scope: ‛Data.List.map’
     Perhaps you meant one of these:
-      `Data.List.zip' (imported from Data.List),
-      `Data.List.sum' (imported from Data.List),
-      `Data.List.all' (imported from Data.List)
+      ‛Data.List.zip’ (imported from Data.List),
+      ‛Data.List.sum’ (imported from Data.List),
+      ‛Data.List.all’ (imported from Data.List)
diff --git a/tests/rename/should_fail/rnfail034.stderr b/tests/rename/should_fail/rnfail034.stderr
index 2ec0a3b8e..6c9b49ec4 100644
--- a/tests/rename/should_fail/rnfail034.stderr
+++ b/tests/rename/should_fail/rnfail034.stderr
@@ -2,5 +2,5 @@
 rnfail034.hs:4:11: Qualified name in binding position: M.y
 
 rnfail034.hs:4:26:
-    Not in scope: `M.y'
-    Perhaps you meant `M.g' (line 4)
+    Not in scope: ‛M.y’
+    Perhaps you meant ‛M.g’ (line 4)
diff --git a/tests/rename/should_fail/rnfail035.stderr b/tests/rename/should_fail/rnfail035.stderr
index 83eb2d85e..35dd128e2 100644
--- a/tests/rename/should_fail/rnfail035.stderr
+++ b/tests/rename/should_fail/rnfail035.stderr
@@ -1,2 +1,2 @@
 
-rnfail035.hs:2:21: Not in scope: type constructor or class `C'
+rnfail035.hs:2:21: Not in scope: type constructor or class ‛C’
diff --git a/tests/rename/should_fail/rnfail040.stderr b/tests/rename/should_fail/rnfail040.stderr
index cacdaa8d8..1ff86a826 100644
--- a/tests/rename/should_fail/rnfail040.stderr
+++ b/tests/rename/should_fail/rnfail040.stderr
@@ -1,8 +1,8 @@
 
 rnfail040.hs:7:12:
-    Conflicting exports for `nub':
-       `module M' exports `M.nub'
-         imported from `Data.List' at rnfail040.hs:10:2-22
-       `module M' exports `T.nub'
-         imported from `Rnfail040_A' at rnfail040.hs:11:2-24
+    Conflicting exports for ‛nub’:
+       ‛module M’ exports ‛M.nub’
+         imported from ‛Data.List’ at rnfail040.hs:10:2-22
+       ‛module M’ exports ‛T.nub’
+         imported from ‛Rnfail040_A’ at rnfail040.hs:11:2-24
          (and originally defined at Rnfail040_A.hs:2:3-5)
diff --git a/tests/rename/should_fail/rnfail041.stderr b/tests/rename/should_fail/rnfail041.stderr
index 0c5c60d4d..bebccf217 100644
--- a/tests/rename/should_fail/rnfail041.stderr
+++ b/tests/rename/should_fail/rnfail041.stderr
@@ -1,6 +1,6 @@
 
 rnfail041.hs:4:1:
-    The type signature for `h' lacks an accompanying binding
+    The type signature for ‛h’ lacks an accompanying binding
 
 rnfail041.hs:5:1:
-    The type signature for `j' lacks an accompanying binding
+    The type signature for ‛j’ lacks an accompanying binding
diff --git a/tests/rename/should_fail/rnfail043.stderr b/tests/rename/should_fail/rnfail043.stderr
index 428c1944d..61cef734f 100644
--- a/tests/rename/should_fail/rnfail043.stderr
+++ b/tests/rename/should_fail/rnfail043.stderr
@@ -1,5 +1,5 @@
 
 rnfail043.hs:10:1:
-    Multiple declarations of `f'
+    Multiple declarations of ‛f’
     Declared at: rnfail043.hs:6:1
                  rnfail043.hs:10:1
diff --git a/tests/rename/should_fail/rnfail044.stderr b/tests/rename/should_fail/rnfail044.stderr
index 48be6944d..fdae4e17c 100644
--- a/tests/rename/should_fail/rnfail044.stderr
+++ b/tests/rename/should_fail/rnfail044.stderr
@@ -1,7 +1,7 @@
 
 rnfail044.hs:5:12:
-    Ambiguous occurrence `splitAt'
-    It could refer to either `A.splitAt', defined at rnfail044.hs:8:3
-                          or `Data.List.splitAt',
-                             imported from `Prelude' at rnfail044.hs:5:8
-                             (and originally defined in `GHC.List')
+    Ambiguous occurrence ‛splitAt’
+    It could refer to either ‛A.splitAt’, defined at rnfail044.hs:8:3
+                          or ‛Data.List.splitAt’,
+                             imported from ‛Prelude’ at rnfail044.hs:5:8
+                             (and originally defined in ‛GHC.List’)
diff --git a/tests/rename/should_fail/rnfail045.stderr b/tests/rename/should_fail/rnfail045.stderr
index d8c80008c..9cba624ac 100644
--- a/tests/rename/should_fail/rnfail045.stderr
+++ b/tests/rename/should_fail/rnfail045.stderr
@@ -1,10 +1,10 @@
 
 rnfail045.hs:5:1:
-    Equations for `op1' have different numbers of arguments
+    Equations for ‛op1’ have different numbers of arguments
       rnfail045.hs:5:1-16
       rnfail045.hs:6:1-13
 
 rnfail045.hs:8:1:
-    Equations for `op2' have different numbers of arguments
+    Equations for ‛op2’ have different numbers of arguments
       rnfail045.hs:8:1-13
       rnfail045.hs:9:1-16
diff --git a/tests/rename/should_fail/rnfail048.stderr b/tests/rename/should_fail/rnfail048.stderr
index 64cd89d28..7dd35d12a 100644
--- a/tests/rename/should_fail/rnfail048.stderr
+++ b/tests/rename/should_fail/rnfail048.stderr
@@ -1,9 +1,9 @@
-
-rnfail048.hs:11:12:
-    Duplicate INLINE pragmas for `foo'
-    at rnfail048.hs:6:17-19
-       rnfail048.hs:7:18-20
-       rnfail048.hs:8:14-16
-       rnfail048.hs:9:15-17
-       rnfail048.hs:10:16-18
-       rnfail048.hs:11:12-14
+
+rnfail048.hs:11:12:
+    Duplicate INLINE pragmas for ‛foo’
+    at rnfail048.hs:6:17-19
+       rnfail048.hs:7:18-20
+       rnfail048.hs:8:14-16
+       rnfail048.hs:9:15-17
+       rnfail048.hs:10:16-18
+       rnfail048.hs:11:12-14
diff --git a/tests/rename/should_fail/rnfail049.stderr b/tests/rename/should_fail/rnfail049.stderr
index 6b753fbf2..8f08407ac 100644
--- a/tests/rename/should_fail/rnfail049.stderr
+++ b/tests/rename/should_fail/rnfail049.stderr
@@ -1,2 +1,2 @@
 
-rnfail049.hs:12:49: Not in scope: `f'
+rnfail049.hs:12:49: Not in scope: ‛f’
diff --git a/tests/rename/should_fail/rnfail050.stderr b/tests/rename/should_fail/rnfail050.stderr
index d097fc5b4..bbd122543 100644
--- a/tests/rename/should_fail/rnfail050.stderr
+++ b/tests/rename/should_fail/rnfail050.stderr
@@ -1,2 +1,2 @@
 
-rnfail050.hs:10:37: Not in scope: `f'
+rnfail050.hs:10:37: Not in scope: ‛f’
diff --git a/tests/rename/should_fail/rnfail053.stderr b/tests/rename/should_fail/rnfail053.stderr
index 47f44c446..8dc85ab49 100644
--- a/tests/rename/should_fail/rnfail053.stderr
+++ b/tests/rename/should_fail/rnfail053.stderr
@@ -1,4 +1,4 @@
 
 rnfail053.hs:5:10:
-    Not a data constructor: `forall'
+    Not a data constructor: ‛forall’
     Perhaps you intended to use -XExistentialQuantification
diff --git a/tests/rename/should_fail/rnfail054.stderr b/tests/rename/should_fail/rnfail054.stderr
index ab952aade..ef5b6d55b 100644
--- a/tests/rename/should_fail/rnfail054.stderr
+++ b/tests/rename/should_fail/rnfail054.stderr
@@ -1,5 +1,5 @@
 
 rnfail054.hs:6:13:
-    `foo' is not a record selector
+    ‛foo’ is not a record selector
     In the expression: x {foo = 1}
-    In an equation for `foo': foo x = x {foo = 1}
+    In an equation for ‛foo’: foo x = x {foo = 1}
diff --git a/tests/rename/should_fail/rnfail055.stderr b/tests/rename/should_fail/rnfail055.stderr
index cd559cca9..5f7602195 100644
--- a/tests/rename/should_fail/rnfail055.stderr
+++ b/tests/rename/should_fail/rnfail055.stderr
@@ -6,22 +6,22 @@ RnFail055.hs-boot:1:73: Warning:
     -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
 RnFail055.hs-boot:4:1:
-    Identifier `f1' has conflicting definitions in the module and its hs-boot file
+    Identifier ‛f1’ has conflicting definitions in the module and its hs-boot file
     Main module: f1 :: Int -> Float
     Boot file:   f1 :: Float -> Int
 
 RnFail055.hs-boot:6:6:
-    Type constructor `S1' has conflicting definitions in the module and its hs-boot file
+    Type constructor ‛S1’ has conflicting definitions in the module and its hs-boot file
     Main module: type S1 a b = (a, b)
     Boot file:   type S1 a b c = (a, b)
 
 RnFail055.hs-boot:8:6:
-    Type constructor `S2' has conflicting definitions in the module and its hs-boot file
+    Type constructor ‛S2’ has conflicting definitions in the module and its hs-boot file
     Main module: type S2 a b = forall a1. (a1, b)
     Boot file:   type S2 a b = forall b1. (a, b1)
 
 RnFail055.hs-boot:12:6:
-    Type constructor `T1' has conflicting definitions in the module and its hs-boot file
+    Type constructor ‛T1’ has conflicting definitions in the module and its hs-boot file
     Main module: data T1 a b
                      No C type associated
                      RecFlag Recursive, Promotable
@@ -34,7 +34,7 @@ RnFail055.hs-boot:12:6:
                      FamilyInstance: none
 
 RnFail055.hs-boot:14:16:
-    Type constructor `T2' has conflicting definitions in the module and its hs-boot file
+    Type constructor ‛T2’ has conflicting definitions in the module and its hs-boot file
     Main module: data Eq b => T2 a b
                      No C type associated
                      RecFlag Recursive, Promotable
@@ -53,7 +53,7 @@ RnFail055.hs-boot:17:12:
     T3' is exported by the hs-boot file, but not exported by the module
 
 RnFail055.hs-boot:21:6:
-    Type constructor `T5' has conflicting definitions in the module and its hs-boot file
+    Type constructor ‛T5’ has conflicting definitions in the module and its hs-boot file
     Main module: data T5 a
                      No C type associated
                      RecFlag Recursive, Promotable
@@ -66,7 +66,7 @@ RnFail055.hs-boot:21:6:
                      FamilyInstance: none
 
 RnFail055.hs-boot:23:6:
-    Type constructor `T6' has conflicting definitions in the module and its hs-boot file
+    Type constructor ‛T6’ has conflicting definitions in the module and its hs-boot file
     Main module: data T6
                      No C type associated
                      RecFlag Recursive, Not promotable
@@ -79,7 +79,7 @@ RnFail055.hs-boot:23:6:
                      FamilyInstance: none
 
 RnFail055.hs-boot:25:6:
-    Type constructor `T7' has conflicting definitions in the module and its hs-boot file
+    Type constructor ‛T7’ has conflicting definitions in the module and its hs-boot file
     Main module: data T7 a
                      No C type associated
                      RecFlag Recursive, Promotable
@@ -95,7 +95,7 @@ RnFail055.hs-boot:27:22:
     RnFail055.m1 is exported by the hs-boot file, but not exported by the module
 
 RnFail055.hs-boot:28:7:
-    Class `C2' has conflicting definitions in the module and its hs-boot file
+    Class ‛C2’ has conflicting definitions in the module and its hs-boot file
     Main module: class C2 a b
                      RecFlag Recursive
                      m2 :: a -> b m2' :: a -> b
@@ -104,6 +104,6 @@ RnFail055.hs-boot:28:7:
                      m2 :: a -> b
 
 RnFail055.hs-boot:29:24:
-    Class `C3' has conflicting definitions in the module and its hs-boot file
+    Class ‛C3’ has conflicting definitions in the module and its hs-boot file
     Main module: class (Eq a, Ord a) => C3 a RecFlag Recursive
     Boot file:   class (Ord a, Eq a) => C3 a RecFlag NonRecursive
diff --git a/tests/rename/should_fail/rnfail057.stderr b/tests/rename/should_fail/rnfail057.stderr
index 79a5ac7ed..682365654 100644
--- a/tests/rename/should_fail/rnfail057.stderr
+++ b/tests/rename/should_fail/rnfail057.stderr
@@ -1,3 +1,3 @@
 
 rnfail057.hs:5:16:
-    Not in scope: type constructor or class `DontExistKind'
+    Not in scope: type constructor or class ‛DontExistKind’
diff --git a/tests/safeHaskell/flags/SafeFlags22.stderr b/tests/safeHaskell/flags/SafeFlags22.stderr
index abef5a8b8..784f0472b 100644
--- a/tests/safeHaskell/flags/SafeFlags22.stderr
+++ b/tests/safeHaskell/flags/SafeFlags22.stderr
@@ -1,6 +1,6 @@
 
 SafeFlags22.hs:1:16: Warning:
-    `SafeFlags22' has been inferred as unsafe!
+    ‛SafeFlags22’ has been inferred as unsafe!
     Reason:
         SafeFlags22.hs:7:1:
             System.IO.Unsafe: Can't be safely imported!
diff --git a/tests/safeHaskell/flags/SafeFlags23.stderr b/tests/safeHaskell/flags/SafeFlags23.stderr
index 410b8a1ba..8af4d95f5 100644
--- a/tests/safeHaskell/flags/SafeFlags23.stderr
+++ b/tests/safeHaskell/flags/SafeFlags23.stderr
@@ -1,6 +1,6 @@
 
 SafeFlags23.hs:1:16: Warning:
-    `SafeFlags22' has been inferred as unsafe!
+    ‛SafeFlags22’ has been inferred as unsafe!
     Reason:
         SafeFlags23.hs:7:1:
             System.IO.Unsafe: Can't be safely imported!
diff --git a/tests/safeHaskell/flags/SafeFlags25.stderr b/tests/safeHaskell/flags/SafeFlags25.stderr
index 3a1e97147..3e1d7b360 100644
--- a/tests/safeHaskell/flags/SafeFlags25.stderr
+++ b/tests/safeHaskell/flags/SafeFlags25.stderr
@@ -1,3 +1,3 @@
 
 SafeFlags25.hs:1:16: Warning:
-    `SafeFlags25' has been inferred as safe!
+    ‛SafeFlags25’ has been inferred as safe!
diff --git a/tests/safeHaskell/flags/SafeFlags26.stderr b/tests/safeHaskell/flags/SafeFlags26.stderr
index fd5b341d1..640f5be41 100644
--- a/tests/safeHaskell/flags/SafeFlags26.stderr
+++ b/tests/safeHaskell/flags/SafeFlags26.stderr
@@ -1,6 +1,6 @@
 
 SafeFlags26.hs:1:16: Warning:
-    `SafeFlags26' has been inferred as safe!
+    ‛SafeFlags26’ has been inferred as safe!
 
 <no location info>: 
 Failing due to -Werror.
diff --git a/tests/safeHaskell/ghci/p10.stderr b/tests/safeHaskell/ghci/p10.stderr
index 768948984..71ace7356 100644
--- a/tests/safeHaskell/ghci/p10.stderr
+++ b/tests/safeHaskell/ghci/p10.stderr
@@ -1,2 +1,2 @@
 
-<interactive>:10:1: Not in scope: `b'
+<interactive>:10:1: Not in scope: ‛b’
diff --git a/tests/safeHaskell/ghci/p13.stderr b/tests/safeHaskell/ghci/p13.stderr
index 5e31e4343..226aac2f0 100644
--- a/tests/safeHaskell/ghci/p13.stderr
+++ b/tests/safeHaskell/ghci/p13.stderr
@@ -1,7 +1,7 @@
 
 <interactive>:12:1:
     Unsafe overlapping instances for Pos [Int]
-      arising from a use of `res'
+      arising from a use of ‛res’
     The matching instance is:
       instance [overlap ok] [safe] Pos [Int]
         -- Defined at <interactive>:10:10
@@ -10,4 +10,4 @@
     overlaps the following instances from different modules:
       instance [overlap ok] [safe] Pos [a] -- Defined at P13_A.hs:6:10
     In the expression: res [1 :: Int, 2 :: Int]
-    In an equation for `it': it = res [1 :: Int, 2 :: Int]
+    In an equation for ‛it’: it = res [1 :: Int, 2 :: Int]
diff --git a/tests/safeHaskell/ghci/p15.stderr b/tests/safeHaskell/ghci/p15.stderr
index f50d460ed..0bc16dfbf 100644
--- a/tests/safeHaskell/ghci/p15.stderr
+++ b/tests/safeHaskell/ghci/p15.stderr
@@ -1,9 +1,9 @@
 
 Top level: Warning:
-    Module `Data.OldTypeable' is deprecated: Use Data.Typeable instead
+    Module ‛Data.OldTypeable’ is deprecated: Use Data.Typeable instead
 
 <interactive>:10:36: Warning:
-    In the use of type constructor or class `Typeable'
+    In the use of type constructor or class ‛Typeable’
     (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
     Deprecated: "Use Data.Typeable.Internal instead"
 
@@ -11,8 +11,8 @@ Top level: Warning:
     Can't create hand written instances of Typeable in Safe Haskell! Can only derive them
 
 <interactive>:22:22:
-    No instance for (Typeable G) arising from a use of `cast'
+    No instance for (Typeable G) arising from a use of ‛cast’
     In the expression: (cast y) :: Maybe H
     In a pattern binding: (Just y_as_H) = (cast y) :: Maybe H
 
-<interactive>:23:1: Not in scope: `y_as_H'
+<interactive>:23:1: Not in scope: ‛y_as_H’
diff --git a/tests/safeHaskell/ghci/p16.stderr b/tests/safeHaskell/ghci/p16.stderr
index 33602c70a..373920e57 100644
--- a/tests/safeHaskell/ghci/p16.stderr
+++ b/tests/safeHaskell/ghci/p16.stderr
@@ -3,13 +3,13 @@
     -XGeneralizedNewtypeDeriving is not allowed in Safe Haskell; ignoring -XGeneralizedNewtypeDeriving
 
 <interactive>:16:29:
-    Can't make a derived instance of `Op T2':
-      `Op' is not a derivable class
+    Can't make a derived instance of ‛Op T2’:
+      ‛Op’ is not a derivable class
       Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension
-    In the newtype declaration for `T2'
+    In the newtype declaration for ‛T2’
 
 <interactive>:19:9:
-    Not in scope: data constructor `T2'
-    Perhaps you meant `T1' (line 13)
+    Not in scope: data constructor ‛T2’
+    Perhaps you meant ‛T1’ (line 13)
 
-<interactive>:22:4: Not in scope: `y'
+<interactive>:22:4: Not in scope: ‛y’
diff --git a/tests/safeHaskell/ghci/p4.stderr b/tests/safeHaskell/ghci/p4.stderr
index 8ff4107af..8ff140a7b 100644
--- a/tests/safeHaskell/ghci/p4.stderr
+++ b/tests/safeHaskell/ghci/p4.stderr
@@ -1,6 +1,6 @@
 
-<interactive>:6:9: Not in scope: `System.IO.Unsafe.unsafePerformIO'
+<interactive>:6:9: Not in scope: ‛System.IO.Unsafe.unsafePerformIO’
 
-<interactive>:7:9: Not in scope: `x'
+<interactive>:7:9: Not in scope: ‛x’
 
-<interactive>:8:1: Not in scope: `y'
+<interactive>:8:1: Not in scope: ‛y’
diff --git a/tests/safeHaskell/ghci/p6.stderr b/tests/safeHaskell/ghci/p6.stderr
index b32c521b4..f46c1f815 100644
--- a/tests/safeHaskell/ghci/p6.stderr
+++ b/tests/safeHaskell/ghci/p6.stderr
@@ -6,5 +6,5 @@
       foreign import ccall safe "static sin" c_sin :: Double -> Double
 
 <interactive>:13:1:
-    Not in scope: `c_sin'
-    Perhaps you meant c_sin' (line 8)
+    Not in scope: ‛c_sin’
+    Perhaps you meant ‛c_sin'’ (line 8)
diff --git a/tests/safeHaskell/ghci/p9.stderr b/tests/safeHaskell/ghci/p9.stderr
index 768948984..71ace7356 100644
--- a/tests/safeHaskell/ghci/p9.stderr
+++ b/tests/safeHaskell/ghci/p9.stderr
@@ -1,2 +1,2 @@
 
-<interactive>:10:1: Not in scope: `b'
+<interactive>:10:1: Not in scope: ‛b’
diff --git a/tests/safeHaskell/safeInfered/UnsafeInfered07.stderr b/tests/safeHaskell/safeInfered/UnsafeInfered07.stderr
index 4a83680d5..e318319ea 100644
--- a/tests/safeHaskell/safeInfered/UnsafeInfered07.stderr
+++ b/tests/safeHaskell/safeInfered/UnsafeInfered07.stderr
@@ -1,20 +1,20 @@
 [1 of 2] Compiling UnsafeInfered07_A ( UnsafeInfered07_A.hs, UnsafeInfered07_A.o )
 
 UnsafeInfered07_A.hs:4:1: Warning:
-    Module `Data.OldTypeable' is deprecated: Use Data.Typeable instead
+    Module ‛Data.OldTypeable’ is deprecated: Use Data.Typeable instead
 
 UnsafeInfered07_A.hs:8:10: Warning:
-    In the use of type constructor or class `Typeable'
+    In the use of type constructor or class ‛Typeable’
     (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
     Deprecated: "Use Data.Typeable.Internal instead"
 
 UnsafeInfered07_A.hs:8:10: Warning:
-    In the use of type constructor or class `Typeable'
+    In the use of type constructor or class ‛Typeable’
     (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
     Deprecated: "Use Data.Typeable.Internal instead"
 
 UnsafeInfered07_A.hs:9:16: Warning:
-    In the use of `typeOf'
+    In the use of ‛typeOf’
     (imported from Data.OldTypeable, but defined in Data.OldTypeable.Internal):
     Deprecated: "Use Data.Typeable.Internal instead"
 [2 of 2] Compiling UnsafeInfered07  ( UnsafeInfered07.hs, UnsafeInfered07.o )
diff --git a/tests/safeHaskell/safeInfered/UnsafeInfered11.stderr b/tests/safeHaskell/safeInfered/UnsafeInfered11.stderr
index a6051e1b3..ec700d62f 100644
--- a/tests/safeHaskell/safeInfered/UnsafeInfered11.stderr
+++ b/tests/safeHaskell/safeInfered/UnsafeInfered11.stderr
@@ -1,7 +1,7 @@
 [1 of 2] Compiling UnsafeInfered11_A ( UnsafeInfered11_A.hs, UnsafeInfered11_A.o )
 
 UnsafeInfered11_A.hs:1:16: Warning:
-    `UnsafeInfered11_A' has been inferred as unsafe!
+    ‛UnsafeInfered11_A’ has been inferred as unsafe!
     Reason:
         UnsafeInfered11_A.hs:17:11: Warning:
             Rule "lookupx/T" ignored
diff --git a/tests/safeHaskell/safeInfered/UnsafeInfered12.stderr b/tests/safeHaskell/safeInfered/UnsafeInfered12.stderr
index 8b6ec36bb..53d7a4c32 100644
--- a/tests/safeHaskell/safeInfered/UnsafeInfered12.stderr
+++ b/tests/safeHaskell/safeInfered/UnsafeInfered12.stderr
@@ -1,6 +1,6 @@
 
 UnsafeInfered12.hs:2:16: Warning:
-    `UnsafeInfered12' has been inferred as unsafe!
+    ‛UnsafeInfered12’ has been inferred as unsafe!
     Reason:
         UnsafeInfered12.hs:1:14:
             -XTemplateHaskell is not allowed in Safe Haskell
diff --git a/tests/safeHaskell/safeLanguage/SafeLang07.stderr b/tests/safeHaskell/safeLanguage/SafeLang07.stderr
index cb081b0eb..50c0ef7e5 100644
--- a/tests/safeHaskell/safeLanguage/SafeLang07.stderr
+++ b/tests/safeHaskell/safeLanguage/SafeLang07.stderr
@@ -1,7 +1,7 @@
 
-SafeLang07.hs:2:14:
-    Warning: -XGeneralizedNewtypeDeriving is not allowed in Safe Haskell; ignoring -XGeneralizedNewtypeDeriving
+SafeLang07.hs:2:14: Warning:
+    -XGeneralizedNewtypeDeriving is not allowed in Safe Haskell; ignoring -XGeneralizedNewtypeDeriving
 
 SafeLang07.hs:15:1:
-    Failed to load interface for `SafeLang07_A'
+    Failed to load interface for ‛SafeLang07_A’
     Use -v to see a list of the files searched for.
diff --git a/tests/safeHaskell/safeLanguage/SafeLang10.stderr b/tests/safeHaskell/safeLanguage/SafeLang10.stderr
index de88221c2..a226c7974 100644
--- a/tests/safeHaskell/safeLanguage/SafeLang10.stderr
+++ b/tests/safeHaskell/safeLanguage/SafeLang10.stderr
@@ -4,7 +4,7 @@
 
 SafeLang10.hs:8:13:
     Unsafe overlapping instances for Pos [Int]
-      arising from a use of `res'
+      arising from a use of ‛res’
     The matching instance is:
       instance [overlap ok] [safe] Pos [Int]
         -- Defined at SafeLang10_B.hs:14:10
@@ -13,7 +13,7 @@ SafeLang10.hs:8:13:
     overlaps the following instances from different modules:
       instance Pos [a] -- Defined at SafeLang10_A.hs:13:10
     In the expression: res [(1 :: Int)]
-    In an equation for `r': r = res [(1 :: Int)]
+    In an equation for ‛r’: r = res [(1 :: Int)]
     In the expression:
       do { let r = res ...;
            putStrLn $ "Result: " ++ show r;
diff --git a/tests/safeHaskell/unsafeLibs/Dep01.stderr b/tests/safeHaskell/unsafeLibs/Dep01.stderr
index de3016e53..656408bc4 100644
--- a/tests/safeHaskell/unsafeLibs/Dep01.stderr
+++ b/tests/safeHaskell/unsafeLibs/Dep01.stderr
@@ -1,4 +1,4 @@
 
 Dep01.hs:8:12: Warning:
-    In the use of `unsafeSTToIO' (imported from Control.Monad.ST):
+    In the use of ‛unsafeSTToIO’ (imported from Control.Monad.ST):
     Deprecated: "Please import from Control.Monad.ST.Unsafe instead; This will be removed in the next release"
diff --git a/tests/safeHaskell/unsafeLibs/Dep02.stderr b/tests/safeHaskell/unsafeLibs/Dep02.stderr
index 531fda011..4ea40a834 100644
--- a/tests/safeHaskell/unsafeLibs/Dep02.stderr
+++ b/tests/safeHaskell/unsafeLibs/Dep02.stderr
@@ -1,4 +1,4 @@
 
 Dep02.hs:15:17: Warning:
-    In the use of `unsafeIOToST' (imported from Control.Monad.ST.Lazy):
+    In the use of ‛unsafeIOToST’ (imported from Control.Monad.ST.Lazy):
     Deprecated: "Please import from Control.Monad.ST.Lazy.Unsafe instead; This will be removed in the next release"
diff --git a/tests/simplCore/should_compile/T4398.stderr b/tests/simplCore/should_compile/T4398.stderr
index ab17c8a4e..692583e68 100644
--- a/tests/simplCore/should_compile/T4398.stderr
+++ b/tests/simplCore/should_compile/T4398.stderr
@@ -1,4 +1,3 @@
-
-T4398.hs:5:11:
-    Warning: Forall'd constraint `Ord a' is not bound in RULE lhs
-               f @ a x y
+
+T4398.hs:5:11: Warning:
+    Forall'd constraint ‛Ord a’ is not bound in RULE lhs f @ a x y
diff --git a/tests/simplCore/should_compile/T5359b.stderr b/tests/simplCore/should_compile/T5359b.stderr
index a3484cfd4..6106f3e17 100644
--- a/tests/simplCore/should_compile/T5359b.stderr
+++ b/tests/simplCore/should_compile/T5359b.stderr
@@ -1,3 +1,3 @@
 
 T5359b.hs:62:1: Warning:
-    SPECIALISE pragma on INLINE function probably won't fire: `genum'
+    SPECIALISE pragma on INLINE function probably won't fire: ‛genum’
diff --git a/tests/simplCore/should_compile/T6082-RULE.stderr b/tests/simplCore/should_compile/T6082-RULE.stderr
index a503b77d1..e133ec7e5 100644
--- a/tests/simplCore/should_compile/T6082-RULE.stderr
+++ b/tests/simplCore/should_compile/T6082-RULE.stderr
@@ -1,8 +1,8 @@
 
 T6082-RULE.hs:5:11: Warning:
-    Rule "foo1" may never fire because `foo1' might inline first
-    Probable fix: add an INLINE[n] or NOINLINE[n] pragma on `foo1'
+    Rule "foo1" may never fire because ‛foo1’ might inline first
+    Probable fix: add an INLINE[n] or NOINLINE[n] pragma on ‛foo1’
 
 T6082-RULE.hs:10:11: Warning:
-    Rule "foo2" may never fire because `foo2' might inline first
-    Probable fix: add an INLINE[n] or NOINLINE[n] pragma on `foo2'
+    Rule "foo2" may never fire because ‛foo2’ might inline first
+    Probable fix: add an INLINE[n] or NOINLINE[n] pragma on ‛foo2’
diff --git a/tests/simplCore/should_compile/simpl016.stderr b/tests/simplCore/should_compile/simpl016.stderr
index 681dd10ca..0bd07fd0e 100644
--- a/tests/simplCore/should_compile/simpl016.stderr
+++ b/tests/simplCore/should_compile/simpl016.stderr
@@ -1,4 +1,4 @@
 
-simpl016.hs:5:1:
-    Warning: Forall'd constraint `Num b' is not bound in RULE lhs
-               delta' @ Int @ b GHC.Classes.$fEqInt
+simpl016.hs:5:1: Warning:
+    Forall'd constraint ‛Num b’ is not bound in RULE lhs
+      delta' @ Int @ b GHC.Classes.$fEqInt
diff --git a/tests/simplCore/should_compile/simpl017.stderr b/tests/simplCore/should_compile/simpl017.stderr
index 334691d2c..26068534b 100644
--- a/tests/simplCore/should_compile/simpl017.stderr
+++ b/tests/simplCore/should_compile/simpl017.stderr
@@ -1,26 +1,26 @@
 
 simpl017.hs:44:12:
-    Couldn't match expected type `forall v. [E m i] -> E' v m a'
-                with actual type `[E m i] -> E' v0 m a'
+    Couldn't match expected type ‛forall v. [E m i] -> E' v m a’
+                with actual type ‛[E m i] -> E' v0 m a’
     Relevant bindings include
       liftArray :: arr i a -> E m (forall v. [E m i] -> E' v m a)
         (bound at simpl017.hs:39:1)
       a :: arr i a (bound at simpl017.hs:39:11)
       ix :: [E m i] -> m i (bound at simpl017.hs:41:9)
       f :: [E m i] -> E' v0 m a (bound at simpl017.hs:43:9)
-    In the first argument of `return', namely `f'
+    In the first argument of ‛return’, namely ‛f’
     In a stmt of a 'do' block: return f
-    In the first argument of `E', namely
-      `(do { let ix :: [E m i] -> m i
+    In the first argument of ‛E’, namely
+      ‛(do { let ix :: [E m i] -> m i
                  ix [i] = runE i
                  {-# INLINE f #-}
                  ....;
-             return f })'
+             return f })’
 
 simpl017.hs:63:5:
-    Couldn't match type `forall v.
-                         [E' RValue (ST s) Int] -> E' v (ST s) Int'
-                  with `[E (ST t0) Int] -> E' RValue (ST s) Int'
+    Couldn't match type ‛forall v.
+                         [E' RValue (ST s) Int] -> E' v (ST s) Int’
+                  with ‛[E (ST t0) Int] -> E' RValue (ST s) Int’
     Expected type: [E (ST t0) Int] -> E (ST s) Int
       Actual type: forall v. [E (ST s) Int] -> E' v (ST s) Int
     Relevant bindings include
@@ -28,15 +28,15 @@ simpl017.hs:63:5:
       ma :: STArray s Int Int (bound at simpl017.hs:59:5)
       a :: forall v. [E (ST s) Int] -> E' v (ST s) Int
         (bound at simpl017.hs:60:5)
-    The function `a' is applied to one argument,
-    but its type `forall v. [E (ST s) Int] -> E' v (ST s) Int' has none
-    In the first argument of `plus', namely `a [one]'
+    The function ‛a’ is applied to one argument,
+    but its type ‛forall v. [E (ST s) Int] -> E' v (ST s) Int’ has none
+    In the first argument of ‛plus’, namely ‛a [one]’
     In a stmt of a 'do' block: a [one] `plus` a [one]
 
 simpl017.hs:63:19:
-    Couldn't match type `forall v.
-                         [E' RValue (ST s) Int] -> E' v (ST s) Int'
-                  with `[E (ST t1) Int] -> E' RValue (ST s) Int'
+    Couldn't match type ‛forall v.
+                         [E' RValue (ST s) Int] -> E' v (ST s) Int’
+                  with ‛[E (ST t1) Int] -> E' RValue (ST s) Int’
     Expected type: [E (ST t1) Int] -> E (ST s) Int
       Actual type: forall v. [E (ST s) Int] -> E' v (ST s) Int
     Relevant bindings include
@@ -44,7 +44,7 @@ simpl017.hs:63:19:
       ma :: STArray s Int Int (bound at simpl017.hs:59:5)
       a :: forall v. [E (ST s) Int] -> E' v (ST s) Int
         (bound at simpl017.hs:60:5)
-    The function `a' is applied to one argument,
-    but its type `forall v. [E (ST s) Int] -> E' v (ST s) Int' has none
-    In the second argument of `plus', namely `a [one]'
+    The function ‛a’ is applied to one argument,
+    but its type ‛forall v. [E (ST s) Int] -> E' v (ST s) Int’ has none
+    In the second argument of ‛plus’, namely ‛a [one]’
     In a stmt of a 'do' block: a [one] `plus` a [one]
diff --git a/tests/simplCore/should_compile/simpl020.stderr b/tests/simplCore/should_compile/simpl020.stderr
index cd84c1d2d..d23a8ddf2 100644
--- a/tests/simplCore/should_compile/simpl020.stderr
+++ b/tests/simplCore/should_compile/simpl020.stderr
@@ -1,8 +1,8 @@
 
-Simpl020_A.hs:25:10:
-    Warning: No explicit method or default declaration for `toGUIObject'
-    In the instance declaration for `GUIObject ()'
+Simpl020_A.hs:25:10: Warning:
+    No explicit method or default declaration for ‛toGUIObject’
+    In the instance declaration for ‛GUIObject ()’
 
-Simpl020_A.hs:25:10:
-    Warning: No explicit method or default declaration for `cset'
-    In the instance declaration for `GUIObject ()'
+Simpl020_A.hs:25:10: Warning:
+    No explicit method or default declaration for ‛cset’
+    In the instance declaration for ‛GUIObject ()’
diff --git a/tests/th/T2597b.stderr b/tests/th/T2597b.stderr
index 8881b8104..a9295ebd5 100644
--- a/tests/th/T2597b.stderr
+++ b/tests/th/T2597b.stderr
@@ -3,4 +3,4 @@ T2597b.hs:8:8:
     Empty stmt list in do-block
     When splicing a TH expression: do
     In the expression: $mkBug2
-    In an equation for `bug2': bug2 = $mkBug2
+    In an equation for ‛bug2’: bug2 = $mkBug2
diff --git a/tests/th/T2674.stderr b/tests/th/T2674.stderr
index a69781dfe..6875684dd 100644
--- a/tests/th/T2674.stderr
+++ b/tests/th/T2674.stderr
@@ -1,4 +1,4 @@
 
 T2674.hs:9:3:
-    Function binding for `foo' has no equations
+    Function binding for ‛foo’ has no equations
     When splicing a TH declaration: 
diff --git a/tests/th/T2713.stderr b/tests/th/T2713.stderr
index 16f130c65..c036b4384 100644
--- a/tests/th/T2713.stderr
+++ b/tests/th/T2713.stderr
@@ -1,8 +1,8 @@
 
 T2713.hs:11:10:
-    The fixity signature for `.*.' lacks an accompanying binding
-      (The fixity signature must be given where `.*.' is declared)
+    The fixity signature for ‛.*.’ lacks an accompanying binding
+      (The fixity signature must be given where ‛.*.’ is declared)
 
 T2713.hs:12:1:
-    The type signature for `f' lacks an accompanying binding
-      (The type signature must be given where `f' is declared)
+    The type signature for ‛f’ lacks an accompanying binding
+      (The type signature must be given where ‛f’ is declared)
diff --git a/tests/th/T3177a.stderr b/tests/th/T3177a.stderr
index a39419b94..4e9d4dd8f 100644
--- a/tests/th/T3177a.stderr
+++ b/tests/th/T3177a.stderr
@@ -1,10 +1,10 @@
 
 T3177a.hs:8:15:
-    `Int' is applied to too many type arguments
-    In the type `Int Int'
+    ‛Int’ is applied to too many type arguments
+    In the type ‛Int Int’
     In the Template Haskell quotation [t| Int Int |]
-    In the first argument of `id', namely `[t| Int Int |]'
+    In the first argument of ‛id’, namely ‛[t| Int Int |]’
 
 T3177a.hs:11:6:
-    `Int' is applied to too many type arguments
-    In the type signature for `g': g :: Int Int
+    ‛Int’ is applied to too many type arguments
+    In the type signature for ‛g’: g :: Int Int
diff --git a/tests/th/T3395.stderr b/tests/th/T3395.stderr
index f85f7cc1d..cd25afe03 100644
--- a/tests/th/T3395.stderr
+++ b/tests/th/T3395.stderr
@@ -5,12 +5,13 @@ T3395.hs:6:9:
     (It should be an expression.)
     When splicing a TH expression: [r1 <- undefined | undefined]
     In the expression:
-        $(return
+      $(return
         $ CompE
             [NoBindS (VarE $ mkName "undefined"),
              BindS (VarP $ mkName "r1") (VarE $ mkName "undefined")])
-    In an equation for `foo':
-        foo = $(return
+    In an equation for ‛foo’:
+        foo
+          = $(return
               $ CompE
                   [NoBindS (VarE $ mkName "undefined"),
                    BindS (VarP $ mkName "r1") (VarE $ mkName "undefined")])
diff --git a/tests/th/T5358.stderr b/tests/th/T5358.stderr
index 26c83758d..bc4138f8a 100644
--- a/tests/th/T5358.stderr
+++ b/tests/th/T5358.stderr
@@ -1,43 +1,43 @@
 
 T5358.hs:7:1:
-    Couldn't match expected type `t1 -> t1' with actual type `Int'
-    The equation(s) for `t1' have one argument,
-    but its type `Int' has none
+    Couldn't match expected type ‛t1 -> t1’ with actual type ‛Int’
+    The equation(s) for ‛t1’ have one argument,
+    but its type ‛Int’ has none
 
 T5358.hs:8:1:
-    Couldn't match expected type `t0 -> t0' with actual type `Int'
-    The equation(s) for `t2' have one argument,
-    but its type `Int' has none
+    Couldn't match expected type ‛t0 -> t0’ with actual type ‛Int’
+    The equation(s) for ‛t2’ have one argument,
+    but its type ‛Int’ has none
 
 T5358.hs:10:13:
-    Couldn't match expected type `t -> a0' with actual type `Int'
+    Couldn't match expected type ‛t -> a0’ with actual type ‛Int’
     Relevant bindings include
       prop_x1 :: t -> Bool (bound at T5358.hs:10:1)
       x :: t (bound at T5358.hs:10:9)
-    The function `t1' is applied to one argument,
-    but its type `Int' has none
-    In the first argument of `(==)', namely `t1 x'
+    The function ‛t1’ is applied to one argument,
+    but its type ‛Int’ has none
+    In the first argument of ‛(==)’, namely ‛t1 x’
     In the expression: t1 x == t2 x
 
 T5358.hs:10:21:
-    Couldn't match expected type `t -> a0' with actual type `Int'
+    Couldn't match expected type ‛t -> a0’ with actual type ‛Int’
     Relevant bindings include
       prop_x1 :: t -> Bool (bound at T5358.hs:10:1)
       x :: t (bound at T5358.hs:10:9)
-    The function `t2' is applied to one argument,
-    but its type `Int' has none
-    In the second argument of `(==)', namely `t2 x'
+    The function ‛t2’ is applied to one argument,
+    but its type ‛Int’ has none
+    In the second argument of ‛(==)’, namely ‛t2 x’
     In the expression: t1 x == t2 x
 
 T5358.hs:12:15:
     Exception when trying to run compile-time code:
       runTest called error: forall t_0 . t_0 -> GHC.Types.Bool
-      Code: do { VarI _ t _ _ <- reify (mkName "prop_x1");
-                 ($) error ((++) "runTest called error: " pprint t) }
+    Code: do { VarI _ t _ _ <- reify (mkName "prop_x1");
+               ($) error ((++) "runTest called error: " pprint t) }
     In the expression:
       $(do { VarI _ t _ _ <- reify (mkName "prop_x1");
              error $ ("runTest called error: " ++ pprint t) })
-    In an equation for `runTests':
+    In an equation for ‛runTests’:
         runTests
           = $(do { VarI _ t _ _ <- reify (mkName "prop_x1");
                    error $ ("runTest called error: " ++ pprint t) })
diff --git a/tests/th/T5795.stderr b/tests/th/T5795.stderr
index 5fce537ea..74d6c3494 100644
--- a/tests/th/T5795.stderr
+++ b/tests/th/T5795.stderr
@@ -1,7 +1,7 @@
 
 T5795.hs:9:6:
     GHC stage restriction:
-      `ty' is used in a top-level splice or annotation,
+      ‛ty’ is used in a top-level splice or annotation,
       and must be imported, not defined locally
     In the expression: ty
-    In the type signature for `f': f :: $ty
+    In the type signature for ‛f’: f :: $ty
diff --git a/tests/th/T5971.stderr b/tests/th/T5971.stderr
index 3a06330a4..9f3f99381 100644
--- a/tests/th/T5971.stderr
+++ b/tests/th/T5971.stderr
@@ -1,6 +1,6 @@
 
 T5971.hs:6:7:
-    The exact Name `x' is not in scope
+    The exact Name ‛x’ is not in scope
       Probable cause: you used a unique Template Haskell name (NameU), 
       perhaps via newName, but did not bind it
       If that's it, then -ddump-splices might be useful
diff --git a/tests/th/T6114.stderr b/tests/th/T6114.stderr
index 253c7c4d6..e588ada7f 100644
--- a/tests/th/T6114.stderr
+++ b/tests/th/T6114.stderr
@@ -1,6 +1,6 @@
 
 T6114.hs:6:17:
-    The exact Name `x' is not in scope
+    The exact Name ‛x’ is not in scope
       Probable cause: you used a unique Template Haskell name (NameU), 
       perhaps via newName, but did not bind it
       If that's it, then -ddump-splices might be useful
@@ -10,7 +10,7 @@ T6114.hs:6:17:
              instanceType <- [t| $(varT xName) |];
              _ <- reifyInstances ''Eq [instanceType];
              .... })
-    In an equation for `instanceVar':
+    In an equation for ‛instanceVar’:
         instanceVar
           = $(do { xName <- newName "x";
                    instanceType <- [t| $(varT xName) |];
diff --git a/tests/th/T7276.stderr b/tests/th/T7276.stderr
index aeb36647d..d1bb7c71f 100644
--- a/tests/th/T7276.stderr
+++ b/tests/th/T7276.stderr
@@ -1,7 +1,7 @@
 
 T7276.hs:6:8:
-    Couldn't match type `[Language.Haskell.TH.Syntax.Dec]'
-                  with `Language.Haskell.TH.Syntax.Exp'
+    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
     In the Template Haskell quotation [d| y = 3 |]
diff --git a/tests/th/T7276a.stdout b/tests/th/T7276a.stdout
index 8c4f7afc6..15ece9337 100644
--- a/tests/th/T7276a.stdout
+++ b/tests/th/T7276a.stdout
@@ -1,21 +1,21 @@
 
 <interactive>:4:9: Warning:
-    Couldn't match type `[Dec]' with `Exp'
+    Couldn't match type ‛[Dec]’ with ‛Exp’
     Expected type: Q Exp
       Actual type: DecsQ
     In the Template Haskell quotation [d| a = () |]
     In the expression: [d| a = () |] :: Q Exp
-    In an equation for `x': x = [d| a = () |] :: Q Exp
+    In an equation for ‛x’: x = [d| a = () |] :: Q Exp
 
 <interactive>:1:1:
     Exception when trying to run compile-time code:
       <interactive>:4:9:
-    Couldn't match type `[Dec]' with `Exp'
+    Couldn't match type ‛[Dec]’ with ‛Exp’
     Expected type: Q Exp
       Actual type: DecsQ
     In the Template Haskell quotation [d| a = () |]
     In the expression: [d| a = () |] :: Q Exp
-    In an equation for `x': x = [d| a = () |] :: Q Exp
+    In an equation for ‛x’: x = [d| a = () |] :: Q Exp
 (deferred type error)
     Code: x
     In the expression: $x
diff --git a/tests/th/TH_1tuple.stderr b/tests/th/TH_1tuple.stderr
index cb8889e4c..309bde5eb 100644
--- a/tests/th/TH_1tuple.stderr
+++ b/tests/th/TH_1tuple.stderr
@@ -3,4 +3,4 @@ TH_1tuple.hs:11:7:
     Illegal 1-tuple type constructor
     When splicing a TH expression: 1 :: ()
     In the expression: $(sigE [| 1 |] (tupleT 1))
-    In an equation for `y': y = $(sigE [| 1 |] (tupleT 1))
+    In an equation for ‛y’: y = $(sigE [| 1 |] (tupleT 1))
diff --git a/tests/th/TH_dupdecl.stderr b/tests/th/TH_dupdecl.stderr
index a8628a3de..4bd90feba 100644
--- a/tests/th/TH_dupdecl.stderr
+++ b/tests/th/TH_dupdecl.stderr
@@ -1,5 +1,5 @@
 
 TH_dupdecl.hs:10:4:
-    Multiple declarations of `x'
+    Multiple declarations of ‛x’
     Declared at: TH_dupdecl.hs:8:4
                  TH_dupdecl.hs:10:4
diff --git a/tests/th/TH_runIO.stderr b/tests/th/TH_runIO.stderr
index f7a536a95..6d7499a3d 100644
--- a/tests/th/TH_runIO.stderr
+++ b/tests/th/TH_runIO.stderr
@@ -2,6 +2,6 @@
 TH_runIO.hs:12:9:
     Exception when trying to run compile-time code:
       user error (hi)
-      Code: runIO (fail "hi")
+    Code: runIO (fail "hi")
     In the expression: $(runIO (fail "hi"))
-    In an equation for `foo': foo = $(runIO (fail "hi"))
+    In an equation for ‛foo’: foo = $(runIO (fail "hi"))
diff --git a/tests/th/TH_spliceD1.stderr b/tests/th/TH_spliceD1.stderr
index d54ef19b8..2a93bb4f5 100644
--- a/tests/th/TH_spliceD1.stderr
+++ b/tests/th/TH_spliceD1.stderr
@@ -1,6 +1,6 @@
 
 TH_spliceD1.hs:10:3:
-    Conflicting definitions for `c'
+    Conflicting definitions for ‛c’
     Bound at: TH_spliceD1.hs:10:3-5
               TH_spliceD1.hs:10:3-5
-    In an equation for `f'
+    In an equation for ‛f’
diff --git a/tests/th/TH_unresolvedInfix2.stderr b/tests/th/TH_unresolvedInfix2.stderr
index a23cd4ae9..fab508a33 100644
--- a/tests/th/TH_unresolvedInfix2.stderr
+++ b/tests/th/TH_unresolvedInfix2.stderr
@@ -1,9 +1,9 @@
 
 TH_unresolvedInfix2.hs:12:11:
-    The operator `:+' [infixl 6] of a section
+    The operator ‛:+’ [infixl 6] of a section
         must have lower precedence than that of the operand,
-          namely `:+' [infixl 6]
-        in the section: `:+ N :+ N'
+          namely ‛:+’ [infixl 6]
+        in the section: ‛:+ N :+ N’
     In the result of the splice:
       $(let
           plus = conE ':+
@@ -15,7 +15,7 @@ TH_unresolvedInfix2.hs:12:11:
           plus = conE ...
           n = conE ...
         in infixE Nothing plus (Just $ uInfixE n plus n))
-    In an equation for `expr':
+    In an equation for ‛expr’:
         expr
           = $(let
                 plus = ...
diff --git a/tests/typecheck/bug1465/bug1465.stderr b/tests/typecheck/bug1465/bug1465.stderr
index 47a4d0c61..3108183be 100644
--- a/tests/typecheck/bug1465/bug1465.stderr
+++ b/tests/typecheck/bug1465/bug1465.stderr
@@ -1,7 +1,7 @@
 
 C.hs:6:11:
-    Couldn't match expected type `bug1465-1.0:A.T'
-                with actual type `A.T'
+    Couldn't match expected type ‛bug1465-1.0:A.T’
+                with actual type ‛A.T’
     In the expression: B2.f
     In the expression: [B1.f, B2.f]
-    In an equation for `x': x = [B1.f, B2.f]
+    In an equation for ‛x’: x = [B1.f, B2.f]
diff --git a/tests/typecheck/prog001/typecheck.prog001.stderr-ghc b/tests/typecheck/prog001/typecheck.prog001.stderr-ghc
index 17d8e2cf8..4652417ce 100644
--- a/tests/typecheck/prog001/typecheck.prog001.stderr-ghc
+++ b/tests/typecheck/prog001/typecheck.prog001.stderr-ghc
@@ -1,5 +1,4 @@
 
-B.hs:7:10:
-    Warning: No explicit method or default declaration for `row'
-    In the instance declaration for `Matrix Bool Val'
-
+B.hs:7:10: Warning:
+    No explicit method or default declaration for ‛row’
+    In the instance declaration for ‛Matrix Bool Val’
diff --git a/tests/typecheck/should_compile/FD1.stderr b/tests/typecheck/should_compile/FD1.stderr
index fdeb30e42..5fa16fdf1 100644
--- a/tests/typecheck/should_compile/FD1.stderr
+++ b/tests/typecheck/should_compile/FD1.stderr
@@ -5,9 +5,9 @@ FD1.hs:16:1:
       bound by the type signature for
                  plus :: E a (Int -> Int) => Int -> a
       at FD1.hs:15:9-38
-      `a' is a rigid type variable bound by
+      ‛a’ is a rigid type variable bound by
           the type signature for plus :: E a (Int -> Int) => Int -> a
           at FD1.hs:15:9
     Relevant bindings include plus :: Int -> a (bound at FD1.hs:16:1)
-    The equation(s) for `plus' have two arguments,
-    but its type `Int -> a' has only one
+    The equation(s) for ‛plus’ have two arguments,
+    but its type ‛Int -> a’ has only one
diff --git a/tests/typecheck/should_compile/FD2.stderr b/tests/typecheck/should_compile/FD2.stderr
index 8822c1ccb..c98c9cf48 100644
--- a/tests/typecheck/should_compile/FD2.stderr
+++ b/tests/typecheck/should_compile/FD2.stderr
@@ -2,7 +2,7 @@
 FD2.hs:26:34:
     Could not deduce (e ~ e1)
     from the context (Foldable a)
-      bound by the class declaration for `Foldable'
+      bound by the class declaration for ‛Foldable’
       at FD2.hs:(17,1)-(26,39)
     or from (Elem a e)
       bound by the type signature for
@@ -12,11 +12,11 @@ FD2.hs:26:34:
       bound by the type signature for
                  mf :: Elem a e1 => e1 -> Maybe e1 -> Maybe e1
       at FD2.hs:24:18-54
-      `e' is a rigid type variable bound by
+      ‛e’ is a rigid type variable bound by
           the type signature for
             foldr1 :: Elem a e => (e -> e -> e) -> a -> e
           at FD2.hs:21:13
-      `e1' is a rigid type variable bound by
+      ‛e1’ is a rigid type variable bound by
            the type signature for
              mf :: Elem a e1 => e1 -> Maybe e1 -> Maybe e1
            at FD2.hs:24:18
@@ -26,6 +26,6 @@ FD2.hs:26:34:
       mf :: e1 -> Maybe e1 -> Maybe e1 (bound at FD2.hs:25:12)
       x :: e1 (bound at FD2.hs:26:15)
       y :: e1 (bound at FD2.hs:26:23)
-    In the return type of a call of `f'
-    In the first argument of `Just', namely `(f x y)'
+    In the return type of a call of ‛f’
+    In the first argument of ‛Just’, namely ‛(f x y)’
     In the expression: Just (f x y)
diff --git a/tests/typecheck/should_compile/FD3.stderr b/tests/typecheck/should_compile/FD3.stderr
index ad849e6b0..9c0a11c36 100644
--- a/tests/typecheck/should_compile/FD3.stderr
+++ b/tests/typecheck/should_compile/FD3.stderr
@@ -1,7 +1,7 @@
 
 FD3.hs:15:15:
-    Couldn't match type `a' with `(String, a)'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛(String, a)’
+      ‛a’ is a rigid type variable bound by
           the type signature for translate :: (String, a) -> A a
           at FD3.hs:14:14
     Relevant bindings include
@@ -9,8 +9,8 @@ FD3.hs:15:15:
       a :: (String, a) (bound at FD3.hs:15:11)
     When using functional dependencies to combine
       MkA a a,
-        arising from the dependency `a -> b'
+        arising from the dependency ‛a -> b’
         in the instance declaration at FD3.hs:12:10
-      MkA (String, a) a, arising from a use of `mkA' at FD3.hs:15:15-17
+      MkA (String, a) a, arising from a use of ‛mkA’ at FD3.hs:15:15-17
     In the expression: mkA a
-    In an equation for `translate': translate a = mkA a
+    In an equation for ‛translate’: translate a = mkA a
diff --git a/tests/typecheck/should_compile/T2494.stderr b/tests/typecheck/should_compile/T2494.stderr
index bbb8d0c94..68b8dd4be 100644
--- a/tests/typecheck/should_compile/T2494.stderr
+++ b/tests/typecheck/should_compile/T2494.stderr
@@ -1,9 +1,9 @@
 
 T2494.hs:15:14:
-    Couldn't match type `a' with `b'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛b’
+      ‛a’ is a rigid type variable bound by
           the RULE "foo/foo" at T2494.hs:13:16
-      `b' is a rigid type variable bound by
+      ‛b’ is a rigid type variable bound by
           the RULE "foo/foo" at T2494.hs:14:16
     Expected type: Maybe (m a) -> Maybe (m a)
       Actual type: Maybe (m b) -> Maybe (m b)
@@ -13,15 +13,15 @@ T2494.hs:15:14:
         (bound at T2494.hs:14:11)
       f :: forall (m :: * -> *). Monad m => Maybe (m a) -> Maybe (m a)
         (bound at T2494.hs:13:11)
-    In the first argument of `foo', namely `g'
-    In the second argument of `foo', namely `(foo g x)'
+    In the first argument of ‛foo’, namely ‛g’
+    In the second argument of ‛foo’, namely ‛(foo g x)’
     In the expression: foo f (foo g x)
 
 T2494.hs:15:30:
-    Couldn't match type `a' with `b'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛b’
+      ‛a’ is a rigid type variable bound by
           the RULE "foo/foo" at T2494.hs:13:16
-      `b' is a rigid type variable bound by
+      ‛b’ is a rigid type variable bound by
           the RULE "foo/foo" at T2494.hs:14:16
     Expected type: Maybe (m a) -> Maybe (m a)
       Actual type: Maybe (m b) -> Maybe (m b)
@@ -31,6 +31,6 @@ T2494.hs:15:30:
         (bound at T2494.hs:14:11)
       f :: forall (m :: * -> *). Monad m => Maybe (m a) -> Maybe (m a)
         (bound at T2494.hs:13:11)
-    In the second argument of `(.)', namely `g'
-    In the first argument of `foo', namely `(f . g)'
+    In the second argument of ‛(.)’, namely ‛g’
+    In the first argument of ‛foo’, namely ‛(f . g)’
     In the expression: foo (f . g) x
diff --git a/tests/typecheck/should_compile/T2497.stderr b/tests/typecheck/should_compile/T2497.stderr
index de6ca484b..7ee9bee08 100644
--- a/tests/typecheck/should_compile/T2497.stderr
+++ b/tests/typecheck/should_compile/T2497.stderr
@@ -1,2 +1,2 @@
 
-T2497.hs:18:1: Warning: Defined but not used: `beq'
+T2497.hs:18:1: Warning: Defined but not used: ‛beq’
diff --git a/tests/typecheck/should_compile/T5481.stderr b/tests/typecheck/should_compile/T5481.stderr
index c88aecbca..931c3e042 100644
--- a/tests/typecheck/should_compile/T5481.stderr
+++ b/tests/typecheck/should_compile/T5481.stderr
@@ -1,8 +1,8 @@
 
 T5481.hs:6:10:
-    The RHS of an associated type declaration mentions type variable `b'
+    The RHS of an associated type declaration mentions type variable ‛b’
       All such variables must be bound on the LHS
 
 T5481.hs:8:10:
-    The RHS of an associated type declaration mentions type variable `a'
+    The RHS of an associated type declaration mentions type variable ‛a’
       All such variables must be bound on the LHS
diff --git a/tests/typecheck/should_compile/T7050.stderr b/tests/typecheck/should_compile/T7050.stderr
index e7330ce4f..860c90757 100644
--- a/tests/typecheck/should_compile/T7050.stderr
+++ b/tests/typecheck/should_compile/T7050.stderr
@@ -1,5 +1,5 @@
 
 T7050.hs:3:14: Warning:
-    Ignoring unusable UNPACK pragma on the first argument of `Foo'
-    In the definition of data constructor `Foo'
-    In the data declaration for `Foo'
+    Ignoring unusable UNPACK pragma on the first argument of ‛Foo’
+    In the definition of data constructor ‛Foo’
+    In the data declaration for ‛Foo’
diff --git a/tests/typecheck/should_compile/T7562.stderr b/tests/typecheck/should_compile/T7562.stderr
index 1460def5c..36f1de578 100644
--- a/tests/typecheck/should_compile/T7562.stderr
+++ b/tests/typecheck/should_compile/T7562.stderr
@@ -1,5 +1,5 @@
 
 T7562.hs:3:14: Warning:
-    UNPACK pragma lacks '!' on the first argument of `Pair2'
-    In the definition of data constructor `Pair2'
-    In the data declaration for `Pair2'
+    UNPACK pragma lacks '!' on the first argument of ‛Pair2’
+    In the definition of data constructor ‛Pair2’
+    In the data declaration for ‛Pair2’
diff --git a/tests/typecheck/should_compile/holes.stderr b/tests/typecheck/should_compile/holes.stderr
index b04bb8f8e..6f00061cb 100644
--- a/tests/typecheck/should_compile/holes.stderr
+++ b/tests/typecheck/should_compile/holes.stderr
@@ -1,26 +1,26 @@
 
 holes.hs:5:5: Warning:
-    Found hole `_' with type: t
-    Where: `t' is a rigid type variable bound by
+    Found hole ‛_’ with type: t
+    Where: ‛t’ is a rigid type variable bound by
                the inferred type of f :: t at holes.hs:5:1
     Relevant bindings include f :: t (bound at holes.hs:5:1)
     In the expression: _
-    In an equation for `f': f = _
+    In an equation for ‛f’: f = _
 
 holes.hs:8:7: Warning:
-    Found hole `_' with type: Char
+    Found hole ‛_’ with type: Char
     In the expression: _
-    In an equation for `g': g x = _
+    In an equation for ‛g’: g x = _
 
 holes.hs:10:5: Warning:
-    Found hole `_' with type: [Char]
-    In the first argument of `(++)', namely `_'
+    Found hole ‛_’ with type: [Char]
+    In the first argument of ‛(++)’, namely ‛_’
     In the expression: _ ++ "a"
-    In an equation for `h': h = _ ++ "a"
+    In an equation for ‛h’: h = _ ++ "a"
 
 holes.hs:13:15: Warning:
-    Found hole `_' with type: b0
-    Where: `b0' is an ambiguous type variable
-    In the second argument of `const', namely `_'
+    Found hole ‛_’ with type: b0
+    Where: ‛b0’ is an ambiguous type variable
+    In the second argument of ‛const’, namely ‛_’
     In the expression: const y _
-    In an equation for `z': z y = const y _
+    In an equation for ‛z’: z y = const y _
diff --git a/tests/typecheck/should_compile/holes2.stderr b/tests/typecheck/should_compile/holes2.stderr
index 9945d288f..5ceb46e05 100644
--- a/tests/typecheck/should_compile/holes2.stderr
+++ b/tests/typecheck/should_compile/holes2.stderr
@@ -1,19 +1,19 @@
 
 holes2.hs:5:5: Warning:
-    No instance for (Show a0) arising from a use of `show'
-    The type variable `a0' is ambiguous
+    No instance for (Show a0) arising from a use of ‛show’
+    The type variable ‛a0’ is ambiguous
     Note: there are several potential instances:
-      instance Show Double -- Defined in `GHC.Float'
-      instance Show Float -- Defined in `GHC.Float'
+      instance Show Double -- Defined in ‛GHC.Float’
+      instance Show Float -- Defined in ‛GHC.Float’
       instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
+        -- Defined in ‛GHC.Real’
       ...plus 23 others
     In the expression: show _
-    In an equation for `f': f = show _
+    In an equation for ‛f’: f = show _
 
 holes2.hs:5:10: Warning:
-    Found hole `_' with type: a0
-    Where: `a0' is an ambiguous type variable
-    In the first argument of `show', namely `_'
+    Found hole ‛_’ with type: a0
+    Where: ‛a0’ is an ambiguous type variable
+    In the first argument of ‛show’, namely ‛_’
     In the expression: show _
-    In an equation for `f': f = show _
+    In an equation for ‛f’: f = show _
diff --git a/tests/typecheck/should_compile/holes3.stderr b/tests/typecheck/should_compile/holes3.stderr
index 87c80fe30..a945e5e25 100644
--- a/tests/typecheck/should_compile/holes3.stderr
+++ b/tests/typecheck/should_compile/holes3.stderr
@@ -1,26 +1,26 @@
 
 holes3.hs:5:5:
-    Found hole `_' with type: t
-    Where: `t' is a rigid type variable bound by
+    Found hole ‛_’ with type: t
+    Where: ‛t’ is a rigid type variable bound by
                the inferred type of f :: t at holes3.hs:5:1
     Relevant bindings include f :: t (bound at holes3.hs:5:1)
     In the expression: _
-    In an equation for `f': f = _
+    In an equation for ‛f’: f = _
 
 holes3.hs:8:7:
-    Found hole `_gr' with type: Char
+    Found hole ‛_gr’ with type: Char
     In the expression: _gr
-    In an equation for `g': g x = _gr
+    In an equation for ‛g’: g x = _gr
 
 holes3.hs:10:5:
-    Found hole `_aa' with type: [Char]
-    In the first argument of `(++)', namely `_aa'
+    Found hole ‛_aa’ with type: [Char]
+    In the first argument of ‛(++)’, namely ‛_aa’
     In the expression: _aa ++ "a"
-    In an equation for `h': h = _aa ++ "a"
+    In an equation for ‛h’: h = _aa ++ "a"
 
 holes3.hs:13:15:
-    Found hole `_x' with type: b0
-    Where: `b0' is an ambiguous type variable
-    In the second argument of `const', namely `_x'
+    Found hole ‛_x’ with type: b0
+    Where: ‛b0’ is an ambiguous type variable
+    In the second argument of ‛const’, namely ‛_x’
     In the expression: const y _x
-    In an equation for `z': z y = const y _x
+    In an equation for ‛z’: z y = const y _x
diff --git a/tests/typecheck/should_compile/tc056.stderr b/tests/typecheck/should_compile/tc056.stderr
index 786c88e80..c05f9b3bc 100644
--- a/tests/typecheck/should_compile/tc056.stderr
+++ b/tests/typecheck/should_compile/tc056.stderr
@@ -1,6 +1,6 @@
 
-tc056.hs:16:10:
-    Warning: Duplicate constraint(s): Eq' a
+tc056.hs:16:10: Warning:
+    Duplicate constraint(s): Eq' a
     In the context: (Eq' a, Eq' a)
     While checking an instance declaration
-    In the instance declaration for `Eq' [a]'
+    In the instance declaration for ‛Eq' [a]’
diff --git a/tests/typecheck/should_compile/tc115.stderr-ghc b/tests/typecheck/should_compile/tc115.stderr-ghc
index 8b3997deb..26c374793 100644
--- a/tests/typecheck/should_compile/tc115.stderr-ghc
+++ b/tests/typecheck/should_compile/tc115.stderr-ghc
@@ -1,4 +1,4 @@
 
-tc115.hs:12:10:
-    Warning: No explicit method or default declaration for `foo'
-    In the instance declaration for `Foo [m a] (m a)'
+tc115.hs:12:10: Warning:
+    No explicit method or default declaration for ‛foo’
+    In the instance declaration for ‛Foo [m a] (m a)’
diff --git a/tests/typecheck/should_compile/tc116.stderr-ghc b/tests/typecheck/should_compile/tc116.stderr-ghc
index 5593928d2..cb1856bfc 100644
--- a/tests/typecheck/should_compile/tc116.stderr-ghc
+++ b/tests/typecheck/should_compile/tc116.stderr-ghc
@@ -1,4 +1,4 @@
 
-tc116.hs:12:10:
-    Warning: No explicit method or default declaration for `foo'
-    In the instance declaration for `Foo [m a] (m a)'
+tc116.hs:12:10: Warning:
+    No explicit method or default declaration for ‛foo’
+    In the instance declaration for ‛Foo [m a] (m a)’
diff --git a/tests/typecheck/should_compile/tc125.stderr-ghc b/tests/typecheck/should_compile/tc125.stderr-ghc
index 2a2de4283..0bbaf442d 100644
--- a/tests/typecheck/should_compile/tc125.stderr-ghc
+++ b/tests/typecheck/should_compile/tc125.stderr-ghc
@@ -1,20 +1,20 @@
 
-tc125.hs:16:10:
-    Warning: No explicit method or default declaration for `add'
-    In the instance declaration for `Add Z a a'
+tc125.hs:16:10: Warning:
+    No explicit method or default declaration for ‛add’
+    In the instance declaration for ‛Add Z a a’
 
-tc125.hs:17:10:
-    Warning: No explicit method or default declaration for `add'
-    In the instance declaration for `Add (S a) b (S c)'
+tc125.hs:17:10: Warning:
+    No explicit method or default declaration for ‛add’
+    In the instance declaration for ‛Add (S a) b (S c)’
 
-tc125.hs:21:10:
-    Warning: No explicit method or default declaration for `mul'
-    In the instance declaration for `Mul Z a Z'
+tc125.hs:21:10: Warning:
+    No explicit method or default declaration for ‛mul’
+    In the instance declaration for ‛Mul Z a Z’
 
-tc125.hs:22:10:
-    Warning: No explicit method or default declaration for `mul'
-    In the instance declaration for `Mul (S a) b d'
+tc125.hs:22:10: Warning:
+    No explicit method or default declaration for ‛mul’
+    In the instance declaration for ‛Mul (S a) b d’
 
-tc125.hs:29:10:
-    Warning: No explicit method or default declaration for `add'
-    In the instance declaration for `Add (Q a b) (Q c d) (Q ad_bc bd)'
+tc125.hs:29:10: Warning:
+    No explicit method or default declaration for ‛add’
+    In the instance declaration for ‛Add (Q a b) (Q c d) (Q ad_bc bd)’
diff --git a/tests/typecheck/should_compile/tc126.stderr-ghc b/tests/typecheck/should_compile/tc126.stderr-ghc
index ee49f159f..c4c41ea47 100644
--- a/tests/typecheck/should_compile/tc126.stderr-ghc
+++ b/tests/typecheck/should_compile/tc126.stderr-ghc
@@ -1,8 +1,8 @@
 
-tc126.hs:15:25:
-    Warning: No explicit method or default declaration for `bug'
-    In the instance declaration for `Bug (Int -> r) Int r'
+tc126.hs:15:25: Warning:
+    No explicit method or default declaration for ‛bug’
+    In the instance declaration for ‛Bug (Int -> r) Int r’
 
-tc126.hs:16:10:
-    Warning: No explicit method or default declaration for `bug'
-    In the instance declaration for `Bug f (c a) (c r)'
+tc126.hs:16:10: Warning:
+    No explicit method or default declaration for ‛bug’
+    In the instance declaration for ‛Bug f (c a) (c r)’
diff --git a/tests/typecheck/should_compile/tc141.stderr b/tests/typecheck/should_compile/tc141.stderr
index e7d7f7cb1..55aac9e94 100644
--- a/tests/typecheck/should_compile/tc141.stderr
+++ b/tests/typecheck/should_compile/tc141.stderr
@@ -1,14 +1,14 @@
 
 tc141.hs:11:12:
-    You cannot bind scoped type variable `a'
+    You cannot bind scoped type variable ‛a’
       in a pattern binding signature
     In the pattern: p :: a
     In the pattern: (p :: a, q :: a)
     In a pattern binding: (p :: a, q :: a) = x
 
 tc141.hs:11:31:
-    Couldn't match expected type `a1' with actual type `a'
-      because type variable `a1' would escape its scope
+    Couldn't match expected type ‛a1’ with actual type ‛a’
+      because type variable ‛a1’ would escape its scope
     This (rigid, skolem) type variable is bound by
       an expression type signature: a1
       at tc141.hs:11:31-34
@@ -22,7 +22,7 @@ tc141.hs:11:31:
     In the expression: let (p :: a, q :: a) = x in (q :: a, p)
 
 tc141.hs:13:13:
-    You cannot bind scoped type variable `a'
+    You cannot bind scoped type variable ‛a’
       in a pattern binding signature
     In the pattern: y :: a
     In a pattern binding: y :: a = a
@@ -34,8 +34,8 @@ tc141.hs:13:13:
       in v
 
 tc141.hs:15:18:
-    Couldn't match expected type `a2' with actual type `t'
-      because type variable `a2' would escape its scope
+    Couldn't match expected type ‛a2’ with actual type ‛t’
+      because type variable ‛a2’ would escape its scope
     This (rigid, skolem) type variable is bound by
       the type signature for v :: a2
       at tc141.hs:14:19
@@ -44,7 +44,7 @@ tc141.hs:15:18:
       b :: t (bound at tc141.hs:13:5)
       v :: a2 (bound at tc141.hs:15:14)
     In the expression: b
-    In an equation for `v': v = b
+    In an equation for ‛v’: v = b
     In the expression:
       let
         v :: a
diff --git a/tests/typecheck/should_compile/tc161.stderr-ghc b/tests/typecheck/should_compile/tc161.stderr-ghc
index 57b0f6083..60b5b95d7 100644
--- a/tests/typecheck/should_compile/tc161.stderr-ghc
+++ b/tests/typecheck/should_compile/tc161.stderr-ghc
@@ -1,4 +1,4 @@
 
-tc161.hs:17:10:
-    Warning: No explicit method or default declaration for `op'
-    In the instance declaration for `Foo Int'
+tc161.hs:17:10: Warning:
+    No explicit method or default declaration for ‛op’
+    In the instance declaration for ‛Foo Int’
diff --git a/tests/typecheck/should_compile/tc167.stderr b/tests/typecheck/should_compile/tc167.stderr
index 7790d2267..51c982a27 100644
--- a/tests/typecheck/should_compile/tc167.stderr
+++ b/tests/typecheck/should_compile/tc167.stderr
@@ -1,4 +1,4 @@
 
 tc167.hs:8:12:
-    Expecting a lifted type, but `Int#' is unlifted
-    In the type signature for `f': f :: ((->) Int#) Int#
+    Expecting a lifted type, but ‛Int#’ is unlifted
+    In the type signature for ‛f’: f :: ((->) Int#) Int#
diff --git a/tests/typecheck/should_compile/tc168.stderr b/tests/typecheck/should_compile/tc168.stderr
index 96fa5a062..6fbc96f93 100644
--- a/tests/typecheck/should_compile/tc168.stderr
+++ b/tests/typecheck/should_compile/tc168.stderr
@@ -1,11 +1,11 @@
-
-tc168.hs:17:1:
-    Could not deduce (C a1 (a, b0))
-      arising from the ambiguity check for `g'
-    from the context (C a1 (a, b))
-      bound by the inferred type for `g': C a1 (a, b) => a1 -> a
-      at tc168.hs:17:1-16
-    The type variable `b0' is ambiguous
-    When checking that `g'
-      has the inferred type `forall a b a1. C a1 (a, b) => a1 -> a'
-    Probable cause: the inferred type is ambiguous
+
+tc168.hs:17:1:
+    Could not deduce (C a1 (a, b0))
+      arising from the ambiguity check for ‛g’
+    from the context (C a1 (a, b))
+      bound by the inferred type for ‛g’: C a1 (a, b) => a1 -> a
+      at tc168.hs:17:1-16
+    The type variable ‛b0’ is ambiguous
+    When checking that ‛g’
+      has the inferred type ‛forall a b a1. C a1 (a, b) => a1 -> a’
+    Probable cause: the inferred type is ambiguous
diff --git a/tests/typecheck/should_compile/tc211.stderr b/tests/typecheck/should_compile/tc211.stderr
index 998cd76f5..7538dedda 100644
--- a/tests/typecheck/should_compile/tc211.stderr
+++ b/tests/typecheck/should_compile/tc211.stderr
@@ -1,20 +1,20 @@
 
 tc211.hs:15:22:
-    Couldn't match type `forall a6. a6 -> a6' with `a -> a'
+    Couldn't match type ‛forall a6. a6 -> a6’ with ‛a -> a’
     Expected type: [a -> a]
       Actual type: [forall a. a -> a]
-    In the first argument of `head', namely `foo'
-    In the first argument of `(:) ::
+    In the first argument of ‛head’, namely ‛foo’
+    In the first argument of ‛(:) ::
                                 (forall a. a -> a)
-                                -> [forall a. a -> a] -> [forall a. a -> a]', namely
-      `(head foo)'
+                                -> [forall a. a -> a] -> [forall a. a -> a]’, namely
+      ‛(head foo)’
     In the expression:
       ((:) ::
          (forall a. a -> a) -> [forall a. a -> a] -> [forall a. a -> a])
         (head foo) foo
 
 tc211.hs:70:9:
-    Couldn't match type `forall a7. a7 -> a7' with `a6 -> a6'
+    Couldn't match type ‛forall a7. a7 -> a7’ with ‛a6 -> a6’
     Expected type: List (forall a. a -> a)
                    -> (forall a. a -> a) -> a6 -> a6
       Actual type: List (forall a. a -> a)
@@ -27,7 +27,7 @@ tc211.hs:70:9:
          List (forall a. a -> a)
          -> (forall a. a -> a) -> (forall a. a -> a))
         xs1 (\ x -> x)
-    In an equation for `bar4':
+    In an equation for ‛bar4’:
         bar4
           = (foo2 ::
                List (forall a. a -> a)
diff --git a/tests/typecheck/should_compile/tc254.stderr b/tests/typecheck/should_compile/tc254.stderr
index b24224d70..a721c7e3b 100644
--- a/tests/typecheck/should_compile/tc254.stderr
+++ b/tests/typecheck/should_compile/tc254.stderr
@@ -1,4 +1,4 @@
 
-tc254.hs:8:1:
-    Warning: No explicit associated type or default declaration for `Typ'
-    In the instance declaration for `Cls Int'
+tc254.hs:8:1: Warning:
+    No explicit associated type or default declaration for ‛Typ’
+    In the instance declaration for ‛Cls Int’
diff --git a/tests/typecheck/should_fail/AssocTyDef01.stderr b/tests/typecheck/should_fail/AssocTyDef01.stderr
index 5d3a596d9..e342e900a 100644
--- a/tests/typecheck/should_fail/AssocTyDef01.stderr
+++ b/tests/typecheck/should_fail/AssocTyDef01.stderr
@@ -1,3 +1,3 @@
 
 AssocTyDef01.hs:9:10:
-    `OtherType' is not a (visible) associated type of class `Cls'
+    ‛OtherType’ is not a (visible) associated type of class ‛Cls’
diff --git a/tests/typecheck/should_fail/AssocTyDef02.stderr b/tests/typecheck/should_fail/AssocTyDef02.stderr
index 2d1b43952..749e42c99 100644
--- a/tests/typecheck/should_fail/AssocTyDef02.stderr
+++ b/tests/typecheck/should_fail/AssocTyDef02.stderr
@@ -1,6 +1,6 @@
-
-AssocTyDef02.hs:6:10:
-    Type indexes must match class instance head
-    Found `[b]' but expected `a'
-    In the type synonym instance default declaration for `Typ'
-    In the class declaration for `Cls'
+
+AssocTyDef02.hs:6:10:
+    Type indexes must match class instance head
+    Found ‛[b]’ but expected ‛a’
+    In the type synonym instance default declaration for ‛Typ’
+    In the class declaration for ‛Cls’
diff --git a/tests/typecheck/should_fail/AssocTyDef03.stderr b/tests/typecheck/should_fail/AssocTyDef03.stderr
index bd7fadfd8..82e9b0f3a 100644
--- a/tests/typecheck/should_fail/AssocTyDef03.stderr
+++ b/tests/typecheck/should_fail/AssocTyDef03.stderr
@@ -1,5 +1,5 @@
-
-AssocTyDef03.hs:6:5:
-    Wrong category of family instance; declaration was for a data type
-    In the type instance declaration for `Typ'
-    In the class declaration for `Cls'
+
+AssocTyDef03.hs:6:5:
+    Wrong category of family instance; declaration was for a data type
+    In the type instance declaration for ‛Typ’
+    In the class declaration for ‛Cls’
diff --git a/tests/typecheck/should_fail/AssocTyDef04.stderr b/tests/typecheck/should_fail/AssocTyDef04.stderr
index e02758b28..b03eb045e 100644
--- a/tests/typecheck/should_fail/AssocTyDef04.stderr
+++ b/tests/typecheck/should_fail/AssocTyDef04.stderr
@@ -1,7 +1,7 @@
-
-AssocTyDef04.hs:6:18:
-    Expecting one more argument to `Maybe'
-    Expected kind `*', but `Maybe' has kind `* -> *'
-    In the type `Maybe'
-    In the type instance declaration for `Typ'
-    In the class declaration for `Cls'
+
+AssocTyDef04.hs:6:18:
+    Expecting one more argument to ‛Maybe’
+    Expected kind ‛*’, but ‛Maybe’ has kind ‛* -> *’
+    In the type ‛Maybe’
+    In the type instance declaration for ‛Typ’
+    In the class declaration for ‛Cls’
diff --git a/tests/typecheck/should_fail/AssocTyDef05.stderr b/tests/typecheck/should_fail/AssocTyDef05.stderr
index 797c83891..401251e36 100644
--- a/tests/typecheck/should_fail/AssocTyDef05.stderr
+++ b/tests/typecheck/should_fail/AssocTyDef05.stderr
@@ -1,5 +1,5 @@
 
 AssocTyDef05.hs:6:10:
     Number of parameters must match family declaration; expected 1
-    In the type instance declaration for `Typ'
-    In the class declaration for `Cls'
+    In the type instance declaration for ‛Typ’
+    In the class declaration for ‛Cls’
diff --git a/tests/typecheck/should_fail/AssocTyDef06.stderr b/tests/typecheck/should_fail/AssocTyDef06.stderr
index 6100ef2a9..91e92bdca 100644
--- a/tests/typecheck/should_fail/AssocTyDef06.stderr
+++ b/tests/typecheck/should_fail/AssocTyDef06.stderr
@@ -1,5 +1,5 @@
 
 AssocTyDef06.hs:6:10:
     Number of parameters must match family declaration; expected 1
-    In the type instance declaration for `Typ'
-    In the class declaration for `Cls'
+    In the type instance declaration for ‛Typ’
+    In the class declaration for ‛Cls’
diff --git a/tests/typecheck/should_fail/AssocTyDef07.stderr b/tests/typecheck/should_fail/AssocTyDef07.stderr
index 4a4562d0e..151f5a9b8 100644
--- a/tests/typecheck/should_fail/AssocTyDef07.stderr
+++ b/tests/typecheck/should_fail/AssocTyDef07.stderr
@@ -1,3 +1,3 @@
 
 AssocTyDef07.hs:5:10:
-    `Typ' is not a (visible) associated type of class `Cls'
+    ‛Typ’ is not a (visible) associated type of class ‛Cls’
diff --git a/tests/typecheck/should_fail/AssocTyDef08.stderr b/tests/typecheck/should_fail/AssocTyDef08.stderr
index c45132f99..97147c7df 100644
--- a/tests/typecheck/should_fail/AssocTyDef08.stderr
+++ b/tests/typecheck/should_fail/AssocTyDef08.stderr
@@ -1,3 +1,3 @@
 
 AssocTyDef08.hs:4:10:
-    `Typ' is not a (visible) associated type of class `Cls'
+    ‛Typ’ is not a (visible) associated type of class ‛Cls’
diff --git a/tests/typecheck/should_fail/AssocTyDef09.stderr b/tests/typecheck/should_fail/AssocTyDef09.stderr
index 053450c48..3f8c11328 100644
--- a/tests/typecheck/should_fail/AssocTyDef09.stderr
+++ b/tests/typecheck/should_fail/AssocTyDef09.stderr
@@ -1,3 +1,3 @@
 
 AssocTyDef09.hs:8:10:
-    `OtherType' is not a (visible) associated type of class `Cls'
+    ‛OtherType’ is not a (visible) associated type of class ‛Cls’
diff --git a/tests/typecheck/should_fail/FDsFromGivens.stderr b/tests/typecheck/should_fail/FDsFromGivens.stderr
index 60a334232..893ec8ae1 100644
--- a/tests/typecheck/should_fail/FDsFromGivens.stderr
+++ b/tests/typecheck/should_fail/FDsFromGivens.stderr
@@ -1,14 +1,14 @@
 
 FDsFromGivens.hs:21:15:
-    Couldn't match type `Char' with `[a]'
+    Couldn't match type ‛Char’ with ‛[a]’
     Relevant bindings include
       bar :: KCC -> a -> a (bound at FDsFromGivens.hs:21:1)
     When using functional dependencies to combine
       C Char Char,
         arising from a pattern with constructor
                        KCC :: C Char Char => () -> KCC,
-                     in an equation for `bar'
+                     in an equation for ‛bar’
         at FDsFromGivens.hs:21:6-10
-      C Char [a], arising from a use of `f' at FDsFromGivens.hs:21:15
+      C Char [a], arising from a use of ‛f’ at FDsFromGivens.hs:21:15
     In the expression: f
-    In an equation for `bar': bar (KCC _) = f
+    In an equation for ‛bar’: bar (KCC _) = f
diff --git a/tests/typecheck/should_fail/FailDueToGivenOverlapping.stderr b/tests/typecheck/should_fail/FailDueToGivenOverlapping.stderr
index 1cf4e9f1c..74e0bc734 100644
--- a/tests/typecheck/should_fail/FailDueToGivenOverlapping.stderr
+++ b/tests/typecheck/should_fail/FailDueToGivenOverlapping.stderr
@@ -1,12 +1,12 @@
 
 FailDueToGivenOverlapping.hs:27:9:
-    Overlapping instances for E [t0] arising from a use of `eop'
+    Overlapping instances for E [t0] arising from a use of ‛eop’
     Matching givens (or their superclasses):
       (E [Int])
         bound by the type signature for bar :: E [Int] => () -> ()
         at FailDueToGivenOverlapping.hs:26:8-26
     Matching instances:
       instance E [a] -- Defined at FailDueToGivenOverlapping.hs:21:10
-    (The choice depends on the instantiation of `t0')
+    (The choice depends on the instantiation of ‛t0’)
     In the expression: eop [undefined]
-    In an equation for `bar': bar _ = eop [undefined]
+    In an equation for ‛bar’: bar _ = eop [undefined]
diff --git a/tests/typecheck/should_fail/FrozenErrorTests.stderr b/tests/typecheck/should_fail/FrozenErrorTests.stderr
index 5a36d7d54..9857c9c9a 100644
--- a/tests/typecheck/should_fail/FrozenErrorTests.stderr
+++ b/tests/typecheck/should_fail/FrozenErrorTests.stderr
@@ -1,53 +1,53 @@
-
-FrozenErrorTests.hs:12:12:
-    Couldn't match type `Int' with `Bool'
-    Inaccessible code in
-      a pattern with constructor
-        MkT3 :: forall a. a ~ Bool => T a,
-      in a case alternative
-    In the pattern: MkT3
-    In a case alternative: MkT3 -> ()
-    In the expression: case x of { MkT3 -> () }
-
-FrozenErrorTests.hs:26:9:
-    Occurs check: cannot construct the infinite type: a ~ [a]
-    Expected type: [a]
-      Actual type: F a Bool
-    Relevant bindings include
-      test1 :: a (bound at FrozenErrorTests.hs:26:1)
-    In the expression: goo1 False undefined
-    In an equation for `test1': test1 = goo1 False undefined
-
-FrozenErrorTests.hs:29:15:
-    Couldn't match type `Int' with `[Int]'
-    Expected type: [[Int]]
-      Actual type: F [Int] Bool
-    In the first argument of `goo2', namely `(goo1 False undefined)'
-    In the expression: goo2 (goo1 False undefined)
-    In an equation for `test2': test2 = goo2 (goo1 False undefined)
-
-FrozenErrorTests.hs:30:9:
-    Couldn't match type `Int' with `[Int]'
-    Expected type: [[Int]]
-      Actual type: F [Int] Bool
-    In the expression: goo1 False (goo2 undefined)
-    In an equation for `test3': test3 = goo1 False (goo2 undefined)
-
-FrozenErrorTests.hs:45:15:
-    Couldn't match type `T2 c c' with `M (T2 (T2 c c) c)'
-    Expected type: T2 (M (T2 (T2 c c) c)) (T2 (T2 c c) c)
-      Actual type: F (T2 (T2 c c) c) Bool
-    Relevant bindings include
-      test4 :: T2 (T2 c c) c (bound at FrozenErrorTests.hs:45:1)
-    In the first argument of `goo4', namely `(goo3 False undefined)'
-    In the expression: goo4 (goo3 False undefined)
-    In an equation for `test4': test4 = goo4 (goo3 False undefined)
-
-FrozenErrorTests.hs:46:9:
-    Couldn't match type `T2 c c' with `M (T2 (T2 c c) c)'
-    Expected type: T2 (M (T2 (T2 c c) c)) (T2 (T2 c c) c)
-      Actual type: F (T2 (T2 c c) c) Bool
-    Relevant bindings include
-      test5 :: T2 (T2 c c) c (bound at FrozenErrorTests.hs:46:1)
-    In the expression: goo3 False (goo4 undefined)
-    In an equation for `test5': test5 = goo3 False (goo4 undefined)
+
+FrozenErrorTests.hs:12:12:
+    Couldn't match type ‛Int’ with ‛Bool’
+    Inaccessible code in
+      a pattern with constructor
+        MkT3 :: forall a. a ~ Bool => T a,
+      in a case alternative
+    In the pattern: MkT3
+    In a case alternative: MkT3 -> ()
+    In the expression: case x of { MkT3 -> () }
+
+FrozenErrorTests.hs:26:9:
+    Occurs check: cannot construct the infinite type: a ~ [a]
+    Expected type: [a]
+      Actual type: F a Bool
+    Relevant bindings include
+      test1 :: a (bound at FrozenErrorTests.hs:26:1)
+    In the expression: goo1 False undefined
+    In an equation for ‛test1’: test1 = goo1 False undefined
+
+FrozenErrorTests.hs:29:15:
+    Couldn't match type ‛Int’ with ‛[Int]’
+    Expected type: [[Int]]
+      Actual type: F [Int] Bool
+    In the first argument of ‛goo2’, namely ‛(goo1 False undefined)’
+    In the expression: goo2 (goo1 False undefined)
+    In an equation for ‛test2’: test2 = goo2 (goo1 False undefined)
+
+FrozenErrorTests.hs:30:9:
+    Couldn't match type ‛Int’ with ‛[Int]’
+    Expected type: [[Int]]
+      Actual type: F [Int] Bool
+    In the expression: goo1 False (goo2 undefined)
+    In an equation for ‛test3’: test3 = goo1 False (goo2 undefined)
+
+FrozenErrorTests.hs:45:15:
+    Couldn't match type ‛T2 c c’ with ‛M (T2 (T2 c c) c)’
+    Expected type: T2 (M (T2 (T2 c c) c)) (T2 (T2 c c) c)
+      Actual type: F (T2 (T2 c c) c) Bool
+    Relevant bindings include
+      test4 :: T2 (T2 c c) c (bound at FrozenErrorTests.hs:45:1)
+    In the first argument of ‛goo4’, namely ‛(goo3 False undefined)’
+    In the expression: goo4 (goo3 False undefined)
+    In an equation for ‛test4’: test4 = goo4 (goo3 False undefined)
+
+FrozenErrorTests.hs:46:9:
+    Couldn't match type ‛T2 c c’ with ‛M (T2 (T2 c c) c)’
+    Expected type: T2 (M (T2 (T2 c c) c)) (T2 (T2 c c) c)
+      Actual type: F (T2 (T2 c c) c) Bool
+    Relevant bindings include
+      test5 :: T2 (T2 c c) c (bound at FrozenErrorTests.hs:46:1)
+    In the expression: goo3 False (goo4 undefined)
+    In an equation for ‛test5’: test5 = goo3 False (goo4 undefined)
diff --git a/tests/typecheck/should_fail/IPFail.stderr b/tests/typecheck/should_fail/IPFail.stderr
index d8efdfec5..127693a5c 100644
--- a/tests/typecheck/should_fail/IPFail.stderr
+++ b/tests/typecheck/should_fail/IPFail.stderr
@@ -1,9 +1,9 @@
 
 IPFail.hs:6:18:
-    Could not deduce (Num Bool) arising from the literal `5'
+    Could not deduce (Num Bool) arising from the literal ‛5’
     from the context (?x::Int)
       bound by the type signature for f0 :: (?x::Int) => () -> Bool
       at IPFail.hs:5:7-31
     In the expression: 5
     In the expression: let ?x = 5 in ?x
-    In an equation for `f0': f0 () = let ?x = 5 in ?x
+    In an equation for ‛f0’: f0 () = let ?x = 5 in ?x
diff --git a/tests/typecheck/should_fail/LongWayOverlapping.stderr b/tests/typecheck/should_fail/LongWayOverlapping.stderr
index fbd0b4486..d50cc847d 100644
--- a/tests/typecheck/should_fail/LongWayOverlapping.stderr
+++ b/tests/typecheck/should_fail/LongWayOverlapping.stderr
@@ -1,7 +1,7 @@
 
 LongWayOverlapping.hs:23:11:
     No instance for (EmbAsChild [Char] Char)
-      arising from a use of `emb'
+      arising from a use of ‛emb’
     In the expression: emb 'c'
-    In an equation for `emb': emb _ = emb 'c'
-    In the instance declaration for `EmbAsChild [Char] Bool'
+    In an equation for ‛emb’: emb _ = emb 'c'
+    In the instance declaration for ‛EmbAsChild [Char] Bool’
diff --git a/tests/typecheck/should_fail/SCLoop.stderr b/tests/typecheck/should_fail/SCLoop.stderr
index 37970cc73..309dd91af 100644
--- a/tests/typecheck/should_fail/SCLoop.stderr
+++ b/tests/typecheck/should_fail/SCLoop.stderr
@@ -1,5 +1,5 @@
 
 SCLoop.hs:22:7:
-    No instance for (SC ()) arising from a use of `op'
+    No instance for (SC ()) arising from a use of ‛op’
     In the expression: op () ([Just True])
-    In an equation for `foo': foo = op () ([Just True])
+    In an equation for ‛foo’: foo = op () ([Just True])
diff --git a/tests/typecheck/should_fail/SilentParametersOverlapping.stderr b/tests/typecheck/should_fail/SilentParametersOverlapping.stderr
index 6a49325e4..255e6513e 100644
--- a/tests/typecheck/should_fail/SilentParametersOverlapping.stderr
+++ b/tests/typecheck/should_fail/SilentParametersOverlapping.stderr
@@ -1,13 +1,13 @@
 
 SilentParametersOverlapping.hs:15:9:
-    Overlapping instances for C [(t0, t1)] arising from a use of `c'
+    Overlapping instances for C [(t0, t1)] arising from a use of ‛c’
     Matching givens (or their superclasses):
       (C [(a, b)])
         bound by the instance declaration
         at SilentParametersOverlapping.hs:14:37-45
     Matching instances:
       instance C [a] -- Defined at SilentParametersOverlapping.hs:11:10
-    (The choice depends on the instantiation of `t0, t1')
+    (The choice depends on the instantiation of ‛t0, t1’)
     In the expression: c [(undefined, undefined)]
-    In an equation for `b': b x = c [(undefined, undefined)]
-    In the instance declaration for `B [(a, b)]'
+    In an equation for ‛b’: b x = c [(undefined, undefined)]
+    In the instance declaration for ‛B [(a, b)]’
diff --git a/tests/typecheck/should_fail/T1595.stderr b/tests/typecheck/should_fail/T1595.stderr
index d3f665c15..a84903ded 100644
--- a/tests/typecheck/should_fail/T1595.stderr
+++ b/tests/typecheck/should_fail/T1595.stderr
@@ -1,6 +1,6 @@
 
 T1595.hs:8:15:
-    Not in scope: type constructor or class `DoesNotExist'
+    Not in scope: type constructor or class ‛DoesNotExist’
 
 T1595.hs:13:22:
-    Not in scope: type constructor or class `DoesNotExist'
+    Not in scope: type constructor or class ‛DoesNotExist’
diff --git a/tests/typecheck/should_fail/T1633.stderr b/tests/typecheck/should_fail/T1633.stderr
index bdfa10ad5..8a01bd9fd 100644
--- a/tests/typecheck/should_fail/T1633.stderr
+++ b/tests/typecheck/should_fail/T1633.stderr
@@ -1,5 +1,5 @@
 
 T1633.hs:6:18:
-    The first argument of `Functor' should have kind `* -> *',
-      but `Bool' has kind `*'
-    In the instance declaration for `Functor Bool'
+    The first argument of ‛Functor’ should have kind ‛* -> *’,
+      but ‛Bool’ has kind ‛*’
+    In the instance declaration for ‛Functor Bool’
diff --git a/tests/typecheck/should_fail/T1897a.stderr b/tests/typecheck/should_fail/T1897a.stderr
index eb1204850..b495f17b1 100644
--- a/tests/typecheck/should_fail/T1897a.stderr
+++ b/tests/typecheck/should_fail/T1897a.stderr
@@ -1,11 +1,11 @@
-
-T1897a.hs:9:1:
-    Could not deduce (Wob a0 b)
-      arising from the ambiguity check for `foo'
-    from the context (Wob a b)
-      bound by the inferred type for `foo': Wob a b => b -> [b]
-      at T1897a.hs:9:1-24
-    The type variable `a0' is ambiguous
-    When checking that `foo'
-      has the inferred type `forall a b. Wob a b => b -> [b]'
-    Probable cause: the inferred type is ambiguous
+
+T1897a.hs:9:1:
+    Could not deduce (Wob a0 b)
+      arising from the ambiguity check for ‛foo’
+    from the context (Wob a b)
+      bound by the inferred type for ‛foo’: Wob a b => b -> [b]
+      at T1897a.hs:9:1-24
+    The type variable ‛a0’ is ambiguous
+    When checking that ‛foo’
+      has the inferred type ‛forall a b. Wob a b => b -> [b]’
+    Probable cause: the inferred type is ambiguous
diff --git a/tests/typecheck/should_fail/T1899.stderr b/tests/typecheck/should_fail/T1899.stderr
index 0838984c2..d637ac7a0 100644
--- a/tests/typecheck/should_fail/T1899.stderr
+++ b/tests/typecheck/should_fail/T1899.stderr
@@ -1,12 +1,12 @@
 
 T1899.hs:12:29:
-    Couldn't match expected type `a' with actual type `Proposition a0'
-      `a' is a rigid type variable bound by
+    Couldn't match expected type ‛a’ with actual type ‛Proposition a0’
+      ‛a’ is a rigid type variable bound by
           the type signature for transRHS :: [a] -> Int -> Constraint a
           at T1899.hs:9:14
     Relevant bindings include
       transRHS :: [a] -> Int -> Constraint a (bound at T1899.hs:10:2)
       varSet :: [a] (bound at T1899.hs:10:11)
-    In the return type of a call of `Auxiliary'
-    In the first argument of `Prop', namely `(Auxiliary undefined)'
+    In the return type of a call of ‛Auxiliary’
+    In the first argument of ‛Prop’, namely ‛(Auxiliary undefined)’
     In the expression: Prop (Auxiliary undefined)
diff --git a/tests/typecheck/should_fail/T2126.stderr b/tests/typecheck/should_fail/T2126.stderr
index 2facb189a..1e0a72df2 100644
--- a/tests/typecheck/should_fail/T2126.stderr
+++ b/tests/typecheck/should_fail/T2126.stderr
@@ -1,4 +1,4 @@
 
 T2126.hs:5:1:
-    A newtype must have exactly one constructor, but `X' has none
-    In the newtype declaration for `X'
+    A newtype must have exactly one constructor, but ‛X’ has none
+    In the newtype declaration for ‛X’
diff --git a/tests/typecheck/should_fail/T2247.stderr b/tests/typecheck/should_fail/T2247.stderr
index 70ef7f703..15ec58448 100644
--- a/tests/typecheck/should_fail/T2247.stderr
+++ b/tests/typecheck/should_fail/T2247.stderr
@@ -1,6 +1,6 @@
 
 T2247.hs:6:10:
-    Illegal instance declaration for `FD a b'
+    Illegal instance declaration for ‛FD a b’
       Multiple uses of this instance may be inconsistent
       with the functional dependencies of the class.
-    In the instance declaration for `FD a b'
+    In the instance declaration for ‛FD a b’
diff --git a/tests/typecheck/should_fail/T2354.stderr b/tests/typecheck/should_fail/T2354.stderr
index da21f7929..55285ffd1 100644
--- a/tests/typecheck/should_fail/T2354.stderr
+++ b/tests/typecheck/should_fail/T2354.stderr
@@ -1,6 +1,6 @@
 
 T2354.hs:4:3:
-    The INLINE pragma for default method `toInt' lacks an accompanying binding
+    The INLINE pragma for default method ‛toInt’ lacks an accompanying binding
 
 T2354.hs:6:3:
-    The INLINE pragma for default method `fromInt' lacks an accompanying binding
+    The INLINE pragma for default method ‛fromInt’ lacks an accompanying binding
diff --git a/tests/typecheck/should_fail/T2414.stderr b/tests/typecheck/should_fail/T2414.stderr
index 53ea2b11e..af968d90d 100644
--- a/tests/typecheck/should_fail/T2414.stderr
+++ b/tests/typecheck/should_fail/T2414.stderr
@@ -3,6 +3,6 @@ T2414.hs:9:13:
     Occurs check: cannot construct the infinite type: b0 ~ (Bool, b0)
     Expected type: b0 -> Maybe (Bool, b0)
       Actual type: b0 -> Maybe b0
-    In the first argument of `unfoldr', namely `Just'
+    In the first argument of ‛unfoldr’, namely ‛Just’
     In the expression: unfoldr Just
-    In an equation for `f': f = unfoldr Just
+    In an equation for ‛f’: f = unfoldr Just
diff --git a/tests/typecheck/should_fail/T2534.stderr b/tests/typecheck/should_fail/T2534.stderr
index 02ad7821f..389b51595 100644
--- a/tests/typecheck/should_fail/T2534.stderr
+++ b/tests/typecheck/should_fail/T2534.stderr
@@ -1,8 +1,8 @@
 
 T2534.hs:3:19:
-    Couldn't match expected type `a -> a -> b' with actual type `[t0]'
+    Couldn't match expected type ‛a -> a -> b’ with actual type ‛[t0]’
     Relevant bindings include
       foo :: a -> a -> b (bound at T2534.hs:3:1)
-    In the second argument of `foldr', namely `[]'
+    In the second argument of ‛foldr’, namely ‛[]’
     In the expression: foldr (>>=) [] []
-    In an equation for `foo': foo = foldr (>>=) [] []
+    In an equation for ‛foo’: foo = foldr (>>=) [] []
diff --git a/tests/typecheck/should_fail/T2538.stderr b/tests/typecheck/should_fail/T2538.stderr
index b2d1d3aeb..2e67c878a 100644
--- a/tests/typecheck/should_fail/T2538.stderr
+++ b/tests/typecheck/should_fail/T2538.stderr
@@ -2,13 +2,13 @@
 T2538.hs:6:6:
     Illegal polymorphic or qualified type: Eq a => a -> a
     Perhaps you intended to use -XRankNTypes or -XRank2Types
-    In the type signature for `f': f :: (Eq a => a -> a) -> Int
+    In the type signature for ‛f’: f :: (Eq a => a -> a) -> Int
 
 T2538.hs:9:6:
     Illegal polymorphic or qualified type: Eq a => a -> a
     Perhaps you intended to use -XImpredicativeTypes
-    In the type signature for `g': g :: [Eq a => a -> a] -> Int
+    In the type signature for ‛g’: g :: [Eq a => a -> a] -> Int
 
 T2538.hs:12:6:
     Illegal polymorphic or qualified type: Eq a => a -> a
-    In the type signature for `h': h :: Ix (Eq a => a -> a) => Int
+    In the type signature for ‛h’: h :: Ix (Eq a => a -> a) => Int
diff --git a/tests/typecheck/should_fail/T2688.stderr b/tests/typecheck/should_fail/T2688.stderr
index 3bb0f4934..bbc415ad8 100644
--- a/tests/typecheck/should_fail/T2688.stderr
+++ b/tests/typecheck/should_fail/T2688.stderr
@@ -2,16 +2,16 @@
 T2688.hs:8:22:
     Could not deduce (s ~ v)
     from the context (VectorSpace v s)
-      bound by the class declaration for `VectorSpace'
+      bound by the class declaration for ‛VectorSpace’
       at T2688.hs:(5,1)-(8,23)
-      `s' is a rigid type variable bound by
-          the class declaration for `VectorSpace' at T2688.hs:5:21
-      `v' is a rigid type variable bound by
-          the class declaration for `VectorSpace' at T2688.hs:5:19
+      ‛s’ is a rigid type variable bound by
+          the class declaration for ‛VectorSpace’ at T2688.hs:5:21
+      ‛v’ is a rigid type variable bound by
+          the class declaration for ‛VectorSpace’ at T2688.hs:5:19
     Relevant bindings include
       ^/ :: v -> s -> v (bound at T2688.hs:8:5)
       v :: v (bound at T2688.hs:8:5)
       s :: s (bound at T2688.hs:8:10)
-    In the second argument of `(/)', namely `s'
-    In the second argument of `(*^)', namely `(1 / s)'
+    In the second argument of ‛(/)’, namely ‛s’
+    In the second argument of ‛(*^)’, namely ‛(1 / s)’
     In the expression: v *^ (1 / s)
diff --git a/tests/typecheck/should_fail/T2714.stderr b/tests/typecheck/should_fail/T2714.stderr
index 68056509c..07adee2ee 100644
--- a/tests/typecheck/should_fail/T2714.stderr
+++ b/tests/typecheck/should_fail/T2714.stderr
@@ -1,7 +1,7 @@
 
 T2714.hs:8:5:
-    Couldn't match type `c' with `f0 (a -> b)'
-      `c' is a rigid type variable bound by
+    Couldn't match type ‛c’ with ‛f0 (a -> b)’
+      ‛c’ is a rigid type variable bound by
           the type signature for f :: ((a -> b) -> b) -> c -> a
           at T2714.hs:8:1
     Expected type: ((a -> b) -> b) -> c -> a
@@ -9,11 +9,11 @@ T2714.hs:8:5:
     Relevant bindings include
       f :: ((a -> b) -> b) -> forall c. c -> a (bound at T2714.hs:8:1)
     In the expression: ffmap
-    In an equation for `f': f = ffmap
+    In an equation for ‛f’: f = ffmap
 
 T2714.hs:8:5:
-    Couldn't match type `a' with `f0 b'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛f0 b’
+      ‛a’ is a rigid type variable bound by
           the type signature for f :: ((a -> b) -> b) -> forall c. c -> a
           at T2714.hs:7:6
     Expected type: ((a -> b) -> b) -> c -> a
@@ -21,4 +21,4 @@ T2714.hs:8:5:
     Relevant bindings include
       f :: ((a -> b) -> b) -> forall c. c -> a (bound at T2714.hs:8:1)
     In the expression: ffmap
-    In an equation for `f': f = ffmap
+    In an equation for ‛f’: f = ffmap
diff --git a/tests/typecheck/should_fail/T2806.stderr b/tests/typecheck/should_fail/T2806.stderr
index ebbffb29e..da35b207d 100644
--- a/tests/typecheck/should_fail/T2806.stderr
+++ b/tests/typecheck/should_fail/T2806.stderr
@@ -1,8 +1,8 @@
 
-T2806.hs:13:11:
-    Warning: Pattern bindings containing unlifted types should use an outermost bang pattern:
-               (I# _x) = 4
-    In an equation for `foo':
+T2806.hs:13:11: Warning:
+    Pattern bindings containing unlifted types should use an outermost bang pattern:
+      (I# _x) = 4
+    In an equation for ‛foo’:
         foo
           = 3
           where
diff --git a/tests/typecheck/should_fail/T2846b.stderr b/tests/typecheck/should_fail/T2846b.stderr
index b70c4d1a0..23b6a6a0e 100644
--- a/tests/typecheck/should_fail/T2846b.stderr
+++ b/tests/typecheck/should_fail/T2846b.stderr
@@ -1,5 +1,5 @@
 
 T2846b.hs:5:5:
-    No instance for (Show (Num a0 => a0)) arising from a use of `show'
+    No instance for (Show (Num a0 => a0)) arising from a use of ‛show’
     In the expression: show ([1, 2, 3] :: [Num a => a])
-    In an equation for `f': f = show ([1, 2, 3] :: [Num a => a])
+    In an equation for ‛f’: f = show ([1, 2, 3] :: [Num a => a])
diff --git a/tests/typecheck/should_fail/T2994.stderr b/tests/typecheck/should_fail/T2994.stderr
index 7c797afb7..2794cb2af 100644
--- a/tests/typecheck/should_fail/T2994.stderr
+++ b/tests/typecheck/should_fail/T2994.stderr
@@ -1,16 +1,16 @@
 
 T2994.hs:11:10:
-    Expecting one more argument to `MonadReader Int'
+    Expecting one more argument to ‛MonadReader Int’
     Expected a constraint,
-      but `MonadReader Int' has kind `* -> Constraint'
-    In the instance declaration for `MonadReader Int'
+      but ‛MonadReader Int’ has kind ‛* -> Constraint’
+    In the instance declaration for ‛MonadReader Int’
 
 T2994.hs:13:23:
-    Expecting one more argument to `Reader' r'
-    The first argument of `MonadReader' should have kind `*',
-      but `Reader' r' has kind `* -> *'
-    In the instance declaration for `MonadReader (Reader' r)'
+    Expecting one more argument to ‛Reader' r’
+    The first argument of ‛MonadReader’ should have kind ‛*’,
+      but ‛Reader' r’ has kind ‛* -> *’
+    In the instance declaration for ‛MonadReader (Reader' r)’
 
 T2994.hs:15:10:
-    `MonadReader' is applied to too many type arguments
-    In the instance declaration for `MonadReader r r (Reader' r)'
+    ‛MonadReader’ is applied to too many type arguments
+    In the instance declaration for ‛MonadReader r r (Reader' r)’
diff --git a/tests/typecheck/should_fail/T3102.stderr b/tests/typecheck/should_fail/T3102.stderr
index 0cf9d5218..b3f69d376 100644
--- a/tests/typecheck/should_fail/T3102.stderr
+++ b/tests/typecheck/should_fail/T3102.stderr
@@ -1,10 +1,10 @@
 
 T3102.hs:11:12:
-    Couldn't match type `a' with `(?p::Int) => a0'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛(?p::Int) => a0’
+      ‛a’ is a rigid type variable bound by
           a type expected by the context: a -> String at T3102.hs:11:10
     Expected type: a -> String
       Actual type: ((?p::Int) => a0) -> String
-    In the first argument of `f', namely `t'
+    In the first argument of ‛f’, namely ‛t’
     In the expression: f t
-    In an equation for `result': result = f t
+    In an equation for ‛result’: result = f t
diff --git a/tests/typecheck/should_fail/T3176.stderr b/tests/typecheck/should_fail/T3176.stderr
index 393880367..160eb4769 100644
--- a/tests/typecheck/should_fail/T3176.stderr
+++ b/tests/typecheck/should_fail/T3176.stderr
@@ -1,7 +1,7 @@
 
 T3176.hs:9:27:
-    Cannot use record selector `unES' as a function due to escaped type variables
+    Cannot use record selector ‛unES’ as a function due to escaped type variables
     Probable fix: use pattern-matching syntax instead
     In the expression: unES
-    In the second argument of `($)', namely `unES $ f t'
+    In the second argument of ‛($)’, namely ‛unES $ f t’
     In the expression: show $ unES $ f t
diff --git a/tests/typecheck/should_fail/T3323.stderr b/tests/typecheck/should_fail/T3323.stderr
index d7c4c2668..029ef7357 100644
--- a/tests/typecheck/should_fail/T3323.stderr
+++ b/tests/typecheck/should_fail/T3323.stderr
@@ -2,4 +2,4 @@
 T3323.hs:18:7:
     Record update for insufficiently polymorphic field: haDevice :: dev
     In the expression: h {haDevice = undefined}
-    In an equation for `f': f h = h {haDevice = undefined}
+    In an equation for ‛f’: f h = h {haDevice = undefined}
diff --git a/tests/typecheck/should_fail/T3406.stderr b/tests/typecheck/should_fail/T3406.stderr
index ceba706f8..40779d4f2 100644
--- a/tests/typecheck/should_fail/T3406.stderr
+++ b/tests/typecheck/should_fail/T3406.stderr
@@ -1,10 +1,10 @@
 
 T3406.hs:11:6:
-    The type variables `a, b'
-    should be bound by the pattern signature `ItemColID a b'
+    The type variables ‛a, b’
+    should be bound by the pattern signature ‛ItemColID a b’
     but are actually discarded by a type synonym
     To fix this, expand the type synonym
     [Note: I hope to lift this restriction in due course]
     In the pattern: x :: ItemColID a b
-    In an equation for `get':
+    In an equation for ‛get’:
         get (x :: ItemColID a b) = x :: ItemColID a b
diff --git a/tests/typecheck/should_fail/T3468.stderr b/tests/typecheck/should_fail/T3468.stderr
index 1dcc3488e..fa702d6d0 100644
--- a/tests/typecheck/should_fail/T3468.stderr
+++ b/tests/typecheck/should_fail/T3468.stderr
@@ -1,12 +1,12 @@
-
-T3468.hs-boot:3:6:
-    Type constructor `Tool' has conflicting definitions in the module and its hs-boot file
-    Main module: data Tool d
-                     No C type associated
-                     RecFlag Recursive, Promotable
-                     = F :: forall d a r. a -> Tool d Stricts: _
-                     FamilyInstance: none
-    Boot file:   abstract(False) Tool
-                     No C type associated
-                     RecFlag NonRecursive, Not promotable
-                     FamilyInstance: none
+
+T3468.hs-boot:3:6:
+    Type constructor ‛Tool’ has conflicting definitions in the module and its hs-boot file
+    Main module: data Tool d
+                     No C type associated
+                     RecFlag Recursive, Promotable
+                     = F :: forall d a r. a -> Tool d Stricts: _
+                     FamilyInstance: none
+    Boot file:   abstract(False) Tool
+                     No C type associated
+                     RecFlag NonRecursive, Not promotable
+                     FamilyInstance: none
diff --git a/tests/typecheck/should_fail/T3540.stderr b/tests/typecheck/should_fail/T3540.stderr
index 83bcbf1f8..db84dcd62 100644
--- a/tests/typecheck/should_fail/T3540.stderr
+++ b/tests/typecheck/should_fail/T3540.stderr
@@ -1,20 +1,20 @@
 
 T3540.hs:4:12:
-    Expected a type, but `a ~ Int' has kind `Constraint'
-    In the type signature for `thing': thing :: a ~ Int
+    Expected a type, but ‛a ~ Int’ has kind ‛Constraint’
+    In the type signature for ‛thing’: thing :: a ~ Int
 
 T3540.hs:7:20:
-    Expected a type, but `a ~ Int' has kind `Constraint'
-    In the type signature for `thing1': thing1 :: Int -> (a ~ Int)
+    Expected a type, but ‛a ~ Int’ has kind ‛Constraint’
+    In the type signature for ‛thing1’: thing1 :: Int -> (a ~ Int)
 
 T3540.hs:10:13:
-    Expected a type, but `a ~ Int' has kind `Constraint'
-    In the type signature for `thing2': thing2 :: (a ~ Int) -> Int
+    Expected a type, but ‛a ~ Int’ has kind ‛Constraint’
+    In the type signature for ‛thing2’: thing2 :: (a ~ Int) -> Int
 
 T3540.hs:13:12:
-    Expected a type, but `?dude :: Int' has kind `Constraint'
-    In the type signature for `thing3': thing3 :: (?dude :: Int) -> Int
+    Expected a type, but ‛?dude :: Int’ has kind ‛Constraint’
+    In the type signature for ‛thing3’: thing3 :: (?dude :: Int) -> Int
 
 T3540.hs:16:11:
-    Expected a type, but `Eq a' has kind `Constraint'
-    In the type signature for `thing4': thing4 :: (Eq a) -> Int
+    Expected a type, but ‛Eq a’ has kind ‛Constraint’
+    In the type signature for ‛thing4’: thing4 :: (Eq a) -> Int
diff --git a/tests/typecheck/should_fail/T3592.stderr b/tests/typecheck/should_fail/T3592.stderr
index 08a02ce8a..be59667e3 100644
--- a/tests/typecheck/should_fail/T3592.stderr
+++ b/tests/typecheck/should_fail/T3592.stderr
@@ -1,13 +1,13 @@
 
 T3592.hs:8:5:
-    No instance for (Show (T a)) arising from a use of `show'
+    No instance for (Show (T a)) arising from a use of ‛show’
     In the expression: show
-    In an equation for `f': f = show
+    In an equation for ‛f’: f = show
 
 T3592.hs:11:7:
-    No instance for (Show a) arising from a use of `show'
+    No instance for (Show a) arising from a use of ‛show’
     Possible fix:
       add (Show a) to the context of
         the type signature for g :: T a -> String
     In the expression: show x
-    In an equation for `g': g x = show x
+    In an equation for ‛g’: g x = show x
diff --git a/tests/typecheck/should_fail/T3613.stderr b/tests/typecheck/should_fail/T3613.stderr
index 1373b7143..956e20cb7 100644
--- a/tests/typecheck/should_fail/T3613.stderr
+++ b/tests/typecheck/should_fail/T3613.stderr
@@ -1,20 +1,20 @@
 
 T3613.hs:14:20:
-    Couldn't match type `IO' with `Maybe'
+    Couldn't match type ‛IO’ with ‛Maybe’
     Expected type: Maybe ()
       Actual type: IO ()
-    In the first argument of `(>>)', namely `bar'
-    In the first argument of `fooThen', namely `(bar >> undefined)'
+    In the first argument of ‛(>>)’, namely ‛bar’
+    In the first argument of ‛fooThen’, namely ‛(bar >> undefined)’
     In the expression: fooThen (bar >> undefined)
 
 T3613.hs:17:24:
-    Couldn't match type `IO' with `Maybe'
+    Couldn't match type ‛IO’ with ‛Maybe’
     Expected type: Maybe ()
       Actual type: IO ()
     In a stmt of a 'do' block: bar
-    In the first argument of `fooThen', namely
-      `(do { bar;
-             undefined })'
+    In the first argument of ‛fooThen’, namely
+      ‛(do { bar;
+             undefined })’
     In the expression:
       fooThen
         (do { bar;
diff --git a/tests/typecheck/should_fail/T3966.stderr b/tests/typecheck/should_fail/T3966.stderr
index ccbe46744..6e292b088 100644
--- a/tests/typecheck/should_fail/T3966.stderr
+++ b/tests/typecheck/should_fail/T3966.stderr
@@ -1,8 +1,8 @@
 
 T3966.hs:5:16: Warning:
-    Ignoring unusable UNPACK pragma on the first argument of `Foo'
-    In the definition of data constructor `Foo'
-    In the data declaration for `Foo'
+    Ignoring unusable UNPACK pragma on the first argument of ‛Foo’
+    In the definition of data constructor ‛Foo’
+    In the data declaration for ‛Foo’
 
 <no location info>: 
 Failing due to -Werror.
diff --git a/tests/typecheck/should_fail/T4875.stderr b/tests/typecheck/should_fail/T4875.stderr
index 24c570e73..ae88bdf97 100644
--- a/tests/typecheck/should_fail/T4875.stderr
+++ b/tests/typecheck/should_fail/T4875.stderr
@@ -1,5 +1,5 @@
-
-T4875.hs:27:24:
-    `r' is applied to too many type arguments
-    In the type `r c -> [c]'
-    In the class declaration for `Morphic'
+
+T4875.hs:27:24:
+    ‛r’ is applied to too many type arguments
+    In the type ‛r c -> [c]’
+    In the class declaration for ‛Morphic’
diff --git a/tests/typecheck/should_fail/T5051.stderr b/tests/typecheck/should_fail/T5051.stderr
index cebde5c29..b15c2d9fa 100644
--- a/tests/typecheck/should_fail/T5051.stderr
+++ b/tests/typecheck/should_fail/T5051.stderr
@@ -1,11 +1,11 @@
 
 T5051.hs:11:11:
-    Overlapping instances for Eq [a] arising from a use of `>='
+    Overlapping instances for Eq [a] arising from a use of ‛>=’
     Matching instances:
-      instance Eq a => Eq [a] -- Defined in `GHC.Classes'
+      instance Eq a => Eq [a] -- Defined in ‛GHC.Classes’
       instance [overlap ok] Eq [T] -- Defined at T5051.hs:8:10
-    (The choice depends on the instantiation of `a'
+    (The choice depends on the instantiation of ‛a’
      To pick the first instance above, use -XIncoherentInstances
      when compiling the other instance declarations)
     In the expression: x >= x
-    In an equation for `foo': foo x = x >= x
+    In an equation for ‛foo’: foo x = x >= x
diff --git a/tests/typecheck/should_fail/T5084.stderr b/tests/typecheck/should_fail/T5084.stderr
index eba942634..de9b4b146 100644
--- a/tests/typecheck/should_fail/T5084.stderr
+++ b/tests/typecheck/should_fail/T5084.stderr
@@ -1,3 +1,3 @@
 
 T5084.hs:6:5:
-    The INLINE pragma for default method `bar' lacks an accompanying binding
+    The INLINE pragma for default method ‛bar’ lacks an accompanying binding
diff --git a/tests/typecheck/should_fail/T5095.stderr b/tests/typecheck/should_fail/T5095.stderr
index 6ef994fdc..166bc5e2c 100644
--- a/tests/typecheck/should_fail/T5095.stderr
+++ b/tests/typecheck/should_fail/T5095.stderr
@@ -1,64 +1,64 @@
 
 T5095.hs:9:11:
-    Overlapping instances for Eq a arising from a use of `=='
+    Overlapping instances for Eq a arising from a use of ‛==’
     Matching instances:
       instance [overlap ok] Show a => Eq a -- Defined at T5095.hs:5:10
-      instance Eq a => Eq (GHC.Real.Ratio a) -- Defined in `GHC.Real'
-      instance Eq () -- Defined in `GHC.Classes'
-      instance (Eq a, Eq b) => Eq (a, b) -- Defined in `GHC.Classes'
+      instance Eq a => Eq (GHC.Real.Ratio a) -- Defined in ‛GHC.Real’
+      instance Eq () -- Defined in ‛GHC.Classes’
+      instance (Eq a, Eq b) => Eq (a, b) -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c) => Eq (a, b, c)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) =>
                Eq (a, b, c, d, e, f)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) =>
                Eq (a, b, c, d, e, f, g)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) =>
                Eq (a, b, c, d, e, f, g, h)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) =>
                Eq (a, b, c, d, e, f, g, h, i)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i,
                 Eq j) =>
                Eq (a, b, c, d, e, f, g, h, i, j)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i,
                 Eq j, Eq k) =>
                Eq (a, b, c, d, e, f, g, h, i, j, k)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i,
                 Eq j, Eq k, Eq l) =>
                Eq (a, b, c, d, e, f, g, h, i, j, k, l)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i,
                 Eq j, Eq k, Eq l, Eq m) =>
                Eq (a, b, c, d, e, f, g, h, i, j, k, l, m)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i,
                 Eq j, Eq k, Eq l, Eq m, Eq n) =>
                Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
-        -- Defined in `GHC.Classes'
+        -- Defined in ‛GHC.Classes’
       instance (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i,
                 Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) =>
                Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
-        -- Defined in `GHC.Classes'
-      instance Eq Bool -- Defined in `GHC.Classes'
-      instance Eq Char -- Defined in `GHC.Classes'
-      instance Eq Double -- Defined in `GHC.Classes'
-      instance Eq Float -- Defined in `GHC.Classes'
-      instance Eq Int -- Defined in `GHC.Classes'
-      instance Eq Ordering -- Defined in `GHC.Classes'
-      instance Eq GHC.Types.Word -- Defined in `GHC.Classes'
-      instance Eq a => Eq [a] -- Defined in `GHC.Classes'
-      instance Eq Integer -- Defined in `integer-gmp:GHC.Integer.Type'
-    (The choice depends on the instantiation of `a'
+        -- Defined in ‛GHC.Classes’
+      instance Eq Bool -- Defined in ‛GHC.Classes’
+      instance Eq Char -- Defined in ‛GHC.Classes’
+      instance Eq Double -- Defined in ‛GHC.Classes’
+      instance Eq Float -- Defined in ‛GHC.Classes’
+      instance Eq Int -- Defined in ‛GHC.Classes’
+      instance Eq Ordering -- Defined in ‛GHC.Classes’
+      instance Eq GHC.Types.Word -- Defined in ‛GHC.Classes’
+      instance Eq a => Eq [a] -- Defined in ‛GHC.Classes’
+      instance Eq Integer -- Defined in ‛integer-gmp:GHC.Integer.Type’
+    (The choice depends on the instantiation of ‛a’
      To pick the first instance above, use -XIncoherentInstances
      when compiling the other instance declarations)
     In the expression: x == y
-    In an equation for `f': f x y = x == y
+    In an equation for ‛f’: f x y = x == y
diff --git a/tests/typecheck/should_fail/T5236.stderr b/tests/typecheck/should_fail/T5236.stderr
index 74e460699..b2de3de8d 100644
--- a/tests/typecheck/should_fail/T5236.stderr
+++ b/tests/typecheck/should_fail/T5236.stderr
@@ -1,12 +1,12 @@
-
-T5236.hs:13:9:
-    Couldn't match type `A' with `B'
-    When using functional dependencies to combine
-      Id A A,
-        arising from the dependency `a -> b'
-        in the instance declaration at T5236.hs:10:10
-      Id A B,
-        arising from the type signature for loop :: Id A B => Bool
-        at T5236.hs:13:9-22
-    In the ambiguity check for: Id A B => Bool
-    In the type signature for `loop': loop :: Id A B => Bool
+
+T5236.hs:13:9:
+    Couldn't match type ‛A’ with ‛B’
+    When using functional dependencies to combine
+      Id A A,
+        arising from the dependency ‛a -> b’
+        in the instance declaration at T5236.hs:10:10
+      Id A B,
+        arising from the type signature for loop :: Id A B => Bool
+        at T5236.hs:13:9-22
+    In the ambiguity check for: Id A B => Bool
+    In the type signature for ‛loop’: loop :: Id A B => Bool
diff --git a/tests/typecheck/should_fail/T5246.stderr b/tests/typecheck/should_fail/T5246.stderr
index b37fbf3eb..f494a4c5b 100644
--- a/tests/typecheck/should_fail/T5246.stderr
+++ b/tests/typecheck/should_fail/T5246.stderr
@@ -1,10 +1,10 @@
 
 T5246.hs:11:10:
-    Couldn't match type `[Char]' with `Int'
+    Couldn't match type ‛[Char]’ with ‛Int’
     When using functional dependencies to combine
       ?x::[Char],
         arising from the implicit-parameter bindings for ?x
         at T5246.hs:(10,7)-(11,12)
-      ?x::Int, arising from a use of `foo' at T5246.hs:11:10-12
+      ?x::Int, arising from a use of ‛foo’ at T5246.hs:11:10-12
     In the expression: foo
     In the expression: let ?x = "hello" in foo
diff --git a/tests/typecheck/should_fail/T5300.stderr b/tests/typecheck/should_fail/T5300.stderr
index 749bd22b2..f2652fcbb 100644
--- a/tests/typecheck/should_fail/T5300.stderr
+++ b/tests/typecheck/should_fail/T5300.stderr
@@ -1,32 +1,32 @@
-
-T5300.hs:11:7:
-    Could not deduce (C1 a b c0)
-      arising from the ambiguity check for `f1'
-    from the context (Monad m, C1 a b c)
-      bound by the type signature for
-                 f1 :: (Monad m, C1 a b c) => a -> StateT (T b) m a
-      at T5300.hs:11:7-50
-    The type variable `c0' is ambiguous
-    In the ambiguity check for:
-      forall a b (m :: * -> *) c.
-      (Monad m, C1 a b c) =>
-      a -> StateT (T b) m a
-    In the type signature for `f1':
-      f1 :: (Monad m, C1 a b c) => a -> StateT (T b) m a
-
-T5300.hs:14:7:
-    Could not deduce (C1 a1 b1 c10)
-      arising from the ambiguity check for `f2'
-    from the context (Monad m, C1 a1 b1 c1, C2 a2 b2 c2)
-      bound by the type signature for
-                 f2 :: (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) =>
-                       a1 -> StateT (T b2) m a2
-      at T5300.hs:14:7-69
-    The type variable `c10' is ambiguous
-    In the ambiguity check for:
-      forall a1 b2 (m :: * -> *) a2 b1 c1 c2.
-      (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) =>
-      a1 -> StateT (T b2) m a2
-    In the type signature for `f2':
-      f2 :: (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) =>
-            a1 -> StateT (T b2) m a2
+
+T5300.hs:11:7:
+    Could not deduce (C1 a b c0)
+      arising from the ambiguity check for ‛f1’
+    from the context (Monad m, C1 a b c)
+      bound by the type signature for
+                 f1 :: (Monad m, C1 a b c) => a -> StateT (T b) m a
+      at T5300.hs:11:7-50
+    The type variable ‛c0’ is ambiguous
+    In the ambiguity check for:
+      forall a b (m :: * -> *) c.
+      (Monad m, C1 a b c) =>
+      a -> StateT (T b) m a
+    In the type signature for ‛f1’:
+      f1 :: (Monad m, C1 a b c) => a -> StateT (T b) m a
+
+T5300.hs:14:7:
+    Could not deduce (C1 a1 b1 c10)
+      arising from the ambiguity check for ‛f2’
+    from the context (Monad m, C1 a1 b1 c1, C2 a2 b2 c2)
+      bound by the type signature for
+                 f2 :: (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) =>
+                       a1 -> StateT (T b2) m a2
+      at T5300.hs:14:7-69
+    The type variable ‛c10’ is ambiguous
+    In the ambiguity check for:
+      forall a1 b2 (m :: * -> *) a2 b1 c1 c2.
+      (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) =>
+      a1 -> StateT (T b2) m a2
+    In the type signature for ‛f2’:
+      f2 :: (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) =>
+            a1 -> StateT (T b2) m a2
diff --git a/tests/typecheck/should_fail/T5570.stderr b/tests/typecheck/should_fail/T5570.stderr
index d45eec581..90f9155af 100644
--- a/tests/typecheck/should_fail/T5570.stderr
+++ b/tests/typecheck/should_fail/T5570.stderr
@@ -1,9 +1,9 @@
-
-T5570.hs:7:16:
-    Couldn't match kind `*' with `#'
-    When matching types
-      s0 :: *
-      Double# :: #
-    In the second argument of `($)', namely `D# $ 3.0##'
-    In the expression: print $ D# $ 3.0##
-    In an equation for `main': main = print $ D# $ 3.0##
+
+T5570.hs:7:16:
+    Couldn't match kind ‛*’ with ‛#’
+    When matching types
+      s0 :: *
+      Double# :: #
+    In the second argument of ‛($)’, namely ‛D# $ 3.0##’
+    In the expression: print $ D# $ 3.0##
+    In an equation for ‛main’: main = print $ D# $ 3.0##
diff --git a/tests/typecheck/should_fail/T5684.stderr b/tests/typecheck/should_fail/T5684.stderr
index a94aa8834..f3534f506 100644
--- a/tests/typecheck/should_fail/T5684.stderr
+++ b/tests/typecheck/should_fail/T5684.stderr
@@ -1,64 +1,64 @@
 
 T5684.hs:25:12:
-    No instance for (A b6) arising from a use of `op'
+    No instance for (A b6) arising from a use of ‛op’
     In the expression: op True undefined
     In the expression:
       [op False False, op 'c' undefined, op True undefined]
-    In an equation for `flop1':
+    In an equation for ‛flop1’:
         flop1 = [op False False, op 'c' undefined, op True undefined]
 
 T5684.hs:30:12:
-    No instance for (A b5) arising from a use of `op'
+    No instance for (A b5) arising from a use of ‛op’
     In the expression: op True undefined
     In the expression:
       [op False False, op True undefined, op 'c' undefined]
-    In an equation for `flop2':
+    In an equation for ‛flop2’:
         flop2 = [op False False, op True undefined, op 'c' undefined]
 
 T5684.hs:36:12:
-    No instance for (A b4) arising from a use of `op'
+    No instance for (A b4) arising from a use of ‛op’
     In the expression: op True undefined
     In the expression:
       [op 'c' undefined, op True undefined, op False False]
-    In an equation for `flop3':
+    In an equation for ‛flop3’:
         flop3 = [op 'c' undefined, op True undefined, op False False]
 
 T5684.hs:42:12:
-    No instance for (A b3) arising from a use of `op'
+    No instance for (A b3) arising from a use of ‛op’
     In the expression: op True undefined
     In the expression:
       [op 'c' undefined, op False False, op True undefined]
-    In an equation for `flop4':
+    In an equation for ‛flop4’:
         flop4 = [op 'c' undefined, op False False, op True undefined]
 
 T5684.hs:46:12:
-    No instance for (A b2) arising from a use of `op'
+    No instance for (A b2) arising from a use of ‛op’
     In the expression: op True undefined
     In the expression:
       [op True undefined, op 'c' undefined, op False False]
-    In an equation for `flop5':
+    In an equation for ‛flop5’:
         flop5 = [op True undefined, op 'c' undefined, op False False]
 
 T5684.hs:52:12:
-    No instance for (A b0) arising from a use of `op'
+    No instance for (A b0) arising from a use of ‛op’
     In the expression: op True undefined
     In the expression:
       [op True undefined, op False False, op 'c' undefined]
-    In an equation for `flop6':
+    In an equation for ‛flop6’:
         flop6 = [op True undefined, op False False, op 'c' undefined]
 
 T5684.hs:53:12:
-    No instance for (A Bool) arising from a use of `op'
+    No instance for (A Bool) arising from a use of ‛op’
     In the expression: op False False
     In the expression:
       [op True undefined, op False False, op 'c' undefined]
-    In an equation for `flop6':
+    In an equation for ‛flop6’:
         flop6 = [op True undefined, op False False, op 'c' undefined]
 
 T5684.hs:54:12:
-    No instance for (B Char b1) arising from a use of `op'
+    No instance for (B Char b1) arising from a use of ‛op’
     In the expression: op 'c' undefined
     In the expression:
       [op True undefined, op False False, op 'c' undefined]
-    In an equation for `flop6':
+    In an equation for ‛flop6’:
         flop6 = [op True undefined, op False False, op 'c' undefined]
diff --git a/tests/typecheck/should_fail/T5689.stderr b/tests/typecheck/should_fail/T5689.stderr
index 4bd121078..6fb1f222d 100644
--- a/tests/typecheck/should_fail/T5689.stderr
+++ b/tests/typecheck/should_fail/T5689.stderr
@@ -1,39 +1,39 @@
-
-T5689.hs:10:36:
-    Couldn't match expected type `Bool' with actual type `t'
-    Relevant bindings include
-      r :: IORef (t -> t) (bound at T5689.hs:7:14)
-      v :: t (bound at T5689.hs:10:28)
-    In the expression: v
-    In the expression: if v then False else True
-    In the second argument of `writeIORef', namely
-      `(\ v -> if v then False else True)'
-
-T5689.hs:10:43:
-    Couldn't match expected type `t' with actual type `Bool'
-    Relevant bindings include
-      r :: IORef (t -> t) (bound at T5689.hs:7:14)
-      v :: t (bound at T5689.hs:10:28)
-    In the expression: False
-    In the expression: if v then False else True
-    In the second argument of `writeIORef', namely
-      `(\ v -> if v then False else True)'
-
-T5689.hs:10:54:
-    Couldn't match expected type `t' with actual type `Bool'
-    Relevant bindings include
-      r :: IORef (t -> t) (bound at T5689.hs:7:14)
-      v :: t (bound at T5689.hs:10:28)
-    In the expression: True
-    In the expression: if v then False else True
-    In the second argument of `writeIORef', namely
-      `(\ v -> if v then False else True)'
-
-T5689.hs:14:23:
-    Couldn't match expected type `t' with actual type `Bool'
-    Relevant bindings include
-      r :: IORef (t -> t) (bound at T5689.hs:7:14)
-      c :: t -> t (bound at T5689.hs:12:13)
-    In the first argument of `c', namely `True'
-    In the second argument of `($)', namely `c True'
-    In a stmt of a 'do' block: print $ c True
+
+T5689.hs:10:36:
+    Couldn't match expected type ‛Bool’ with actual type ‛t’
+    Relevant bindings include
+      r :: IORef (t -> t) (bound at T5689.hs:7:14)
+      v :: t (bound at T5689.hs:10:28)
+    In the expression: v
+    In the expression: if v then False else True
+    In the second argument of ‛writeIORef’, namely
+      ‛(\ v -> if v then False else True)’
+
+T5689.hs:10:43:
+    Couldn't match expected type ‛t’ with actual type ‛Bool’
+    Relevant bindings include
+      r :: IORef (t -> t) (bound at T5689.hs:7:14)
+      v :: t (bound at T5689.hs:10:28)
+    In the expression: False
+    In the expression: if v then False else True
+    In the second argument of ‛writeIORef’, namely
+      ‛(\ v -> if v then False else True)’
+
+T5689.hs:10:54:
+    Couldn't match expected type ‛t’ with actual type ‛Bool’
+    Relevant bindings include
+      r :: IORef (t -> t) (bound at T5689.hs:7:14)
+      v :: t (bound at T5689.hs:10:28)
+    In the expression: True
+    In the expression: if v then False else True
+    In the second argument of ‛writeIORef’, namely
+      ‛(\ v -> if v then False else True)’
+
+T5689.hs:14:23:
+    Couldn't match expected type ‛t’ with actual type ‛Bool’
+    Relevant bindings include
+      r :: IORef (t -> t) (bound at T5689.hs:7:14)
+      c :: t -> t (bound at T5689.hs:12:13)
+    In the first argument of ‛c’, namely ‛True’
+    In the second argument of ‛($)’, namely ‛c True’
+    In a stmt of a 'do' block: print $ c True
diff --git a/tests/typecheck/should_fail/T5691.stderr b/tests/typecheck/should_fail/T5691.stderr
index fc517c2d4..4b5676374 100644
--- a/tests/typecheck/should_fail/T5691.stderr
+++ b/tests/typecheck/should_fail/T5691.stderr
@@ -1,17 +1,17 @@
-
-T5691.hs:14:9:
-    Couldn't match type `p' with `PrintRuleInterp'
-    Expected type: PrintRuleInterp a
-      Actual type: p a
-    In the pattern: f :: p a
-    In an equation for `test': test (f :: p a) = MkPRI $ printRule_ f
-    In the instance declaration for `Test PrintRuleInterp'
-
-T5691.hs:15:24:
-    Couldn't match type `p' with `PrintRuleInterp'
-    Expected type: PrintRuleInterp a
-      Actual type: p a
-    Relevant bindings include f :: p a (bound at T5691.hs:14:9)
-    In the first argument of `printRule_', namely `f'
-    In the second argument of `($)', namely `printRule_ f'
-    In the expression: MkPRI $ printRule_ f
+
+T5691.hs:14:9:
+    Couldn't match type ‛p’ with ‛PrintRuleInterp’
+    Expected type: PrintRuleInterp a
+      Actual type: p a
+    In the pattern: f :: p a
+    In an equation for ‛test’: test (f :: p a) = MkPRI $ printRule_ f
+    In the instance declaration for ‛Test PrintRuleInterp’
+
+T5691.hs:15:24:
+    Couldn't match type ‛p’ with ‛PrintRuleInterp’
+    Expected type: PrintRuleInterp a
+      Actual type: p a
+    Relevant bindings include f :: p a (bound at T5691.hs:14:9)
+    In the first argument of ‛printRule_’, namely ‛f’
+    In the second argument of ‛($)’, namely ‛printRule_ f’
+    In the expression: MkPRI $ printRule_ f
diff --git a/tests/typecheck/should_fail/T5853.stderr b/tests/typecheck/should_fail/T5853.stderr
index c36d64e84..4fdef8cdd 100644
--- a/tests/typecheck/should_fail/T5853.stderr
+++ b/tests/typecheck/should_fail/T5853.stderr
@@ -8,7 +8,7 @@ T5853.hs:15:52:
                       Elem (Subst fa a) ~ a,
                       Subst (Subst fa a) (Elem fa) ~ fa)
       bound by the RULE "map/map" at T5853.hs:15:2-57
-    NB: `Subst' is a type function, and may not be injective
+    NB: ‛Subst’ is a type function, and may not be injective
     Relevant bindings include
       xs :: Subst fa a (bound at T5853.hs:15:23)
       g :: a -> Elem fa (bound at T5853.hs:15:21)
diff --git a/tests/typecheck/should_fail/T5858.stderr b/tests/typecheck/should_fail/T5858.stderr
index 437b5baca..893fd1a62 100644
--- a/tests/typecheck/should_fail/T5858.stderr
+++ b/tests/typecheck/should_fail/T5858.stderr
@@ -1,10 +1,10 @@
 
 T5858.hs:11:7:
     No instance for (InferOverloaded ([t0], [t1]))
-      arising from a use of `infer'
-    The type variables `t0', `t1' are ambiguous
+      arising from a use of ‛infer’
+    The type variables ‛t0’, ‛t1’ are ambiguous
     Note: there is a potential instance available:
       instance t1 ~ String => InferOverloaded (t1, t1)
         -- Defined at T5858.hs:8:10
     In the expression: infer ([], [])
-    In an equation for `foo': foo = infer ([], [])
+    In an equation for ‛foo’: foo = infer ([], [])
diff --git a/tests/typecheck/should_fail/T5957.stderr b/tests/typecheck/should_fail/T5957.stderr
index c0bc12a7a..f4300b063 100644
--- a/tests/typecheck/should_fail/T5957.stderr
+++ b/tests/typecheck/should_fail/T5957.stderr
@@ -2,5 +2,5 @@
 T5957.hs:3:9:
     Illegal polymorphic or qualified type: Show a => a -> String
     Perhaps you intended to use -XRankNTypes or -XRank2Types
-    In the type signature for `flex':
+    In the type signature for ‛flex’:
       flex :: Int -> Show a => a -> String
diff --git a/tests/typecheck/should_fail/T5978.stderr b/tests/typecheck/should_fail/T5978.stderr
index 9edfde072..e07acd49b 100644
--- a/tests/typecheck/should_fail/T5978.stderr
+++ b/tests/typecheck/should_fail/T5978.stderr
@@ -1,10 +1,10 @@
-
-T5978.hs:22:11:
-    Couldn't match type `Bool' with `Char'
-    When using functional dependencies to combine
-      C Double Bool,
-        arising from the dependency `from -> to'
-        in the instance declaration at T5978.hs:8:10
-      C Double Char, arising from a use of `polyBar' at T5978.hs:22:11-17
-    In the expression: polyBar id monoFoo
-    In an equation for `monoBar': monoBar = polyBar id monoFoo
+
+T5978.hs:22:11:
+    Couldn't match type ‛Bool’ with ‛Char’
+    When using functional dependencies to combine
+      C Double Bool,
+        arising from the dependency ‛from -> to’
+        in the instance declaration at T5978.hs:8:10
+      C Double Char, arising from a use of ‛polyBar’ at T5978.hs:22:11-17
+    In the expression: polyBar id monoFoo
+    In an equation for ‛monoBar’: monoBar = polyBar id monoFoo
diff --git a/tests/typecheck/should_fail/T6001.stderr b/tests/typecheck/should_fail/T6001.stderr
index 7fe591d54..b1ef88d9f 100644
--- a/tests/typecheck/should_fail/T6001.stderr
+++ b/tests/typecheck/should_fail/T6001.stderr
@@ -2,4 +2,4 @@
 T6001.hs:8:18:
     Method signature does not match class; it should be
       fromInteger :: Integer -> DayKind
-    In the instance declaration for `Num DayKind'
+    In the instance declaration for ‛Num DayKind’
diff --git a/tests/typecheck/should_fail/T6069.stderr b/tests/typecheck/should_fail/T6069.stderr
index b6ce7799b..750dcbc54 100644
--- a/tests/typecheck/should_fail/T6069.stderr
+++ b/tests/typecheck/should_fail/T6069.stderr
@@ -1,24 +1,24 @@
 
 T6069.hs:13:15:
-    Couldn't match type `ST s0 Int' with `forall s. ST s b0'
+    Couldn't match type ‛ST s0 Int’ with ‛forall s. ST s b0’
     Expected type: ST s0 Int -> b0
       Actual type: (forall s. ST s b0) -> b0
-    In the second argument of `(.)', namely `runST'
+    In the second argument of ‛(.)’, namely ‛runST’
     In the expression: print . runST
     In the expression: (print . runST) fourty_two
 
 T6069.hs:14:15:
-    Couldn't match type `ST s1 Int' with `forall s. ST s b1'
+    Couldn't match type ‛ST s1 Int’ with ‛forall s. ST s b1’
     Expected type: ST s1 Int -> b1
       Actual type: (forall s. ST s b1) -> b1
-    In the second argument of `(.)', namely `runST'
+    In the second argument of ‛(.)’, namely ‛runST’
     In the expression: (print . runST)
     In the expression: (print . runST) $ fourty_two
 
 T6069.hs:15:16:
-    Couldn't match type `ST s2 Int' with `forall s. ST s b2'
+    Couldn't match type ‛ST s2 Int’ with ‛forall s. ST s b2’
     Expected type: ST s2 Int -> b2
       Actual type: (forall s. ST s b2) -> b2
-    In the second argument of `(.)', namely `runST'
-    In the first argument of `($)', namely `(print . runST)'
+    In the second argument of ‛(.)’, namely ‛runST’
+    In the first argument of ‛($)’, namely ‛(print . runST)’
     In the expression: (print . runST) $
diff --git a/tests/typecheck/should_fail/T6078.stderr b/tests/typecheck/should_fail/T6078.stderr
index 7690ecd9c..32e3e056d 100644
--- a/tests/typecheck/should_fail/T6078.stderr
+++ b/tests/typecheck/should_fail/T6078.stderr
@@ -7,5 +7,5 @@ T6078.hs:8:10:
       let ip1p@(Ptr ip1) = Ptr ip0 `plusPtr` len in ip1p
     In the expression:
       \ fpbuf ip0 ipe s0 -> let ip1p@(Ptr ip1) = ... in ip1p
-    In an equation for `byteStringSlice':
+    In an equation for ‛byteStringSlice’:
         byteStringSlice len = \ fpbuf ip0 ipe s0 -> let ... in ip1p
diff --git a/tests/typecheck/should_fail/T6161.stderr b/tests/typecheck/should_fail/T6161.stderr
index 089da39f2..afc3a946f 100644
--- a/tests/typecheck/should_fail/T6161.stderr
+++ b/tests/typecheck/should_fail/T6161.stderr
@@ -1,5 +1,5 @@
 
 T6161.hs:29:12:
-    No instance for (Super (Fam Float)) arising from a use of `testDup'
+    No instance for (Super (Fam Float)) arising from a use of ‛testDup’
     In the expression: testDup (FamFloat 3.0)
-    In an equation for `testProg': testProg = testDup (FamFloat 3.0)
+    In an equation for ‛testProg’: testProg = testDup (FamFloat 3.0)
diff --git a/tests/typecheck/should_fail/T7019.stderr b/tests/typecheck/should_fail/T7019.stderr
index 43f1fe520..935c3be52 100644
--- a/tests/typecheck/should_fail/T7019.stderr
+++ b/tests/typecheck/should_fail/T7019.stderr
@@ -1,6 +1,6 @@
 
 T7019.hs:14:10:
-    Malformed predicate `C c'
+    Malformed predicate ‛C c’
     In the context: (C c)
     While checking an instance declaration
-    In the instance declaration for `Monad (Free c)'
+    In the instance declaration for ‛Monad (Free c)’
diff --git a/tests/typecheck/should_fail/T7019a.stderr b/tests/typecheck/should_fail/T7019a.stderr
index 2859f716b..cd474af8a 100644
--- a/tests/typecheck/should_fail/T7019a.stderr
+++ b/tests/typecheck/should_fail/T7019a.stderr
@@ -1,6 +1,6 @@
 
 T7019a.hs:11:1:
-    Malformed predicate `forall b. Context (Associated a b)'
+    Malformed predicate ‛forall b. Context (Associated a b)’
     In the context: (forall b. Context (Associated a b))
-    While checking the super-classes of class `Class'
-    In the class declaration for `Class'
+    While checking the super-classes of class ‛Class’
+    In the class declaration for ‛Class’
diff --git a/tests/typecheck/should_fail/T7175.stderr b/tests/typecheck/should_fail/T7175.stderr
index 92272b6b3..e65918c22 100644
--- a/tests/typecheck/should_fail/T7175.stderr
+++ b/tests/typecheck/should_fail/T7175.stderr
@@ -1,6 +1,6 @@
 
 T7175.hs:8:4:
-    Data constructor `G1C' returns type `F Int'
-      instead of an instance of its parent type `G1 a'
-    In the definition of data constructor `G1C'
-    In the data declaration for `G1'
+    Data constructor ‛G1C’ returns type ‛F Int’
+      instead of an instance of its parent type ‛G1 a’
+    In the definition of data constructor ‛G1C’
+    In the data declaration for ‛G1’
diff --git a/tests/typecheck/should_fail/T7210.stderr b/tests/typecheck/should_fail/T7210.stderr
index d0fbf382c..148f9bcd5 100644
--- a/tests/typecheck/should_fail/T7210.stderr
+++ b/tests/typecheck/should_fail/T7210.stderr
@@ -1,6 +1,6 @@
 
 T7210.hs:5:19:
     Unexpected strictness annotation: !IntMap
-    In the type `!IntMap Int'
-    In the definition of data constructor `C'
-    In the data declaration for `T'
+    In the type ‛!IntMap Int’
+    In the definition of data constructor ‛C’
+    In the data declaration for ‛T’
diff --git a/tests/typecheck/should_fail/T7220.stderr b/tests/typecheck/should_fail/T7220.stderr
index 50860145d..d57e06843 100644
--- a/tests/typecheck/should_fail/T7220.stderr
+++ b/tests/typecheck/should_fail/T7220.stderr
@@ -1,9 +1,9 @@
 
 T7220.hs:24:6:
-    Cannot instantiate unification variable `b0'
+    Cannot instantiate unification variable ‛b0’
     with a type involving foralls: forall b. (C A b, TF b ~ Y) => b
       Perhaps you want -XImpredicativeTypes
     In the expression: f :: (forall b. (C A b, TF b ~ Y) => b) -> X
     In the expression: (f :: (forall b. (C A b, TF b ~ Y) => b) -> X) u
-    In an equation for `v':
+    In an equation for ‛v’:
         v = (f :: (forall b. (C A b, TF b ~ Y) => b) -> X) u
diff --git a/tests/typecheck/should_fail/T7264.stderr b/tests/typecheck/should_fail/T7264.stderr
index 31cc1dfbe..3c0c068af 100644
--- a/tests/typecheck/should_fail/T7264.stderr
+++ b/tests/typecheck/should_fail/T7264.stderr
@@ -1,13 +1,13 @@
 
 T7264.hs:13:19:
-    Couldn't match type `a' with `forall r. r -> String'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛forall r. r -> String’
+      ‛a’ is a rigid type variable bound by
           the inferred type of mkFoo2 :: a -> Maybe Foo at T7264.hs:13:1
     Expected type: a -> Foo
       Actual type: (forall r. r -> String) -> Foo
     Relevant bindings include
       mkFoo2 :: a -> Maybe Foo (bound at T7264.hs:13:1)
       val :: a (bound at T7264.hs:13:8)
-    In the first argument of `mmap', namely `Foo'
+    In the first argument of ‛mmap’, namely ‛Foo’
     In the expression: mmap Foo (Just val)
-    In an equation for `mkFoo2': mkFoo2 val = mmap Foo (Just val)
+    In an equation for ‛mkFoo2’: mkFoo2 val = mmap Foo (Just val)
diff --git a/tests/typecheck/should_fail/T7279.stderr b/tests/typecheck/should_fail/T7279.stderr
index 6af478e52..52793544c 100644
--- a/tests/typecheck/should_fail/T7279.stderr
+++ b/tests/typecheck/should_fail/T7279.stderr
@@ -5,6 +5,6 @@ T7279.hs:6:10:
     from the context (Eq a, Show b)
       bound by an instance declaration: (Eq a, Show b) => Eq (T a)
       at T7279.hs:6:10-35
-    The type variable `b0' is ambiguous
+    The type variable ‛b0’ is ambiguous
     In the ambiguity check for: forall a b. (Eq a, Show b) => Eq (T a)
-    In the instance declaration for `Eq (T a)'
+    In the instance declaration for ‛Eq (T a)’
diff --git a/tests/typecheck/should_fail/T7368.stderr b/tests/typecheck/should_fail/T7368.stderr
index e189c8907..8f1f478b9 100644
--- a/tests/typecheck/should_fail/T7368.stderr
+++ b/tests/typecheck/should_fail/T7368.stderr
@@ -1,20 +1,20 @@
 
 T7368.hs:3:10:
-    Couldn't match kind `* -> *' with `*'
+    Couldn't match kind ‛* -> *’ with ‛*’
     When matching types
       c0 :: (* -> *) -> *
       (->) a0 :: * -> *
     Expected type: a0 -> b0
       Actual type: c0 b1
-    In the return type of a call of `l'
-    Probable cause: `l' is applied to too many arguments
-    In the first argument of `b', namely `(l ())'
+    In the return type of a call of ‛l’
+    Probable cause: ‛l’ is applied to too many arguments
+    In the first argument of ‛b’, namely ‛(l ())’
     In the expression: b (l ())
 
 T7368.hs:3:13:
-    Couldn't match type `()' with `b0 a1'
+    Couldn't match type ‛()’ with ‛b0 a1’
     Expected type: b1 a1
       Actual type: ()
-    In the first argument of `l', namely `()'
-    In the first argument of `b', namely `(l ())'
+    In the first argument of ‛l’, namely ‛()’
+    In the first argument of ‛b’, namely ‛(l ())’
     In the expression: b (l ())
diff --git a/tests/typecheck/should_fail/T7368a.stderr b/tests/typecheck/should_fail/T7368a.stderr
index db0f69fba..bc193cab0 100644
--- a/tests/typecheck/should_fail/T7368a.stderr
+++ b/tests/typecheck/should_fail/T7368a.stderr
@@ -1,10 +1,10 @@
-
-T7368a.hs:8:6:
-    Couldn't match kind `*' with `* -> *'
-    When matching types
-      f :: * -> *
-      Bad :: (* -> *) -> *
-    Expected type: f (Bad f)
-      Actual type: Bad t0
-    In the pattern: Bad x
-    In an equation for `fun': fun (Bad x) = True
+
+T7368a.hs:8:6:
+    Couldn't match kind ‛*’ with ‛* -> *’
+    When matching types
+      f :: * -> *
+      Bad :: (* -> *) -> *
+    Expected type: f (Bad f)
+      Actual type: Bad t0
+    In the pattern: Bad x
+    In an equation for ‛fun’: fun (Bad x) = True
diff --git a/tests/typecheck/should_fail/T7410.stderr b/tests/typecheck/should_fail/T7410.stderr
index 805265146..877377e1b 100644
--- a/tests/typecheck/should_fail/T7410.stderr
+++ b/tests/typecheck/should_fail/T7410.stderr
@@ -1,6 +1,6 @@
 
 T7410.hs:3:9:
-    Expecting one more argument to `Either Int'
-    The first argument of a tuple should have kind `*',
-      but `Either Int' has kind `* -> *'
-    In the type signature for `foo': foo :: (Either Int, Int)
+    Expecting one more argument to ‛Either Int’
+    The first argument of a tuple should have kind ‛*’,
+      but ‛Either Int’ has kind ‛* -> *’
+    In the type signature for ‛foo’: foo :: (Either Int, Int)
diff --git a/tests/typecheck/should_fail/T7453.stderr b/tests/typecheck/should_fail/T7453.stderr
index af88fef12..4a95105f4 100644
--- a/tests/typecheck/should_fail/T7453.stderr
+++ b/tests/typecheck/should_fail/T7453.stderr
@@ -1,7 +1,7 @@
 
 T7453.hs:10:30:
-    Couldn't match expected type `t1' with actual type `t'
-      because type variable `t1' would escape its scope
+    Couldn't match expected type ‛t1’ with actual type ‛t’
+      because type variable ‛t1’ would escape its scope
     This (rigid, skolem) type variable is bound by
       the type signature for z :: Id t1
       at T7453.hs:8:16-19
@@ -10,13 +10,13 @@ T7453.hs:10:30:
       v :: t (bound at T7453.hs:7:7)
       z :: Id t1 (bound at T7453.hs:9:11)
       aux :: Id t1 (bound at T7453.hs:10:21)
-    In the first argument of `Id', namely `v'
+    In the first argument of ‛Id’, namely ‛v’
     In the expression: Id v
-    In an equation for `aux': aux = Id v
+    In an equation for ‛aux’: aux = Id v
 
 T7453.hs:16:33:
-    Couldn't match expected type `t2' with actual type `t'
-      because type variable `t2' would escape its scope
+    Couldn't match expected type ‛t2’ with actual type ‛t’
+      because type variable ‛t2’ would escape its scope
     This (rigid, skolem) type variable is bound by
       the type signature for z :: () -> t2
       at T7453.hs:14:16-22
@@ -25,13 +25,13 @@ T7453.hs:16:33:
       v :: t (bound at T7453.hs:13:7)
       z :: () -> t2 (bound at T7453.hs:15:11)
       aux :: b -> t2 (bound at T7453.hs:16:21)
-    In the first argument of `const', namely `v'
+    In the first argument of ‛const’, namely ‛v’
     In the expression: const v
-    In an equation for `aux': aux = const v
+    In an equation for ‛aux’: aux = const v
 
 T7453.hs:21:15:
-    Couldn't match expected type `t2' with actual type `t'
-      because type variable `t2' would escape its scope
+    Couldn't match expected type ‛t2’ with actual type ‛t’
+      because type variable ‛t2’ would escape its scope
     This (rigid, skolem) type variable is bound by
       the type signature for z :: t2
       at T7453.hs:20:16
@@ -41,11 +41,11 @@ T7453.hs:21:15:
       z :: t2 (bound at T7453.hs:21:11)
       aux :: forall b. b -> t2 (bound at T7453.hs:22:21)
     In the expression: v
-    In an equation for `z':
+    In an equation for ‛z’:
         z = v
           where
               aux = const v
-    In an equation for `cast3':
+    In an equation for ‛cast3’:
         cast3 v
           = z
           where
diff --git a/tests/typecheck/should_fail/T7525.stderr b/tests/typecheck/should_fail/T7525.stderr
index 032de67df..1e2c0eb23 100644
--- a/tests/typecheck/should_fail/T7525.stderr
+++ b/tests/typecheck/should_fail/T7525.stderr
@@ -1,9 +1,9 @@
 
 T7525.hs:5:30:
     Could not deduce (?b::Bool)
-      arising from a use of implicit parameter `?b'
+      arising from a use of implicit parameter ‛?b’
     from the context (?a::Bool)
       bound by the implicit-parameter bindings for ?a at T7525.hs:5:7-31
-    In the second argument of `(&&)', namely `?b'
+    In the second argument of ‛(&&)’, namely ‛?b’
     In the expression: ?a && ?b
     In the expression: let ?a = True in ?a && ?b
diff --git a/tests/typecheck/should_fail/T7545.stderr b/tests/typecheck/should_fail/T7545.stderr
index 1b6a3370d..dc661dae7 100644
--- a/tests/typecheck/should_fail/T7545.stderr
+++ b/tests/typecheck/should_fail/T7545.stderr
@@ -2,4 +2,4 @@
 T7545.hs:8:9:
     Method signature does not match class; it should be
       f :: forall b1. (a -> b) -> b1
-    In the instance declaration for `C (a -> b)'
+    In the instance declaration for ‛C (a -> b)’
diff --git a/tests/typecheck/should_fail/T7609.stderr b/tests/typecheck/should_fail/T7609.stderr
index 1431bcb7c..650329a29 100644
--- a/tests/typecheck/should_fail/T7609.stderr
+++ b/tests/typecheck/should_fail/T7609.stderr
@@ -1,11 +1,11 @@
 
 T7609.hs:7:16:
-    Expecting one more argument to `Maybe'
-    The second argument of a tuple should have kind `*',
-      but `Maybe' has kind `* -> *'
-    In the type signature for `f': f :: (a `X` a, Maybe)
+    Expecting one more argument to ‛Maybe’
+    The second argument of a tuple should have kind ‛*’,
+      but ‛Maybe’ has kind ‛* -> *’
+    In the type signature for ‛f’: f :: (a `X` a, Maybe)
 
 T7609.hs:10:19:
-    Expecting one more argument to `Maybe'
-    Expected a type, but `Maybe' has kind `* -> *'
-    In the type signature for `g': g :: a `X` a => Maybe
+    Expecting one more argument to ‛Maybe’
+    Expected a type, but ‛Maybe’ has kind ‛* -> *’
+    In the type signature for ‛g’: g :: a `X` a => Maybe
diff --git a/tests/typecheck/should_fail/T7645.stderr b/tests/typecheck/should_fail/T7645.stderr
index 96bd2e47c..ae00e21ca 100644
--- a/tests/typecheck/should_fail/T7645.stderr
+++ b/tests/typecheck/should_fail/T7645.stderr
@@ -1,6 +1,6 @@
 
 T7645.hs:6:23:
-    Expecting one more argument to `Maybe'
-    The second argument of a tuple should have kind `*',
-      but `Maybe' has kind `* -> *'
-    In the type signature for `f': f :: ((+) a (a :: *), Maybe)
+    Expecting one more argument to ‛Maybe’
+    The second argument of a tuple should have kind ‛*’,
+      but ‛Maybe’ has kind ‛* -> *’
+    In the type signature for ‛f’: f :: ((+) a (a :: *), Maybe)
diff --git a/tests/typecheck/should_fail/TcMultiWayIfFail.stderr b/tests/typecheck/should_fail/TcMultiWayIfFail.stderr
index fe53beac4..5655af9da 100644
--- a/tests/typecheck/should_fail/TcMultiWayIfFail.stderr
+++ b/tests/typecheck/should_fail/TcMultiWayIfFail.stderr
@@ -1,16 +1,16 @@
 
 TcMultiWayIfFail.hs:6:24:
-    Couldn't match expected type `Int' with actual type `[Char]'
+    Couldn't match expected type ‛Int’ with actual type ‛[Char]’
     In the expression: "2"
     In the expression:
       if | True -> 1 :: Int | False -> "2" | otherwise -> [3 :: Int]
-    In an equation for `x1':
+    In an equation for ‛x1’:
         x1 = if | True -> 1 :: Int | False -> "2" | otherwise -> [3 :: Int]
 
 TcMultiWayIfFail.hs:7:24:
-    Couldn't match expected type `Int' with actual type `[Int]'
+    Couldn't match expected type ‛Int’ with actual type ‛[Int]’
     In the expression: [3 :: Int]
     In the expression:
       if | True -> 1 :: Int | False -> "2" | otherwise -> [3 :: Int]
-    In an equation for `x1':
+    In an equation for ‛x1’:
         x1 = if | True -> 1 :: Int | False -> "2" | otherwise -> [3 :: Int]
diff --git a/tests/typecheck/should_fail/fd-loop.stderr b/tests/typecheck/should_fail/fd-loop.stderr
index 3158a1007..37eae5d95 100644
--- a/tests/typecheck/should_fail/fd-loop.stderr
+++ b/tests/typecheck/should_fail/fd-loop.stderr
@@ -1,12 +1,12 @@
-
-fd-loop.hs:12:10:
-    Variable `b' occurs more often than in the instance head
-      in the constraint: C a b
-    (Use -XUndecidableInstances to permit this)
-    In the instance declaration for `Eq (T a)'
-
-fd-loop.hs:12:10:
-    Variable `b' occurs more often than in the instance head
-      in the constraint: Eq b
-    (Use -XUndecidableInstances to permit this)
-    In the instance declaration for `Eq (T a)'
+
+fd-loop.hs:12:10:
+    Variable ‛b’ occurs more often than in the instance head
+      in the constraint: C a b
+    (Use -XUndecidableInstances to permit this)
+    In the instance declaration for ‛Eq (T a)’
+
+fd-loop.hs:12:10:
+    Variable ‛b’ occurs more often than in the instance head
+      in the constraint: Eq b
+    (Use -XUndecidableInstances to permit this)
+    In the instance declaration for ‛Eq (T a)’
diff --git a/tests/typecheck/should_fail/mc19.stderr b/tests/typecheck/should_fail/mc19.stderr
index 7015d47d7..de2367cfe 100644
--- a/tests/typecheck/should_fail/mc19.stderr
+++ b/tests/typecheck/should_fail/mc19.stderr
@@ -1,7 +1,7 @@
 
 mc19.hs:10:31:
-    Couldn't match type `a' with `[a]'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛[a]’
+      ‛a’ is a rigid type variable bound by
           a type expected by the context: [a] -> [a] at mc19.hs:10:26
     Expected type: [a] -> [a]
       Actual type: [a] -> [[a]]
diff --git a/tests/typecheck/should_fail/mc20.stderr b/tests/typecheck/should_fail/mc20.stderr
index 01048c448..86be7f4a1 100644
--- a/tests/typecheck/should_fail/mc20.stderr
+++ b/tests/typecheck/should_fail/mc20.stderr
@@ -1,6 +1,6 @@
 
 mc20.hs:14:31:
-    No instance for (Ord Unorderable) arising from a use of `groupWith'
+    No instance for (Ord Unorderable) arising from a use of ‛groupWith’
     In the expression: groupWith
     In a stmt of a monad comprehension: then group by x using groupWith
     In the expression:
diff --git a/tests/typecheck/should_fail/mc21.stderr b/tests/typecheck/should_fail/mc21.stderr
index bd7bac1dd..eeda10a39 100644
--- a/tests/typecheck/should_fail/mc21.stderr
+++ b/tests/typecheck/should_fail/mc21.stderr
@@ -1,10 +1,10 @@
 
 mc21.hs:12:26:
-    Couldn't match type `a' with `[a]'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛[a]’
+      ‛a’ is a rigid type variable bound by
           a type expected by the context: [a] -> [[a]] at mc21.hs:12:9
     Expected type: [a] -> [[a]]
       Actual type: [a] -> [a]
-    In the return type of a call of `take'
+    In the return type of a call of ‛take’
     In the expression: take 5
     In a stmt of a monad comprehension: then group using take 5
diff --git a/tests/typecheck/should_fail/mc22.stderr b/tests/typecheck/should_fail/mc22.stderr
index d020bae09..7a4cc4e44 100644
--- a/tests/typecheck/should_fail/mc22.stderr
+++ b/tests/typecheck/should_fail/mc22.stderr
@@ -1,11 +1,11 @@
 
 mc22.hs:10:26:
-    Couldn't match type `a' with `t a'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛t a’
+      ‛a’ is a rigid type variable bound by
           a type expected by the context: [a] -> [t a] at mc22.hs:10:9
     Expected type: [a] -> [t a]
       Actual type: [a] -> [a]
     Relevant bindings include foo :: [t [Char]] (bound at mc22.hs:8:1)
-    In the return type of a call of `take'
+    In the return type of a call of ‛take’
     In the expression: take 5
     In a stmt of a monad comprehension: then group using take 5
diff --git a/tests/typecheck/should_fail/mc23.stderr b/tests/typecheck/should_fail/mc23.stderr
index b8c398728..674c5571d 100644
--- a/tests/typecheck/should_fail/mc23.stderr
+++ b/tests/typecheck/should_fail/mc23.stderr
@@ -1,10 +1,10 @@
 
 mc23.hs:9:29:
-    Couldn't match type `[a0]' with `a -> b'
+    Couldn't match type ‛[a0]’ with ‛a -> b’
     Expected type: (a -> b) -> [a] -> t a
       Actual type: [a0] -> [a0]
     Relevant bindings include z :: t b (bound at mc23.hs:9:1)
-    In the return type of a call of `take'
-    Probable cause: `take' is applied to too many arguments
+    In the return type of a call of ‛take’
+    Probable cause: ‛take’ is applied to too many arguments
     In the expression: take 5
     In a stmt of a monad comprehension: then take 5 by x
diff --git a/tests/typecheck/should_fail/mc24.stderr b/tests/typecheck/should_fail/mc24.stderr
index 92b66b046..8a67d364d 100644
--- a/tests/typecheck/should_fail/mc24.stderr
+++ b/tests/typecheck/should_fail/mc24.stderr
@@ -1,9 +1,9 @@
 
 mc24.hs:10:31:
-    Couldn't match type `[a0]' with `a -> a1'
+    Couldn't match type ‛[a0]’ with ‛a -> a1’
     Expected type: (a -> a1) -> [a] -> t [a]
       Actual type: [a0] -> [a0]
-    In the return type of a call of `take'
-    Probable cause: `take' is applied to too many arguments
+    In the return type of a call of ‛take’
+    Probable cause: ‛take’ is applied to too many arguments
     In the expression: take 2
     In a stmt of a monad comprehension: then group by x using take 2
diff --git a/tests/typecheck/should_fail/mc25.stderr b/tests/typecheck/should_fail/mc25.stderr
index 3925f833f..855ec1eb1 100644
--- a/tests/typecheck/should_fail/mc25.stderr
+++ b/tests/typecheck/should_fail/mc25.stderr
@@ -1,6 +1,6 @@
 
 mc25.hs:9:46:
-    Couldn't match type `Int' with `a -> t'
+    Couldn't match type ‛Int’ with ‛a -> t’
     Expected type: (a -> t) -> [a] -> [t1 a]
       Actual type: Int -> [a] -> [a]
     Relevant bindings include z :: [t1 t] (bound at mc25.hs:9:1)
diff --git a/tests/typecheck/should_fail/tcfail001.stderr b/tests/typecheck/should_fail/tcfail001.stderr
index 8734ee32b..32418ac5c 100644
--- a/tests/typecheck/should_fail/tcfail001.stderr
+++ b/tests/typecheck/should_fail/tcfail001.stderr
@@ -1,7 +1,7 @@
 
 tcfail001.hs:9:2:
-    Couldn't match expected type `[t0] -> [t1]' with actual type `[a]'
+    Couldn't match expected type ‛[t0] -> [t1]’ with actual type ‛[a]’
     Relevant bindings include op :: [a] (bound at tcfail001.hs:9:2)
-    The equation(s) for `op' have one argument,
-    but its type `[a]' has none
-    In the instance declaration for `A [a]'
+    The equation(s) for ‛op’ have one argument,
+    but its type ‛[a]’ has none
+    In the instance declaration for ‛A [a]’
diff --git a/tests/typecheck/should_fail/tcfail002.stderr b/tests/typecheck/should_fail/tcfail002.stderr
index 3a9c89c13..f055d66eb 100644
--- a/tests/typecheck/should_fail/tcfail002.stderr
+++ b/tests/typecheck/should_fail/tcfail002.stderr
@@ -5,4 +5,4 @@ tcfail002.hs:4:7:
       c :: [t] -> t (bound at tcfail002.hs:3:1)
       z :: [t] (bound at tcfail002.hs:4:3)
     In the expression: z
-    In an equation for `c': c z = z
+    In an equation for ‛c’: c z = z
diff --git a/tests/typecheck/should_fail/tcfail003.stderr b/tests/typecheck/should_fail/tcfail003.stderr
index 42d7c5976..e60549789 100644
--- a/tests/typecheck/should_fail/tcfail003.stderr
+++ b/tests/typecheck/should_fail/tcfail003.stderr
@@ -1,6 +1,6 @@
 
 tcfail003.hs:3:10:
-    No instance for (Num Char) arising from the literal `1'
+    No instance for (Num Char) arising from the literal ‛1’
     In the expression: 1
     In the expression: [1, 'a']
     In a pattern binding: (d : e) = [1, 'a']
diff --git a/tests/typecheck/should_fail/tcfail004.stderr b/tests/typecheck/should_fail/tcfail004.stderr
index 112a3aab3..bf439ab34 100644
--- a/tests/typecheck/should_fail/tcfail004.stderr
+++ b/tests/typecheck/should_fail/tcfail004.stderr
@@ -1,7 +1,7 @@
 
 tcfail004.hs:3:9:
-    Couldn't match expected type `(t, t3)'
-                with actual type `(t0, t1, t2)'
+    Couldn't match expected type ‛(t, t3)’
+                with actual type ‛(t0, t1, t2)’
     Relevant bindings include
       g :: t3 (bound at tcfail004.hs:3:4)
       f :: t (bound at tcfail004.hs:3:2)
diff --git a/tests/typecheck/should_fail/tcfail005.stderr b/tests/typecheck/should_fail/tcfail005.stderr
index fa97c98b0..ebb2999f7 100644
--- a/tests/typecheck/should_fail/tcfail005.stderr
+++ b/tests/typecheck/should_fail/tcfail005.stderr
@@ -1,6 +1,6 @@
 
 tcfail005.hs:3:9:
-    Couldn't match expected type `[t]' with actual type `(t0, Char)'
+    Couldn't match expected type ‛[t]’ with actual type ‛(t0, Char)’
     Relevant bindings include
       i :: [t] (bound at tcfail005.hs:3:4)
       h :: t (bound at tcfail005.hs:3:2)
diff --git a/tests/typecheck/should_fail/tcfail006.stderr b/tests/typecheck/should_fail/tcfail006.stderr
index a31f4fdc2..387fe56b4 100644
--- a/tests/typecheck/should_fail/tcfail006.stderr
+++ b/tests/typecheck/should_fail/tcfail006.stderr
@@ -1,6 +1,6 @@
 
 tcfail006.hs:4:24:
-    No instance for (Num Bool) arising from the literal `1'
+    No instance for (Num Bool) arising from the literal ‛1’
     In the expression: 1
     In the expression: (True, 1)
     In a case alternative: True -> (True, 1)
diff --git a/tests/typecheck/should_fail/tcfail007.stderr b/tests/typecheck/should_fail/tcfail007.stderr
index d375e40eb..99c9504a7 100644
--- a/tests/typecheck/should_fail/tcfail007.stderr
+++ b/tests/typecheck/should_fail/tcfail007.stderr
@@ -1,8 +1,8 @@
 
 tcfail007.hs:3:15:
-    No instance for (Num Bool) arising from a use of `+'
+    No instance for (Num Bool) arising from a use of ‛+’
     In the expression: x + 1
-    In an equation for `n':
+    In an equation for ‛n’:
         n x
           | True = x + 1
           | False = True
diff --git a/tests/typecheck/should_fail/tcfail008.stderr b/tests/typecheck/should_fail/tcfail008.stderr
index 7abed93f5..09c4c5455 100644
--- a/tests/typecheck/should_fail/tcfail008.stderr
+++ b/tests/typecheck/should_fail/tcfail008.stderr
@@ -1,20 +1,20 @@
-
-tcfail008.hs:3:5:
-    No instance for (Num a0) arising from the literal `1'
-    The type variable `a0' is ambiguous
-    Relevant bindings include o :: [a0] (bound at tcfail008.hs:3:1)
-    Note: there are several potential instances:
-      instance Num Double -- Defined in `GHC.Float'
-      instance Num Float -- Defined in `GHC.Float'
-      instance Integral a => Num (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
-      ...plus three others
-    In the first argument of `(:)', namely `1'
-    In the expression: 1 : 2
-    In an equation for `o': o = 1 : 2
-
-tcfail008.hs:3:7:
-    No instance for (Num [a0]) arising from the literal `2'
-    In the second argument of `(:)', namely `2'
-    In the expression: 1 : 2
-    In an equation for `o': o = 1 : 2
+
+tcfail008.hs:3:5:
+    No instance for (Num a0) arising from the literal ‛1’
+    The type variable ‛a0’ is ambiguous
+    Relevant bindings include o :: [a0] (bound at tcfail008.hs:3:1)
+    Note: there are several potential instances:
+      instance Num Double -- Defined in ‛GHC.Float’
+      instance Num Float -- Defined in ‛GHC.Float’
+      instance Integral a => Num (GHC.Real.Ratio a)
+        -- Defined in ‛GHC.Real’
+      ...plus three others
+    In the first argument of ‛(:)’, namely ‛1’
+    In the expression: 1 : 2
+    In an equation for ‛o’: o = 1 : 2
+
+tcfail008.hs:3:7:
+    No instance for (Num [a0]) arising from the literal ‛2’
+    In the second argument of ‛(:)’, namely ‛2’
+    In the expression: 1 : 2
+    In an equation for ‛o’: o = 1 : 2
diff --git a/tests/typecheck/should_fail/tcfail009.stderr b/tests/typecheck/should_fail/tcfail009.stderr
index 8226c1fbd..517e39c36 100644
--- a/tests/typecheck/should_fail/tcfail009.stderr
+++ b/tests/typecheck/should_fail/tcfail009.stderr
@@ -1,6 +1,6 @@
 
 tcfail009.hs:3:17:
-    Couldn't match expected type `Int' with actual type `Integer'
+    Couldn't match expected type ‛Int’ with actual type ‛Integer’
     In the expression: (2 :: Integer)
     In the expression: [(1 :: Int) .. (2 :: Integer)]
-    In an equation for `p': p = [(1 :: Int) .. (2 :: Integer)]
+    In an equation for ‛p’: p = [(1 :: Int) .. (2 :: Integer)]
diff --git a/tests/typecheck/should_fail/tcfail010.stderr b/tests/typecheck/should_fail/tcfail010.stderr
index 695655c31..3f718371a 100644
--- a/tests/typecheck/should_fail/tcfail010.stderr
+++ b/tests/typecheck/should_fail/tcfail010.stderr
@@ -1,6 +1,6 @@
 
 tcfail010.hs:3:17:
-    No instance for (Num [t0]) arising from a use of `+'
+    No instance for (Num [t0]) arising from a use of ‛+’
     In the expression: z + 2
     In the expression: \ (y : z) -> z + 2
-    In an equation for `q': q = \ (y : z) -> z + 2
+    In an equation for ‛q’: q = \ (y : z) -> z + 2
diff --git a/tests/typecheck/should_fail/tcfail011.stderr b/tests/typecheck/should_fail/tcfail011.stderr
index f41e3a67c..8ef94fec1 100644
--- a/tests/typecheck/should_fail/tcfail011.stderr
+++ b/tests/typecheck/should_fail/tcfail011.stderr
@@ -1,2 +1,2 @@
 
-tcfail011.hs:3:25: Not in scope: `y'
+tcfail011.hs:3:25: Not in scope: ‛y’
diff --git a/tests/typecheck/should_fail/tcfail012.stderr b/tests/typecheck/should_fail/tcfail012.stderr
index 7d99a18a3..257eca351 100644
--- a/tests/typecheck/should_fail/tcfail012.stderr
+++ b/tests/typecheck/should_fail/tcfail012.stderr
@@ -1,5 +1,5 @@
 
 tcfail012.hs:3:8:
-    Couldn't match expected type `Bool' with actual type `[t0]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[t0]’
     In the expression: []
     In a pattern binding: True = []
diff --git a/tests/typecheck/should_fail/tcfail013.stderr b/tests/typecheck/should_fail/tcfail013.stderr
index a1fd433f6..075c4dab8 100644
--- a/tests/typecheck/should_fail/tcfail013.stderr
+++ b/tests/typecheck/should_fail/tcfail013.stderr
@@ -1,6 +1,6 @@
 
 tcfail013.hs:4:3:
-    Couldn't match expected type `[t]' with actual type `Bool'
+    Couldn't match expected type ‛[t]’ with actual type ‛Bool’
     Relevant bindings include f :: [t] -> a (bound at tcfail013.hs:3:1)
     In the pattern: True
-    In an equation for `f': f True = 2
+    In an equation for ‛f’: f True = 2
diff --git a/tests/typecheck/should_fail/tcfail014.stderr b/tests/typecheck/should_fail/tcfail014.stderr
index 713ffce5e..1e4b637a9 100644
--- a/tests/typecheck/should_fail/tcfail014.stderr
+++ b/tests/typecheck/should_fail/tcfail014.stderr
@@ -4,6 +4,6 @@ tcfail014.hs:5:33:
     Relevant bindings include
       h :: (t8 -> t7) -> t7 (bound at tcfail014.hs:5:25)
       z :: t8 -> t7 (bound at tcfail014.hs:5:27)
-    In the first argument of `z', namely `z'
+    In the first argument of ‛z’, namely ‛z’
     In the expression: z z
-    In an equation for `h': h z = z z
+    In an equation for ‛h’: h z = z z
diff --git a/tests/typecheck/should_fail/tcfail015.stderr b/tests/typecheck/should_fail/tcfail015.stderr
index 41899dffb..7e0225376 100644
--- a/tests/typecheck/should_fail/tcfail015.stderr
+++ b/tests/typecheck/should_fail/tcfail015.stderr
@@ -1,5 +1,5 @@
 
 tcfail015.hs:7:13:
-    No instance for (Num Bool) arising from the literal `2'
+    No instance for (Num Bool) arising from the literal ‛2’
     In the expression: 2
-    In an equation for `g': g (ANull) = 2
+    In an equation for ‛g’: g (ANull) = 2
diff --git a/tests/typecheck/should_fail/tcfail016.stderr b/tests/typecheck/should_fail/tcfail016.stderr
index 17f2f16e4..15122e8e1 100644
--- a/tests/typecheck/should_fail/tcfail016.stderr
+++ b/tests/typecheck/should_fail/tcfail016.stderr
@@ -1,24 +1,24 @@
 
 tcfail016.hs:9:20:
-    Couldn't match type `(t, Expr t)' with `Expr t'
+    Couldn't match type ‛(t, Expr t)’ with ‛Expr t’
     Expected type: Expr t
       Actual type: AnnExpr t
     Relevant bindings include
       g :: Expr t -> [[Char]] (bound at tcfail016.hs:8:1)
       e1 :: AnnExpr t (bound at tcfail016.hs:9:8)
       e2 :: AnnExpr t (bound at tcfail016.hs:9:11)
-    In the first argument of `g', namely `e1'
-    In the first argument of `(++)', namely `(g e1)'
+    In the first argument of ‛g’, namely ‛e1’
+    In the first argument of ‛(++)’, namely ‛(g e1)’
     In the expression: (g e1) ++ (g e2)
 
 tcfail016.hs:9:28:
-    Couldn't match type `(t, Expr t)' with `Expr t'
+    Couldn't match type ‛(t, Expr t)’ with ‛Expr t’
     Expected type: Expr t
       Actual type: AnnExpr t
     Relevant bindings include
       g :: Expr t -> [[Char]] (bound at tcfail016.hs:8:1)
       e1 :: AnnExpr t (bound at tcfail016.hs:9:8)
       e2 :: AnnExpr t (bound at tcfail016.hs:9:11)
-    In the first argument of `g', namely `e2'
-    In the second argument of `(++)', namely `(g e2)'
+    In the first argument of ‛g’, namely ‛e2’
+    In the second argument of ‛(++)’, namely ‛(g e2)’
     In the expression: (g e1) ++ (g e2)
diff --git a/tests/typecheck/should_fail/tcfail017.stderr b/tests/typecheck/should_fail/tcfail017.stderr
index 006ff73d1..a0d73da86 100644
--- a/tests/typecheck/should_fail/tcfail017.stderr
+++ b/tests/typecheck/should_fail/tcfail017.stderr
@@ -4,4 +4,4 @@ tcfail017.hs:10:10:
       arising from the superclasses of an instance declaration
     from the context (B a)
       bound by the instance declaration at tcfail017.hs:10:10-23
-    In the instance declaration for `B [a]'
+    In the instance declaration for ‛B [a]’
diff --git a/tests/typecheck/should_fail/tcfail018.stderr b/tests/typecheck/should_fail/tcfail018.stderr
index 67b3cbb47..687938983 100644
--- a/tests/typecheck/should_fail/tcfail018.stderr
+++ b/tests/typecheck/should_fail/tcfail018.stderr
@@ -1,5 +1,5 @@
 
 tcfail018.hs:5:10:
-    No instance for (Num [t0]) arising from the literal `1'
+    No instance for (Num [t0]) arising from the literal ‛1’
     In the expression: 1
     In a pattern binding: (a : []) = 1
diff --git a/tests/typecheck/should_fail/tcfail019.stderr b/tests/typecheck/should_fail/tcfail019.stderr
index 79ab41179..848805abd 100644
--- a/tests/typecheck/should_fail/tcfail019.stderr
+++ b/tests/typecheck/should_fail/tcfail019.stderr
@@ -2,4 +2,4 @@
 tcfail019.hs:18:10:
     No instance for (B [a])
       arising from the superclasses of an instance declaration
-    In the instance declaration for `D [a]'
+    In the instance declaration for ‛D [a]’
diff --git a/tests/typecheck/should_fail/tcfail020.stderr b/tests/typecheck/should_fail/tcfail020.stderr
index 13ef851ed..9dfaa63a4 100644
--- a/tests/typecheck/should_fail/tcfail020.stderr
+++ b/tests/typecheck/should_fail/tcfail020.stderr
@@ -4,4 +4,4 @@ tcfail020.hs:10:10:
       arising from the superclasses of an instance declaration
     from the context (A a)
       bound by the instance declaration at tcfail020.hs:10:10-23
-    In the instance declaration for `B [a]'
+    In the instance declaration for ‛B [a]’
diff --git a/tests/typecheck/should_fail/tcfail027.stderr b/tests/typecheck/should_fail/tcfail027.stderr
index c5df0bcbf..cc4ffcaab 100644
--- a/tests/typecheck/should_fail/tcfail027.stderr
+++ b/tests/typecheck/should_fail/tcfail027.stderr
@@ -1,8 +1,8 @@
 
 tcfail027.hs:4:1:
     Cycle in class declaration (via superclasses): A -> B -> A
-    In the class declaration for `A'
+    In the class declaration for ‛A’
 
 tcfail027.hs:7:1:
     Cycle in class declaration (via superclasses): B -> A -> B
-    In the class declaration for `B'
+    In the class declaration for ‛B’
diff --git a/tests/typecheck/should_fail/tcfail028.stderr b/tests/typecheck/should_fail/tcfail028.stderr
index 53e3f7614..a5c0a5961 100644
--- a/tests/typecheck/should_fail/tcfail028.stderr
+++ b/tests/typecheck/should_fail/tcfail028.stderr
@@ -1,7 +1,7 @@
 
 tcfail028.hs:4:17:
-    Expecting one more argument to `A a'
-    Expected a type, but `A a' has kind `k0 -> *'
-    In the type `A a'
-    In the definition of data constructor `B'
-    In the data declaration for `A'
+    Expecting one more argument to ‛A a’
+    Expected a type, but ‛A a’ has kind ‛k0 -> *’
+    In the type ‛A a’
+    In the definition of data constructor ‛B’
+    In the data declaration for ‛A’
diff --git a/tests/typecheck/should_fail/tcfail029.stderr b/tests/typecheck/should_fail/tcfail029.stderr
index d9cb86238..13a1e4936 100644
--- a/tests/typecheck/should_fail/tcfail029.stderr
+++ b/tests/typecheck/should_fail/tcfail029.stderr
@@ -1,5 +1,5 @@
 
 tcfail029.hs:6:9:
-    No instance for (Ord Foo) arising from a use of `>'
+    No instance for (Ord Foo) arising from a use of ‛>’
     In the expression: x > Bar
-    In an equation for `f': f x = x > Bar
+    In an equation for ‛f’: f x = x > Bar
diff --git a/tests/typecheck/should_fail/tcfail030.stderr b/tests/typecheck/should_fail/tcfail030.stderr
index cb9d80959..e0a8b494f 100644
--- a/tests/typecheck/should_fail/tcfail030.stderr
+++ b/tests/typecheck/should_fail/tcfail030.stderr
@@ -1,3 +1,3 @@
 
 tcfail030.hs:1:1:
-    The function `main' is not defined in module `Main'
+    The function ‛main’ is not defined in module ‛Main’
diff --git a/tests/typecheck/should_fail/tcfail031.stderr b/tests/typecheck/should_fail/tcfail031.stderr
index f7fc14bb1..5d55430ea 100644
--- a/tests/typecheck/should_fail/tcfail031.stderr
+++ b/tests/typecheck/should_fail/tcfail031.stderr
@@ -1,6 +1,6 @@
 
 tcfail031.hs:3:10:
-    Couldn't match expected type `Bool' with actual type `Char'
+    Couldn't match expected type ‛Bool’ with actual type ‛Char’
     In the expression: 'a'
     In the expression: if 'a' then 1 else 2
-    In an equation for `f': f x = if 'a' then 1 else 2
+    In an equation for ‛f’: f x = if 'a' then 1 else 2
diff --git a/tests/typecheck/should_fail/tcfail032.stderr b/tests/typecheck/should_fail/tcfail032.stderr
index 5a93f8c66..56e4a791a 100644
--- a/tests/typecheck/should_fail/tcfail032.stderr
+++ b/tests/typecheck/should_fail/tcfail032.stderr
@@ -1,7 +1,7 @@
 
 tcfail032.hs:14:8:
-    Couldn't match expected type `a1 -> Int' with actual type `t'
-      because type variable `a1' would escape its scope
+    Couldn't match expected type ‛a1 -> Int’ with actual type ‛t’
+      because type variable ‛a1’ would escape its scope
     This (rigid, skolem) type variable is bound by
       an expression type signature: Eq a1 => a1 -> Int
       at tcfail032.hs:14:8-30
@@ -9,4 +9,4 @@ tcfail032.hs:14:8:
       f :: t -> a -> Int (bound at tcfail032.hs:14:1)
       x :: t (bound at tcfail032.hs:14:3)
     In the expression: (x :: Eq a => a -> Int)
-    In an equation for `f': f x = (x :: Eq a => a -> Int)
+    In an equation for ‛f’: f x = (x :: Eq a => a -> Int)
diff --git a/tests/typecheck/should_fail/tcfail033.stderr b/tests/typecheck/should_fail/tcfail033.stderr
index 538228433..0ebb5c826 100644
--- a/tests/typecheck/should_fail/tcfail033.stderr
+++ b/tests/typecheck/should_fail/tcfail033.stderr
@@ -7,4 +7,4 @@ tcfail033.hs:4:12:
       y :: t1 (bound at tcfail033.hs:4:19)
     In the expression: x
     In the expression: [x | (x, y) <- buglet]
-    In an equation for `buglet': buglet = [x | (x, y) <- buglet]
+    In an equation for ‛buglet’: buglet = [x | (x, y) <- buglet]
diff --git a/tests/typecheck/should_fail/tcfail034.stderr b/tests/typecheck/should_fail/tcfail034.stderr
index 38b04c10c..3fca8122b 100644
--- a/tests/typecheck/should_fail/tcfail034.stderr
+++ b/tests/typecheck/should_fail/tcfail034.stderr
@@ -1,12 +1,12 @@
 
 tcfail034.hs:17:13:
-    Could not deduce (Integral a) arising from a use of `mod'
+    Could not deduce (Integral a) arising from a use of ‛mod’
     from the context (Num a, Eq a)
       bound by the type signature for test :: (Num a, Eq a) => a -> Bool
       at tcfail034.hs:16:7-32
     Possible fix:
       add (Integral a) to the context of
         the type signature for test :: (Num a, Eq a) => a -> Bool
-    In the first argument of `(==)', namely `(x `mod` 3)'
+    In the first argument of ‛(==)’, namely ‛(x `mod` 3)’
     In the expression: (x `mod` 3) == 0
-    In an equation for `test': test x = (x `mod` 3) == 0
+    In an equation for ‛test’: test x = (x `mod` 3) == 0
diff --git a/tests/typecheck/should_fail/tcfail036.stderr b/tests/typecheck/should_fail/tcfail036.stderr
index 98d172278..465e45471 100644
--- a/tests/typecheck/should_fail/tcfail036.stderr
+++ b/tests/typecheck/should_fail/tcfail036.stderr
@@ -5,7 +5,7 @@ tcfail036.hs:6:10:
       instance Num NUM -- Defined at tcfail036.hs:8:10
 
 tcfail036.hs:9:13:
-    Expecting one more argument to `Num'
-    The first argument of `Eq' should have kind `*',
-      but `Num' has kind `* -> Constraint'
-    In the instance declaration for `Eq Num'
+    Expecting one more argument to ‛Num’
+    The first argument of ‛Eq’ should have kind ‛*’,
+      but ‛Num’ has kind ‛* -> Constraint’
+    In the instance declaration for ‛Eq Num’
diff --git a/tests/typecheck/should_fail/tcfail037.stderr b/tests/typecheck/should_fail/tcfail037.stderr
index 998a68ccd..00f757841 100644
--- a/tests/typecheck/should_fail/tcfail037.stderr
+++ b/tests/typecheck/should_fail/tcfail037.stderr
@@ -1,8 +1,8 @@
 
 tcfail037.hs:7:11:
-    Ambiguous occurrence `+'
-    It could refer to either `ShouldFail.+',
+    Ambiguous occurrence ‛+’
+    It could refer to either ‛ShouldFail.+’,
                              defined at tcfail037.hs:10:5
-                          or `Prelude.+',
-                             imported from `Prelude' at tcfail037.hs:3:8-17
-                             (and originally defined in `GHC.Num')
+                          or ‛Prelude.+’,
+                             imported from ‛Prelude’ at tcfail037.hs:3:8-17
+                             (and originally defined in ‛GHC.Num’)
diff --git a/tests/typecheck/should_fail/tcfail038.stderr b/tests/typecheck/should_fail/tcfail038.stderr
index 70e13f3c7..f8b7915e0 100644
--- a/tests/typecheck/should_fail/tcfail038.stderr
+++ b/tests/typecheck/should_fail/tcfail038.stderr
@@ -1,10 +1,10 @@
 
 tcfail038.hs:7:11:
-    Conflicting definitions for `=='
+    Conflicting definitions for ‛==’
     Bound at: tcfail038.hs:7:11-12
               tcfail038.hs:9:11-12
 
 tcfail038.hs:8:11:
-    Conflicting definitions for `/='
+    Conflicting definitions for ‛/=’
     Bound at: tcfail038.hs:8:11-12
               tcfail038.hs:10:11-12
diff --git a/tests/typecheck/should_fail/tcfail040.stderr b/tests/typecheck/should_fail/tcfail040.stderr
index 003cb9f6d..90fb76d99 100644
--- a/tests/typecheck/should_fail/tcfail040.stderr
+++ b/tests/typecheck/should_fail/tcfail040.stderr
@@ -1,9 +1,9 @@
-
-tcfail040.hs:19:5:
-    No instance for (ORD a0) arising from a use of `<<'
-    The type variable `a0' is ambiguous
-    Note: there is a potential instance available:
-      instance ORD (a -> b) -- Defined at tcfail040.hs:17:10
-    In the first argument of `(===)', namely `(<<)'
-    In the expression: (<<) === (<<)
-    In an equation for `f': f = (<<) === (<<)
+
+tcfail040.hs:19:5:
+    No instance for (ORD a0) arising from a use of ‛<<’
+    The type variable ‛a0’ is ambiguous
+    Note: there is a potential instance available:
+      instance ORD (a -> b) -- Defined at tcfail040.hs:17:10
+    In the first argument of ‛(===)’, namely ‛(<<)’
+    In the expression: (<<) === (<<)
+    In an equation for ‛f’: f = (<<) === (<<)
diff --git a/tests/typecheck/should_fail/tcfail041.stderr b/tests/typecheck/should_fail/tcfail041.stderr
index ae8cd47ae..f86384133 100644
--- a/tests/typecheck/should_fail/tcfail041.stderr
+++ b/tests/typecheck/should_fail/tcfail041.stderr
@@ -2,4 +2,4 @@
 tcfail041.hs:9:10:
     Unbound implicit parameter (?imp::Int)
       arising from the superclasses of an instance declaration
-    In the instance declaration for `D Int'
+    In the instance declaration for ‛D Int’
diff --git a/tests/typecheck/should_fail/tcfail042.stderr b/tests/typecheck/should_fail/tcfail042.stderr
index 76031bb22..1e1c5ad01 100644
--- a/tests/typecheck/should_fail/tcfail042.stderr
+++ b/tests/typecheck/should_fail/tcfail042.stderr
@@ -6,4 +6,4 @@ tcfail042.hs:15:10:
       bound by the instance declaration at tcfail042.hs:15:10-34
     Possible fix:
       add (Num a) to the context of the instance declaration
-    In the instance declaration for `Bar [a]'
+    In the instance declaration for ‛Bar [a]’
diff --git a/tests/typecheck/should_fail/tcfail043.stderr b/tests/typecheck/should_fail/tcfail043.stderr
index ef4e99999..9be218f04 100644
--- a/tests/typecheck/should_fail/tcfail043.stderr
+++ b/tests/typecheck/should_fail/tcfail043.stderr
@@ -1,40 +1,40 @@
-
-tcfail043.hs:38:17:
-    No instance for (Ord_ a0) arising from a use of `gt'
-    The type variable `a0' is ambiguous
-    Relevant bindings include
-      search :: a0 -> [a0] -> Bool (bound at tcfail043.hs:37:1)
-      a :: a0 (bound at tcfail043.hs:38:6)
-      bs :: [a0] (bound at tcfail043.hs:38:8)
-    Note: there is a potential instance available:
-      instance Ord_ Int -- Defined at tcfail043.hs:34:10
-    In the expression: gt (hd bs) a
-    In the expression:
-      if gt (hd bs) a then
-          False
-      else
-          if eq a (hd bs) then True else search a (tl bs)
-    In the expression:
-      \ a bs
-        -> if gt (hd bs) a then
-               False
-           else
-               if eq a (hd bs) then True else search a (tl bs)
-
-tcfail043.hs:40:25:
-    No instance for (Eq_ a0) arising from a use of `eq'
-    The type variable `a0' is ambiguous
-    Relevant bindings include
-      search :: a0 -> [a0] -> Bool (bound at tcfail043.hs:37:1)
-      a :: a0 (bound at tcfail043.hs:38:6)
-      bs :: [a0] (bound at tcfail043.hs:38:8)
-    Note: there are several potential instances:
-      instance Eq_ a => Eq_ [a] -- Defined at tcfail043.hs:23:10
-      instance Eq_ Int -- Defined at tcfail043.hs:20:10
-    In the expression: eq a (hd bs)
-    In the expression: if eq a (hd bs) then True else search a (tl bs)
-    In the expression:
-      if gt (hd bs) a then
-          False
-      else
-          if eq a (hd bs) then True else search a (tl bs)
+
+tcfail043.hs:38:17:
+    No instance for (Ord_ a0) arising from a use of ‛gt’
+    The type variable ‛a0’ is ambiguous
+    Relevant bindings include
+      search :: a0 -> [a0] -> Bool (bound at tcfail043.hs:37:1)
+      a :: a0 (bound at tcfail043.hs:38:6)
+      bs :: [a0] (bound at tcfail043.hs:38:8)
+    Note: there is a potential instance available:
+      instance Ord_ Int -- Defined at tcfail043.hs:34:10
+    In the expression: gt (hd bs) a
+    In the expression:
+      if gt (hd bs) a then
+          False
+      else
+          if eq a (hd bs) then True else search a (tl bs)
+    In the expression:
+      \ a bs
+        -> if gt (hd bs) a then
+               False
+           else
+               if eq a (hd bs) then True else search a (tl bs)
+
+tcfail043.hs:40:25:
+    No instance for (Eq_ a0) arising from a use of ‛eq’
+    The type variable ‛a0’ is ambiguous
+    Relevant bindings include
+      search :: a0 -> [a0] -> Bool (bound at tcfail043.hs:37:1)
+      a :: a0 (bound at tcfail043.hs:38:6)
+      bs :: [a0] (bound at tcfail043.hs:38:8)
+    Note: there are several potential instances:
+      instance Eq_ a => Eq_ [a] -- Defined at tcfail043.hs:23:10
+      instance Eq_ Int -- Defined at tcfail043.hs:20:10
+    In the expression: eq a (hd bs)
+    In the expression: if eq a (hd bs) then True else search a (tl bs)
+    In the expression:
+      if gt (hd bs) a then
+          False
+      else
+          if eq a (hd bs) then True else search a (tl bs)
diff --git a/tests/typecheck/should_fail/tcfail044.stderr b/tests/typecheck/should_fail/tcfail044.stderr
index 03ad2fb70..ab3b94f00 100644
--- a/tests/typecheck/should_fail/tcfail044.stderr
+++ b/tests/typecheck/should_fail/tcfail044.stderr
@@ -1,16 +1,16 @@
 
 tcfail044.hs:5:20:
-    Illegal instance declaration for `Eq (a -> a)'
+    Illegal instance declaration for ‛Eq (a -> a)’
       (All instance types must be of the form (T a1 ... an)
        where a1 ... an are *distinct type variables*,
        and each type variable appears at most once in the instance head.
        Use -XFlexibleInstances if you want to disable this.)
-    In the instance declaration for `Eq (a -> a)'
+    In the instance declaration for ‛Eq (a -> a)’
 
 tcfail044.hs:8:21:
-    Illegal instance declaration for `Num (a -> a)'
+    Illegal instance declaration for ‛Num (a -> a)’
       (All instance types must be of the form (T a1 ... an)
        where a1 ... an are *distinct type variables*,
        and each type variable appears at most once in the instance head.
        Use -XFlexibleInstances if you want to disable this.)
-    In the instance declaration for `Num (a -> a)'
+    In the instance declaration for ‛Num (a -> a)’
diff --git a/tests/typecheck/should_fail/tcfail047.stderr b/tests/typecheck/should_fail/tcfail047.stderr
index e99d9df75..5c96920f0 100644
--- a/tests/typecheck/should_fail/tcfail047.stderr
+++ b/tests/typecheck/should_fail/tcfail047.stderr
@@ -1,8 +1,8 @@
 
 tcfail047.hs:6:10:
-    Illegal instance declaration for `A (a, (b, c))'
+    Illegal instance declaration for ‛A (a, (b, c))’
       (All instance types must be of the form (T a1 ... an)
        where a1 ... an are *distinct type variables*,
        and each type variable appears at most once in the instance head.
        Use -XFlexibleInstances if you want to disable this.)
-    In the instance declaration for `A (a, (b, c))'
+    In the instance declaration for ‛A (a, (b, c))’
diff --git a/tests/typecheck/should_fail/tcfail048.stderr b/tests/typecheck/should_fail/tcfail048.stderr
index aa1330d46..29d205e27 100644
--- a/tests/typecheck/should_fail/tcfail048.stderr
+++ b/tests/typecheck/should_fail/tcfail048.stderr
@@ -1,2 +1,2 @@
 
-tcfail048.hs:3:8: Not in scope: type constructor or class `B'
+tcfail048.hs:3:8: Not in scope: type constructor or class ‛B’
diff --git a/tests/typecheck/should_fail/tcfail049.stderr b/tests/typecheck/should_fail/tcfail049.stderr
index 750a65bc3..3a632e242 100644
--- a/tests/typecheck/should_fail/tcfail049.stderr
+++ b/tests/typecheck/should_fail/tcfail049.stderr
@@ -1,2 +1,2 @@
 
-tcfail049.hs:3:7: Not in scope: `g'
+tcfail049.hs:3:7: Not in scope: ‛g’
diff --git a/tests/typecheck/should_fail/tcfail050.stderr b/tests/typecheck/should_fail/tcfail050.stderr
index 9115af93f..5d7a917f5 100644
--- a/tests/typecheck/should_fail/tcfail050.stderr
+++ b/tests/typecheck/should_fail/tcfail050.stderr
@@ -1,2 +1,2 @@
 
-tcfail050.hs:3:7: Not in scope: data constructor `B'
+tcfail050.hs:3:7: Not in scope: data constructor ‛B’
diff --git a/tests/typecheck/should_fail/tcfail051.stderr b/tests/typecheck/should_fail/tcfail051.stderr
index 35a33d2aa..f4b0c0c56 100644
--- a/tests/typecheck/should_fail/tcfail051.stderr
+++ b/tests/typecheck/should_fail/tcfail051.stderr
@@ -1,2 +1,2 @@
-
-tcfail051.hs:3:10: Not in scope: type constructor or class `B'
+
+tcfail051.hs:3:10: Not in scope: type constructor or class ‛B’
diff --git a/tests/typecheck/should_fail/tcfail052.stderr b/tests/typecheck/should_fail/tcfail052.stderr
index 9ffa31c22..2359b4433 100644
--- a/tests/typecheck/should_fail/tcfail052.stderr
+++ b/tests/typecheck/should_fail/tcfail052.stderr
@@ -1,2 +1,2 @@
 
-tcfail052.hs:3:16: Not in scope: type variable `c'
+tcfail052.hs:3:16: Not in scope: type variable ‛c’
diff --git a/tests/typecheck/should_fail/tcfail053.stderr b/tests/typecheck/should_fail/tcfail053.stderr
index 9889c3f0f..c014f2f4f 100644
--- a/tests/typecheck/should_fail/tcfail053.stderr
+++ b/tests/typecheck/should_fail/tcfail053.stderr
@@ -1,2 +1,2 @@
 
-tcfail053.hs:3:12: Not in scope: type constructor or class `A'
+tcfail053.hs:3:12: Not in scope: type constructor or class ‛A’
diff --git a/tests/typecheck/should_fail/tcfail054.stderr b/tests/typecheck/should_fail/tcfail054.stderr
index 1a5cfca05..93b200983 100644
--- a/tests/typecheck/should_fail/tcfail054.stderr
+++ b/tests/typecheck/should_fail/tcfail054.stderr
@@ -1,2 +1,2 @@
 
-tcfail054.hs:3:4: Not in scope: data constructor `B'
+tcfail054.hs:3:4: Not in scope: data constructor ‛B’
diff --git a/tests/typecheck/should_fail/tcfail055.stderr b/tests/typecheck/should_fail/tcfail055.stderr
index ac012da98..c82e9af2a 100644
--- a/tests/typecheck/should_fail/tcfail055.stderr
+++ b/tests/typecheck/should_fail/tcfail055.stderr
@@ -1,5 +1,5 @@
 
 tcfail055.hs:3:8:
-    Couldn't match expected type `Float' with actual type `Int'
+    Couldn't match expected type ‛Float’ with actual type ‛Int’
     In the expression: (x + 1 :: Int) :: Float
-    In an equation for `f': f x = (x + 1 :: Int) :: Float
+    In an equation for ‛f’: f x = (x + 1 :: Int) :: Float
diff --git a/tests/typecheck/should_fail/tcfail056.stderr b/tests/typecheck/should_fail/tcfail056.stderr
index 09505ed94..60bba9745 100644
--- a/tests/typecheck/should_fail/tcfail056.stderr
+++ b/tests/typecheck/should_fail/tcfail056.stderr
@@ -1,2 +1,2 @@
 
-tcfail056.hs:10:15: `<=' is not a (visible) method of class `Eq'
+tcfail056.hs:10:15: ‛<=’ is not a (visible) method of class ‛Eq’
diff --git a/tests/typecheck/should_fail/tcfail057.stderr b/tests/typecheck/should_fail/tcfail057.stderr
index 9399e9148..5b19563bf 100644
--- a/tests/typecheck/should_fail/tcfail057.stderr
+++ b/tests/typecheck/should_fail/tcfail057.stderr
@@ -1,4 +1,4 @@
 
 tcfail057.hs:5:7:
-    Expected a type, but `RealFrac a' has kind `Constraint'
-    In the type signature for `f': f :: (RealFrac a) -> a -> a
+    Expected a type, but ‛RealFrac a’ has kind ‛Constraint’
+    In the type signature for ‛f’: f :: (RealFrac a) -> a -> a
diff --git a/tests/typecheck/should_fail/tcfail058.stderr b/tests/typecheck/should_fail/tcfail058.stderr
index 880bef69e..f5770a42d 100644
--- a/tests/typecheck/should_fail/tcfail058.stderr
+++ b/tests/typecheck/should_fail/tcfail058.stderr
@@ -1,5 +1,5 @@
 
 tcfail058.hs:6:7:
-    Expecting one more argument to `Array a'
-    Expected a constraint, but `Array a' has kind `* -> *'
-    In the type signature for `f': f :: Array a => a -> b
+    Expecting one more argument to ‛Array a’
+    Expected a constraint, but ‛Array a’ has kind ‛* -> *’
+    In the type signature for ‛f’: f :: Array a => a -> b
diff --git a/tests/typecheck/should_fail/tcfail061.stderr b/tests/typecheck/should_fail/tcfail061.stderr
index a047863e9..14ce5aec7 100644
--- a/tests/typecheck/should_fail/tcfail061.stderr
+++ b/tests/typecheck/should_fail/tcfail061.stderr
@@ -1,8 +1,8 @@
 
-tcfail061.hs:5:17: Not in scope: type variable `b'
+tcfail061.hs:5:17: Not in scope: type variable ‛b’
 
-tcfail061.hs:5:19: Not in scope: type variable `b'
+tcfail061.hs:5:19: Not in scope: type variable ‛b’
 
-tcfail061.hs:11:22: Not in scope: type variable `b'
+tcfail061.hs:11:22: Not in scope: type variable ‛b’
 
-tcfail061.hs:11:24: Not in scope: type variable `b'
+tcfail061.hs:11:24: Not in scope: type variable ‛b’
diff --git a/tests/typecheck/should_fail/tcfail062.stderr b/tests/typecheck/should_fail/tcfail062.stderr
index 9ee1bb75a..2111c7e0f 100644
--- a/tests/typecheck/should_fail/tcfail062.stderr
+++ b/tests/typecheck/should_fail/tcfail062.stderr
@@ -1,6 +1,6 @@
 
 tcfail062.hs:34:6:
-    Not in scope: type variable `behaviouralExpression'
+    Not in scope: type variable ‛behaviouralExpression’
 
 tcfail062.hs:34:29:
-    Not in scope: type variable `behaviouralExpression'
+    Not in scope: type variable ‛behaviouralExpression’
diff --git a/tests/typecheck/should_fail/tcfail063.stderr b/tests/typecheck/should_fail/tcfail063.stderr
index 35d4f406a..046439672 100644
--- a/tests/typecheck/should_fail/tcfail063.stderr
+++ b/tests/typecheck/should_fail/tcfail063.stderr
@@ -1,5 +1,5 @@
 
 tcfail063.hs:6:9:
-    Expecting one more argument to `Num'
-    Expected a constraint, but `Num' has kind `* -> Constraint'
-    In the type signature for `moby': moby :: Num => Int -> a -> Int
+    Expecting one more argument to ‛Num’
+    Expected a constraint, but ‛Num’ has kind ‛* -> Constraint’
+    In the type signature for ‛moby’: moby :: Num => Int -> a -> Int
diff --git a/tests/typecheck/should_fail/tcfail065.stderr b/tests/typecheck/should_fail/tcfail065.stderr
index c680e8264..8599dfeb2 100644
--- a/tests/typecheck/should_fail/tcfail065.stderr
+++ b/tests/typecheck/should_fail/tcfail065.stderr
@@ -1,14 +1,14 @@
 
 tcfail065.hs:29:20:
-    Couldn't match expected type `x' with actual type `x1'
-      `x1' is a rigid type variable bound by
+    Couldn't match expected type ‛x’ with actual type ‛x1’
+      ‛x1’ is a rigid type variable bound by
            the type signature for setX :: x1 -> X x -> X x
            at tcfail065.hs:29:3
-      `x' is a rigid type variable bound by
+      ‛x’ is a rigid type variable bound by
           the instance declaration at tcfail065.hs:28:10
     Relevant bindings include
       setX :: x1 -> X x -> X x (bound at tcfail065.hs:29:3)
       x :: x1 (bound at tcfail065.hs:29:8)
-    In the first argument of `X', namely `x'
+    In the first argument of ‛X’, namely ‛x’
     In the expression: X x
-    In an equation for `setX': setX x (X _) = X x
+    In an equation for ‛setX’: setX x (X _) = X x
diff --git a/tests/typecheck/should_fail/tcfail067.stderr b/tests/typecheck/should_fail/tcfail067.stderr
index 9e47a0beb..ebe87035d 100644
--- a/tests/typecheck/should_fail/tcfail067.stderr
+++ b/tests/typecheck/should_fail/tcfail067.stderr
@@ -3,24 +3,24 @@ tcfail067.hs:1:14: Warning:
     -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
 tcfail067.hs:12:16:
-    No instance for (Ord a) arising from a use of `SubRange'
+    No instance for (Ord a) arising from a use of ‛SubRange’
     Possible fix:
       add (Ord a) to the context of
         the type signature for subRangeValue :: SubRange a -> a
     In the pattern: SubRange (lower, upper) value
-    In an equation for `subRangeValue':
+    In an equation for ‛subRangeValue’:
         subRangeValue (SubRange (lower, upper) value) = value
 
 tcfail067.hs:15:11:
-    No instance for (Ord a) arising from a use of `SubRange'
+    No instance for (Ord a) arising from a use of ‛SubRange’
     Possible fix:
       add (Ord a) to the context of
         the type signature for subRange :: SubRange a -> (a, a)
     In the pattern: SubRange r value
-    In an equation for `subRange': subRange (SubRange r value) = r
+    In an equation for ‛subRange’: subRange (SubRange r value) = r
 
 tcfail067.hs:46:12:
-    Could not deduce (Ord a) arising from a use of `SubRange'
+    Could not deduce (Ord a) arising from a use of ‛SubRange’
     from the context (Show a)
       bound by the type signature for
                  showRange :: Show a => SubRange a -> String
@@ -29,35 +29,35 @@ tcfail067.hs:46:12:
       add (Ord a) to the context of
         the type signature for showRange :: Show a => SubRange a -> String
     In the pattern: SubRange (lower, upper) value
-    In an equation for `showRange':
+    In an equation for ‛showRange’:
         showRange (SubRange (lower, upper) value)
           = show value ++ " :" ++ show lower ++ ".." ++ show upper
 
 tcfail067.hs:61:12:
-    Could not deduce (Show a) arising from a use of `numSubRangeNegate'
+    Could not deduce (Show a) arising from a use of ‛numSubRangeNegate’
     from the context (Num a)
       bound by the instance declaration at tcfail067.hs:60:10-34
     Possible fix:
       add (Show a) to the context of the instance declaration
     In the expression: numSubRangeNegate
-    In an equation for `negate': negate = numSubRangeNegate
-    In the instance declaration for `Num (SubRange a)'
+    In an equation for ‛negate’: negate = numSubRangeNegate
+    In the instance declaration for ‛Num (SubRange a)’
 
 tcfail067.hs:65:19:
-    Could not deduce (Ord a) arising from a use of `SubRange'
+    Could not deduce (Ord a) arising from a use of ‛SubRange’
     from the context (Num a)
       bound by the instance declaration at tcfail067.hs:60:10-34
     Possible fix:
       add (Ord a) to the context of the instance declaration
     In the expression:
       SubRange (fromInteger a, fromInteger a) (fromInteger a)
-    In an equation for `fromInteger':
+    In an equation for ‛fromInteger’:
         fromInteger a
           = SubRange (fromInteger a, fromInteger a) (fromInteger a)
-    In the instance declaration for `Num (SubRange a)'
+    In the instance declaration for ‛Num (SubRange a)’
 
 tcfail067.hs:74:5:
-    Could not deduce (Ord a) arising from a use of `SubRange'
+    Could not deduce (Ord a) arising from a use of ‛SubRange’
     from the context (Num a)
       bound by the type signature for
                  numSubRangeBinOp :: Num a =>
@@ -69,7 +69,7 @@ tcfail067.hs:74:5:
           numSubRangeBinOp :: Num a =>
                               (a -> a -> a) -> SubRange a -> SubRange a -> SubRange a
     In the expression: SubRange (result, result) result
-    In an equation for `numSubRangeBinOp':
+    In an equation for ‛numSubRangeBinOp’:
         numSubRangeBinOp op a b
           = SubRange (result, result) result
           where
diff --git a/tests/typecheck/should_fail/tcfail068.stderr b/tests/typecheck/should_fail/tcfail068.stderr
index 687c8eaca..4e889720e 100644
--- a/tests/typecheck/should_fail/tcfail068.stderr
+++ b/tests/typecheck/should_fail/tcfail068.stderr
@@ -5,10 +5,10 @@ tcfail068.hs:14:9:
       bound by the type signature for
                  itgen :: Constructed a => (Int, Int) -> a -> IndTree s a
       at tcfail068.hs:11:10-55
-      `s1' is a rigid type variable bound by
+      ‛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
+      ‛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
@@ -17,9 +17,9 @@ tcfail068.hs:14:9:
     Relevant bindings include
       itgen :: (Int, Int) -> a -> IndTree s a
         (bound at tcfail068.hs:12:1)
-    In the return type of a call of `newSTArray'
-    In the first argument of `runST', namely
-      `(newSTArray ((1, 1), n) x)'
+    In the return type of a call of ‛newSTArray’
+    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:
@@ -29,12 +29,12 @@ tcfail068.hs:19:21:
                  itiap :: Constructed a =>
                           (Int, Int) -> (a -> a) -> IndTree s a -> IndTree s a
       at tcfail068.hs:16:10-75
-      `s' is a rigid type variable bound by
+      ‛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
+      ‛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
@@ -43,11 +43,11 @@ tcfail068.hs:19:21:
       itiap :: (Int, Int) -> (a -> a) -> IndTree s a -> IndTree s a
         (bound at tcfail068.hs:17:1)
       arr :: IndTree s a (bound at tcfail068.hs:17:11)
-    In the first argument of `readSTArray', namely `arr'
-    In the first argument of `(>>=)', namely `readSTArray arr i'
-    In the first argument of `runST', namely
-      `(readSTArray arr i
-        >>= \ val -> writeSTArray arr i (f val) >> return arr)'
+    In the first argument of ‛readSTArray’, namely ‛arr’
+    In the first argument of ‛(>>=)’, namely ‛readSTArray arr i’
+    In the first argument of ‛runST’, namely
+      ‛(readSTArray arr i
+        >>= \ val -> writeSTArray arr i (f val) >> return arr)’
 
 tcfail068.hs:24:35:
     Could not deduce (s ~ s1)
@@ -56,12 +56,12 @@ tcfail068.hs:24:35:
                  itrap :: Constructed a =>
                           ((Int, Int), (Int, Int)) -> (a -> a) -> IndTree s a -> IndTree s a
       at tcfail068.hs:23:10-87
-      `s' is a rigid type variable bound by
+      ‛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
+      ‛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)
@@ -75,8 +75,8 @@ tcfail068.hs:24:35:
         (bound at tcfail068.hs:29:9)
       itrap' :: Int -> Int -> GHC.ST.ST s (IndTree s a)
         (bound at tcfail068.hs:26:9)
-    In the return type of a call of itrap'
-    In the first argument of `runST', namely `(itrap' i k)'
+    In the return type of a call of ‛itrap'’
+    In the first argument of ‛runST’, namely ‛(itrap' i k)’
     In the expression: runST (itrap' i k)
 
 tcfail068.hs:36:46:
@@ -92,7 +92,7 @@ tcfail068.hs:36:46:
                                -> IndTree s b
                                -> (c, IndTree s b)
       at tcfail068.hs:(34,15)-(35,62)
-      `s' is a rigid type variable bound by
+      ‛s’ is a rigid type variable bound by
           the type signature for
             itrapstate :: Constructed b =>
                           ((Int, Int), (Int, Int))
@@ -103,7 +103,7 @@ tcfail068.hs:36:46:
                           -> IndTree s b
                           -> (c, IndTree s b)
           at tcfail068.hs:34:15
-      `s1' is a rigid type variable bound by
+      ‛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)
@@ -122,6 +122,6 @@ tcfail068.hs:36:46:
         (bound at tcfail068.hs:41:9)
       itrapstate' :: Int -> Int -> c -> GHC.ST.ST s (c, IndTree s b)
         (bound at tcfail068.hs:38:9)
-    In the return type of a call of itrapstate'
-    In the first argument of `runST', namely `(itrapstate' i k s)'
+    In the return type of a call of ‛itrapstate'’
+    In the first argument of ‛runST’, namely ‛(itrapstate' i k s)’
     In the expression: runST (itrapstate' i k s)
diff --git a/tests/typecheck/should_fail/tcfail069.stderr b/tests/typecheck/should_fail/tcfail069.stderr
index 4c40526b5..7c793c49b 100644
--- a/tests/typecheck/should_fail/tcfail069.stderr
+++ b/tests/typecheck/should_fail/tcfail069.stderr
@@ -1,7 +1,7 @@
 
 tcfail069.hs:21:7:
-    Couldn't match expected type `([Int], [Int])'
-                with actual type `[t0]'
+    Couldn't match expected type ‛([Int], [Int])’
+                with actual type ‛[t0]’
     In the pattern: []
     In a case alternative: [] -> error "foo"
     In the expression: case (list1, list2) of { [] -> error "foo" }
diff --git a/tests/typecheck/should_fail/tcfail070.stderr b/tests/typecheck/should_fail/tcfail070.stderr
index 76e9feb51..bc0590aae 100644
--- a/tests/typecheck/should_fail/tcfail070.stderr
+++ b/tests/typecheck/should_fail/tcfail070.stderr
@@ -1,5 +1,5 @@
-
-tcfail070.hs:15:15:
-    `[Int]' is applied to too many type arguments
-    In the type `[Int] Bool'
-    In the type declaration for `State'
+
+tcfail070.hs:15:15:
+    ‛[Int]’ is applied to too many type arguments
+    In the type ‛[Int] Bool’
+    In the type declaration for ‛State’
diff --git a/tests/typecheck/should_fail/tcfail072.stderr b/tests/typecheck/should_fail/tcfail072.stderr
index a71b0effd..b533d3650 100644
--- a/tests/typecheck/should_fail/tcfail072.stderr
+++ b/tests/typecheck/should_fail/tcfail072.stderr
@@ -1,16 +1,16 @@
-
-tcfail072.hs:23:13:
-    Could not deduce (Ord q0) arising from a use of `g'
-    from the context (Ord p, Ord q)
-      bound by the type signature for
-                 g :: (Ord p, Ord q) => AB p q -> Bool
-      at tcfail072.hs:22:6-38
-    The type variable `q0' is ambiguous
-    Note: there are several potential instances:
-      instance Integral a => Ord (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
-      instance Ord () -- Defined in `GHC.Classes'
-      instance (Ord a, Ord b) => Ord (a, b) -- Defined in `GHC.Classes'
-      ...plus 22 others
-    In the expression: g A
-    In an equation for `g': g (B _ _) = g A
+
+tcfail072.hs:23:13:
+    Could not deduce (Ord q0) arising from a use of ‛g’
+    from the context (Ord p, Ord q)
+      bound by the type signature for
+                 g :: (Ord p, Ord q) => AB p q -> Bool
+      at tcfail072.hs:22:6-38
+    The type variable ‛q0’ is ambiguous
+    Note: there are several potential instances:
+      instance Integral a => Ord (GHC.Real.Ratio a)
+        -- Defined in ‛GHC.Real’
+      instance Ord () -- Defined in ‛GHC.Classes’
+      instance (Ord a, Ord b) => Ord (a, b) -- Defined in ‛GHC.Classes’
+      ...plus 22 others
+    In the expression: g A
+    In an equation for ‛g’: g (B _ _) = g A
diff --git a/tests/typecheck/should_fail/tcfail073.stderr b/tests/typecheck/should_fail/tcfail073.stderr
index 3ac8e21e0..16bcdf4c0 100644
--- a/tests/typecheck/should_fail/tcfail073.stderr
+++ b/tests/typecheck/should_fail/tcfail073.stderr
@@ -2,4 +2,4 @@
 tcfail073.hs:8:10:
     Duplicate instance declarations:
       instance Eq a => Eq (a, b) -- Defined at tcfail073.hs:8:10
-      instance (Eq a, Eq b) => Eq (a, b) -- Defined in `GHC.Classes'
+      instance (Eq a, Eq b) => Eq (a, b) -- Defined in ‛GHC.Classes’
diff --git a/tests/typecheck/should_fail/tcfail076.stderr b/tests/typecheck/should_fail/tcfail076.stderr
index 5e8361aa6..c5bd8a5bc 100644
--- a/tests/typecheck/should_fail/tcfail076.stderr
+++ b/tests/typecheck/should_fail/tcfail076.stderr
@@ -1,10 +1,10 @@
 
 tcfail076.hs:18:82:
-    Couldn't match type `res' with `res1'
-      `res' is a rigid type variable bound by
+    Couldn't match type ‛res’ with ‛res1’
+      ‛res’ is a rigid type variable bound by
             a type expected by the context: (a -> m res) -> m res
             at tcfail076.hs:18:28
-      `res1' is a rigid type variable bound by
+      ‛res1’ is a rigid type variable bound by
              a type expected by the context: (b -> m res1) -> m res1
              at tcfail076.hs:18:64
     Expected type: m res1
@@ -12,6 +12,6 @@ tcfail076.hs:18:82:
     Relevant bindings include
       cont :: a -> m res (bound at tcfail076.hs:18:37)
       cont' :: b -> m res1 (bound at tcfail076.hs:18:73)
-    In the return type of a call of `cont'
+    In the return type of a call of ‛cont’
     In the expression: cont a
-    In the first argument of `KContT', namely `(\ cont' -> cont a)'
+    In the first argument of ‛KContT’, namely ‛(\ cont' -> cont a)’
diff --git a/tests/typecheck/should_fail/tcfail077.stderr b/tests/typecheck/should_fail/tcfail077.stderr
index 105604f66..3f25950fa 100644
--- a/tests/typecheck/should_fail/tcfail077.stderr
+++ b/tests/typecheck/should_fail/tcfail077.stderr
@@ -1,2 +1,2 @@
 
-tcfail077.hs:8:3: `op2' is not a (visible) method of class `Foo'
+tcfail077.hs:8:3: ‛op2’ is not a (visible) method of class ‛Foo’
diff --git a/tests/typecheck/should_fail/tcfail078.stderr b/tests/typecheck/should_fail/tcfail078.stderr
index 714e2807b..b3fabd30b 100644
--- a/tests/typecheck/should_fail/tcfail078.stderr
+++ b/tests/typecheck/should_fail/tcfail078.stderr
@@ -1,4 +1,4 @@
 
 tcfail078.hs:5:6:
-    `Integer' is applied to too many type arguments
-    In the type signature for `f': f :: Integer i => i
+    ‛Integer’ is applied to too many type arguments
+    In the type signature for ‛f’: f :: Integer i => i
diff --git a/tests/typecheck/should_fail/tcfail079.stderr b/tests/typecheck/should_fail/tcfail079.stderr
index a7b9b7cb3..4cce1a69b 100644
--- a/tests/typecheck/should_fail/tcfail079.stderr
+++ b/tests/typecheck/should_fail/tcfail079.stderr
@@ -1,6 +1,6 @@
 
 tcfail079.hs:9:27:
-    Expecting a lifted type, but `Int#' is unlifted
-    In the type `Int#'
-    In the definition of data constructor `Unboxed'
-    In the newtype declaration for `Unboxed'
+    Expecting a lifted type, but ‛Int#’ is unlifted
+    In the type ‛Int#’
+    In the definition of data constructor ‛Unboxed’
+    In the newtype declaration for ‛Unboxed’
diff --git a/tests/typecheck/should_fail/tcfail080.stderr b/tests/typecheck/should_fail/tcfail080.stderr
index 31ad54621..23afa16ba 100644
--- a/tests/typecheck/should_fail/tcfail080.stderr
+++ b/tests/typecheck/should_fail/tcfail080.stderr
@@ -1,13 +1,13 @@
-
-tcfail080.hs:27:1:
-    Could not deduce (Collection c0 a)
-      arising from the ambiguity check for `q'
-    from the context (Collection c a)
-      bound by the inferred type for `q': Collection c a => a -> Bool
-      at tcfail080.hs:27:1-27
-    The type variable `c0' is ambiguous
-    When checking that `q'
-      has the inferred type `forall (c :: * -> *) a.
-                             Collection c a =>
-                             a -> Bool'
-    Probable cause: the inferred type is ambiguous
+
+tcfail080.hs:27:1:
+    Could not deduce (Collection c0 a)
+      arising from the ambiguity check for ‛q’
+    from the context (Collection c a)
+      bound by the inferred type for ‛q’: Collection c a => a -> Bool
+      at tcfail080.hs:27:1-27
+    The type variable ‛c0’ is ambiguous
+    When checking that ‛q’
+      has the inferred type ‛forall (c :: * -> *) a.
+                             Collection c a =>
+                             a -> Bool’
+    Probable cause: the inferred type is ambiguous
diff --git a/tests/typecheck/should_fail/tcfail082.stderr b/tests/typecheck/should_fail/tcfail082.stderr
index 4fd34e602..b34c6d1ec 100644
--- a/tests/typecheck/should_fail/tcfail082.stderr
+++ b/tests/typecheck/should_fail/tcfail082.stderr
@@ -1,4 +1,4 @@
 
 tcfail082.hs:2:1:
-    Failed to load interface for `Data82'
+    Failed to load interface for ‛Data82’
     Use -v to see a list of the files searched for.
diff --git a/tests/typecheck/should_fail/tcfail083.stderr b/tests/typecheck/should_fail/tcfail083.stderr
index 07717e090..dc4ce59e9 100644
--- a/tests/typecheck/should_fail/tcfail083.stderr
+++ b/tests/typecheck/should_fail/tcfail083.stderr
@@ -1,20 +1,20 @@
-
-tcfail083.hs:8:39:
-    Constructor `Bar' does not have field `baz'
-    In the pattern: Bar {flag = f, baz = b}
-    In the pattern: State {bar = Bar {flag = f, baz = b}}
-    In an equation for `display':
-        display (State {bar = Bar {flag = f, baz = b}}) = print (f, b)
-
-tcfail083.hs:8:53:
-    No instance for (Show t0) arising from a use of `print'
-    The type variable `t0' is ambiguous
-    Relevant bindings include b :: t0 (bound at tcfail083.hs:8:45)
-    Note: there are several potential instances:
-      instance Show Bar -- Defined at tcfail083.hs:3:43
-      instance Show Double -- Defined in `GHC.Float'
-      instance Show Float -- Defined in `GHC.Float'
-      ...plus 24 others
-    In the expression: print (f, b)
-    In an equation for `display':
-        display (State {bar = Bar {flag = f, baz = b}}) = print (f, b)
+
+tcfail083.hs:8:39:
+    Constructor ‛Bar’ does not have field ‛baz’
+    In the pattern: Bar {flag = f, baz = b}
+    In the pattern: State {bar = Bar {flag = f, baz = b}}
+    In an equation for ‛display’:
+        display (State {bar = Bar {flag = f, baz = b}}) = print (f, b)
+
+tcfail083.hs:8:53:
+    No instance for (Show t0) arising from a use of ‛print’
+    The type variable ‛t0’ is ambiguous
+    Relevant bindings include b :: t0 (bound at tcfail083.hs:8:45)
+    Note: there are several potential instances:
+      instance Show Bar -- Defined at tcfail083.hs:3:43
+      instance Show Double -- Defined in ‛GHC.Float’
+      instance Show Float -- Defined in ‛GHC.Float’
+      ...plus 24 others
+    In the expression: print (f, b)
+    In an equation for ‛display’:
+        display (State {bar = Bar {flag = f, baz = b}}) = print (f, b)
diff --git a/tests/typecheck/should_fail/tcfail084.stderr b/tests/typecheck/should_fail/tcfail084.stderr
index 1a7e8c3e2..cfa0ff483 100644
--- a/tests/typecheck/should_fail/tcfail084.stderr
+++ b/tests/typecheck/should_fail/tcfail084.stderr
@@ -1,5 +1,5 @@
 
 tcfail084.hs:10:5:
-    Constructor `F' does not have field `y'
+    Constructor ‛F’ does not have field ‛y’
     In the expression: F {y = 2}
-    In an equation for `z': z = F {y = 2}
+    In an equation for ‛z’: z = F {y = 2}
diff --git a/tests/typecheck/should_fail/tcfail085.stderr b/tests/typecheck/should_fail/tcfail085.stderr
index c500e7a18..feb7c6daf 100644
--- a/tests/typecheck/should_fail/tcfail085.stderr
+++ b/tests/typecheck/should_fail/tcfail085.stderr
@@ -1,5 +1,5 @@
 
 tcfail085.hs:9:5:
-    Constructor `F' does not have the required strict field(s): y
+    Constructor ‛F’ does not have the required strict field(s): y
     In the expression: F {x = 2}
-    In an equation for `z': z = F {x = 2}
+    In an equation for ‛z’: z = F {x = 2}
diff --git a/tests/typecheck/should_fail/tcfail086.stderr b/tests/typecheck/should_fail/tcfail086.stderr
index 1aa420928..ebf4d4e8e 100644
--- a/tests/typecheck/should_fail/tcfail086.stderr
+++ b/tests/typecheck/should_fail/tcfail086.stderr
@@ -1,6 +1,6 @@
-
-tcfail086.hs:6:38:
-    Can't make a derived instance of `Eq Ex':
-      Constructor `Ex' must have a Haskell-98 type
-      Possible fix: use a standalone deriving declaration instead
-    In the data declaration for `Ex'
+
+tcfail086.hs:6:38:
+    Can't make a derived instance of ‛Eq Ex’:
+      Constructor ‛Ex’ must have a Haskell-98 type
+      Possible fix: use a standalone deriving declaration instead
+    In the data declaration for ‛Ex’
diff --git a/tests/typecheck/should_fail/tcfail088.stderr b/tests/typecheck/should_fail/tcfail088.stderr
index 1bf22ffaa..1c303d9a6 100644
--- a/tests/typecheck/should_fail/tcfail088.stderr
+++ b/tests/typecheck/should_fail/tcfail088.stderr
@@ -1,4 +1,4 @@
 
 tcfail088.hs:9:19:
     Illegal polymorphic or qualified type: forall s. T s a
-    In the instance declaration for `Ord (forall s. T s a)'
+    In the instance declaration for ‛Ord (forall s. T s a)’
diff --git a/tests/typecheck/should_fail/tcfail090.stderr b/tests/typecheck/should_fail/tcfail090.stderr
index 3096b226c..622e18140 100644
--- a/tests/typecheck/should_fail/tcfail090.stderr
+++ b/tests/typecheck/should_fail/tcfail090.stderr
@@ -1,8 +1,8 @@
 
 tcfail090.hs:8:9:
-    Couldn't match kind `*' with `#'
+    Couldn't match kind ‛*’ with ‛#’
     When matching types
       a0 :: *
       ByteArray# :: #
     In the expression: undefined
-    In an equation for `die': die _ = undefined
+    In an equation for ‛die’: die _ = undefined
diff --git a/tests/typecheck/should_fail/tcfail092.stderr b/tests/typecheck/should_fail/tcfail092.stderr
index 2ba048bb2..d1079d879 100644
--- a/tests/typecheck/should_fail/tcfail092.stderr
+++ b/tests/typecheck/should_fail/tcfail092.stderr
@@ -1,3 +1,3 @@
 
 tcfail092.hs:7:27:
-    Duplicate binding in parallel list comprehension for: `a'
+    Duplicate binding in parallel list comprehension for: ‛a’
diff --git a/tests/typecheck/should_fail/tcfail097.stderr b/tests/typecheck/should_fail/tcfail097.stderr
index e7dadd4a6..7b2b3aed8 100644
--- a/tests/typecheck/should_fail/tcfail097.stderr
+++ b/tests/typecheck/should_fail/tcfail097.stderr
@@ -1,9 +1,9 @@
-
-tcfail097.hs:5:6:
-    Could not deduce (Eq a0) arising from the ambiguity check for `f'
-    from the context (Eq a)
-      bound by the type signature for f :: Eq a => Int -> Int
-      at tcfail097.hs:5:6-23
-    The type variable `a0' is ambiguous
-    In the ambiguity check for: forall a. Eq a => Int -> Int
-    In the type signature for `f': f :: Eq a => Int -> Int
+
+tcfail097.hs:5:6:
+    Could not deduce (Eq a0) arising from the ambiguity check for ‛f’
+    from the context (Eq a)
+      bound by the type signature for f :: Eq a => Int -> Int
+      at tcfail097.hs:5:6-23
+    The type variable ‛a0’ is ambiguous
+    In the ambiguity check for: forall a. Eq a => Int -> Int
+    In the type signature for ‛f’: f :: Eq a => Int -> Int
diff --git a/tests/typecheck/should_fail/tcfail098.stderr b/tests/typecheck/should_fail/tcfail098.stderr
index 8853e6932..cfb7aaf9b 100644
--- a/tests/typecheck/should_fail/tcfail098.stderr
+++ b/tests/typecheck/should_fail/tcfail098.stderr
@@ -1,10 +1,10 @@
-
-tcfail098.hs:12:10:
-    Could not deduce (Bar a0)
-      arising from the ambiguity check for an instance declaration
-    from the context (Bar a)
-      bound by an instance declaration: Bar a => Bar Bool
-      at tcfail098.hs:12:10-26
-    The type variable `a0' is ambiguous
-    In the ambiguity check for: forall a. Bar a => Bar Bool
-    In the instance declaration for `Bar Bool'
+
+tcfail098.hs:12:10:
+    Could not deduce (Bar a0)
+      arising from the ambiguity check for an instance declaration
+    from the context (Bar a)
+      bound by an instance declaration: Bar a => Bar Bool
+      at tcfail098.hs:12:10-26
+    The type variable ‛a0’ is ambiguous
+    In the ambiguity check for: forall a. Bar a => Bar Bool
+    In the instance declaration for ‛Bar Bool’
diff --git a/tests/typecheck/should_fail/tcfail099.stderr b/tests/typecheck/should_fail/tcfail099.stderr
index 45531250b..f4b77b770 100644
--- a/tests/typecheck/should_fail/tcfail099.stderr
+++ b/tests/typecheck/should_fail/tcfail099.stderr
@@ -1,16 +1,16 @@
 
 tcfail099.hs:9:20:
-    Couldn't match expected type `a' with actual type `t'
-      because type variable `a' would escape its scope
+    Couldn't match expected type ‛a’ with actual type ‛t’
+      because type variable ‛a’ would escape its scope
     This (rigid, skolem) type variable is bound by
       a pattern with constructor
         C :: forall a. (a -> Int) -> DS,
-      in an equation for `call'
+      in an equation for ‛call’
       at tcfail099.hs:9:7-9
     Relevant bindings include
       call :: DS -> t -> Int (bound at tcfail099.hs:9:1)
       f :: a -> Int (bound at tcfail099.hs:9:9)
       arg :: t (bound at tcfail099.hs:9:12)
-    In the first argument of `f', namely `arg'
+    In the first argument of ‛f’, namely ‛arg’
     In the expression: f arg
-    In an equation for `call': call (C f) arg = f arg
+    In an equation for ‛call’: call (C f) arg = f arg
diff --git a/tests/typecheck/should_fail/tcfail100.stderr b/tests/typecheck/should_fail/tcfail100.stderr
index 885c8220b..1e7807670 100644
--- a/tests/typecheck/should_fail/tcfail100.stderr
+++ b/tests/typecheck/should_fail/tcfail100.stderr
@@ -1,4 +1,4 @@
-
-tcfail100.hs:7:1:
-    Type synonym `A' should have 1 argument, but has been given none
-    In the type declaration for `B'
+
+tcfail100.hs:7:1:
+    Type synonym ‛A’ should have 1 argument, but has been given none
+    In the type declaration for ‛B’
diff --git a/tests/typecheck/should_fail/tcfail101.stderr b/tests/typecheck/should_fail/tcfail101.stderr
index 5cca6de0a..f9b3f2f71 100644
--- a/tests/typecheck/should_fail/tcfail101.stderr
+++ b/tests/typecheck/should_fail/tcfail101.stderr
@@ -1,4 +1,4 @@
 
 tcfail101.hs:9:6:
-    Type synonym `A' should have 1 argument, but has been given none
-    In the type signature for `f': f :: T A
+    Type synonym ‛A’ should have 1 argument, but has been given none
+    In the type signature for ‛f’: f :: T A
diff --git a/tests/typecheck/should_fail/tcfail102.stderr b/tests/typecheck/should_fail/tcfail102.stderr
index 516734b05..1009fb4cc 100644
--- a/tests/typecheck/should_fail/tcfail102.stderr
+++ b/tests/typecheck/should_fail/tcfail102.stderr
@@ -3,11 +3,11 @@ tcfail102.hs:1:14: Warning:
     -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
 tcfail102.hs:9:15:
-    Could not deduce (Integral (Ratio a)) arising from a use of `p'
+    Could not deduce (Integral (Ratio a)) arising from a use of ‛p’
     from the context (Integral a)
       bound by the type signature for
                  f :: Integral a => P (Ratio a) -> P (Ratio a)
       at tcfail102.hs:8:6-45
-    In the `p' field of a record
+    In the ‛p’ field of a record
     In the expression: x {p = p x}
-    In an equation for `f': f x = x {p = p x}
+    In an equation for ‛f’: f x = x {p = p x}
diff --git a/tests/typecheck/should_fail/tcfail103.stderr b/tests/typecheck/should_fail/tcfail103.stderr
index ea873e637..ba581be12 100644
--- a/tests/typecheck/should_fail/tcfail103.stderr
+++ b/tests/typecheck/should_fail/tcfail103.stderr
@@ -1,9 +1,9 @@
 
 tcfail103.hs:15:23:
-    Couldn't match type `t' with `s'
-      `t' is a rigid type variable bound by
+    Couldn't match type ‛t’ with ‛s’
+      ‛t’ is a rigid type variable bound by
           the type signature for f :: ST t Int at tcfail103.hs:10:5
-      `s' is a rigid type variable bound by
+      ‛s’ is a rigid type variable bound by
           the type signature for g :: ST s Int at tcfail103.hs:13:14
     Expected type: STRef s Int
       Actual type: STRef t Int
@@ -11,6 +11,6 @@ tcfail103.hs:15:23:
       f :: ST t Int (bound at tcfail103.hs:11:1)
       v :: STRef t Int (bound at tcfail103.hs:12:5)
       g :: ST s Int (bound at tcfail103.hs:15:9)
-    In the first argument of `readSTRef', namely `v'
+    In the first argument of ‛readSTRef’, namely ‛v’
     In the expression: readSTRef v
-    In an equation for `g': g = readSTRef v
+    In an equation for ‛g’: g = readSTRef v
diff --git a/tests/typecheck/should_fail/tcfail104.stderr b/tests/typecheck/should_fail/tcfail104.stderr
index 5e6fc3bb1..a32e413f6 100644
--- a/tests/typecheck/should_fail/tcfail104.stderr
+++ b/tests/typecheck/should_fail/tcfail104.stderr
@@ -1,15 +1,15 @@
 
 tcfail104.hs:16:19:
-    Couldn't match expected type `Char -> Char'
-                with actual type `forall a. a -> a'
+    Couldn't match expected type ‛Char -> Char’
+                with actual type ‛forall a. a -> a’
     In the expression: x
     In the expression: (\ x -> x)
     In the expression:
       if v then (\ (x :: forall a. a -> a) -> x) else (\ x -> x)
 
 tcfail104.hs:22:39:
-    Couldn't match expected type `forall a. a -> a'
-                with actual type `a0 -> a0'
+    Couldn't match expected type ‛forall a. a -> a’
+                with actual type ‛a0 -> a0’
     In the expression: x
     In the expression: (\ (x :: forall a. a -> a) -> x)
     In the expression:
diff --git a/tests/typecheck/should_fail/tcfail106.stderr b/tests/typecheck/should_fail/tcfail106.stderr
index b08c7dfe8..2eeaf7197 100644
--- a/tests/typecheck/should_fail/tcfail106.stderr
+++ b/tests/typecheck/should_fail/tcfail106.stderr
@@ -2,4 +2,4 @@
 tcfail106.hs:14:10:
     No instance for (S Int)
       arising from the superclasses of an instance declaration
-    In the instance declaration for `D Int'
+    In the instance declaration for ‛D Int’
diff --git a/tests/typecheck/should_fail/tcfail107.stderr b/tests/typecheck/should_fail/tcfail107.stderr
index 92a89b754..b65881477 100644
--- a/tests/typecheck/should_fail/tcfail107.stderr
+++ b/tests/typecheck/should_fail/tcfail107.stderr
@@ -1,5 +1,5 @@
 
 tcfail107.hs:13:9:
-    Type synonym `Const' should have 2 arguments, but has been given 1
-    In the type signature for `test':
+    Type synonym ‛Const’ should have 2 arguments, but has been given 1
+    In the type signature for ‛test’:
       test :: Thing (Const Int) -> Thing (Const Int)
diff --git a/tests/typecheck/should_fail/tcfail108.stderr b/tests/typecheck/should_fail/tcfail108.stderr
index 56c97c20d..f3c241563 100644
--- a/tests/typecheck/should_fail/tcfail108.stderr
+++ b/tests/typecheck/should_fail/tcfail108.stderr
@@ -4,4 +4,4 @@ tcfail108.hs:7:10:
     (Use -XFlexibleContexts to permit this)
     In the context: (Eq (f (Rec f)))
     While checking an instance declaration
-    In the instance declaration for `Eq (Rec f)'
+    In the instance declaration for ‛Eq (Rec f)’
diff --git a/tests/typecheck/should_fail/tcfail109.stderr b/tests/typecheck/should_fail/tcfail109.stderr
index 545581540..4b5960718 100644
--- a/tests/typecheck/should_fail/tcfail109.stderr
+++ b/tests/typecheck/should_fail/tcfail109.stderr
@@ -2,4 +2,4 @@
 tcfail109.hs:16:10:
     No instance for (Eq Stupid)
       arising from the superclasses of an instance declaration
-    In the instance declaration for `Collects Bool Stupid'
+    In the instance declaration for ‛Collects Bool Stupid’
diff --git a/tests/typecheck/should_fail/tcfail110.stderr b/tests/typecheck/should_fail/tcfail110.stderr
index 91ba52195..840dc29de 100644
--- a/tests/typecheck/should_fail/tcfail110.stderr
+++ b/tests/typecheck/should_fail/tcfail110.stderr
@@ -1,6 +1,6 @@
 
 tcfail110.hs:8:30:
-    Expecting one more argument to `Foo a'
-    Expected a type, but `Foo a' has kind `* -> *'
-    In the type signature for `bar':
+    Expecting one more argument to ‛Foo a’
+    Expected a type, but ‛Foo a’ has kind ‛* -> *’
+    In the type signature for ‛bar’:
       bar :: String -> (forall a. Foo a) -> IO ()
diff --git a/tests/typecheck/should_fail/tcfail112.stderr b/tests/typecheck/should_fail/tcfail112.stderr
index 602c1e4b6..70cd77bca 100644
--- a/tests/typecheck/should_fail/tcfail112.stderr
+++ b/tests/typecheck/should_fail/tcfail112.stderr
@@ -1,15 +1,15 @@
 
 tcfail112.hs:11:6:
-    Constructor `S' does not have the required strict field(s): y
+    Constructor ‛S’ does not have the required strict field(s): y
     In the expression: S {}
-    In an equation for `s1': s1 = S {}
+    In an equation for ‛s1’: s1 = S {}
 
 tcfail112.hs:12:6:
-    Constructor `S' does not have the required strict field(s): y
+    Constructor ‛S’ does not have the required strict field(s): y
     In the expression: S {x = 3}
-    In an equation for `s2': s2 = S {x = 3}
+    In an equation for ‛s2’: s2 = S {x = 3}
 
 tcfail112.hs:14:6:
-    Constructor `T' does not have the required strict field(s)
+    Constructor ‛T’ does not have the required strict field(s)
     In the expression: T {}
-    In an equation for `t': t = T {}
+    In an equation for ‛t’: t = T {}
diff --git a/tests/typecheck/should_fail/tcfail113.stderr b/tests/typecheck/should_fail/tcfail113.stderr
index 2584b46bd..f9314f5dc 100644
--- a/tests/typecheck/should_fail/tcfail113.stderr
+++ b/tests/typecheck/should_fail/tcfail113.stderr
@@ -1,14 +1,14 @@
 
 tcfail113.hs:12:7:
-    Expecting one more argument to `Maybe'
-    Expected kind `*', but `Maybe' has kind `* -> *'
-    In the type signature for `f': f :: [Maybe]
+    Expecting one more argument to ‛Maybe’
+    Expected kind ‛*’, but ‛Maybe’ has kind ‛* -> *’
+    In the type signature for ‛f’: f :: [Maybe]
 
 tcfail113.hs:15:8:
-    The first argument of `T' should have kind `* -> *',
-      but `Int' has kind `*'
-    In the type signature for `g': g :: T Int
+    The first argument of ‛T’ should have kind ‛* -> *’,
+      but ‛Int’ has kind ‛*’
+    In the type signature for ‛g’: g :: T Int
 
 tcfail113.hs:18:6:
-    `Int' is applied to too many type arguments
-    In the type signature for `h': h :: Int Int
+    ‛Int’ is applied to too many type arguments
+    In the type signature for ‛h’: h :: Int Int
diff --git a/tests/typecheck/should_fail/tcfail114.stderr b/tests/typecheck/should_fail/tcfail114.stderr
index 601feff85..41c8a65ce 100644
--- a/tests/typecheck/should_fail/tcfail114.stderr
+++ b/tests/typecheck/should_fail/tcfail114.stderr
@@ -1,5 +1,5 @@
 
 tcfail114.hs:11:20:
-    `foo' is not a record selector
+    ‛foo’ is not a record selector
     In the expression: undefined {foo = ()}
-    In an equation for `test': test = undefined {foo = ()}
+    In an equation for ‛test’: test = undefined {foo = ()}
diff --git a/tests/typecheck/should_fail/tcfail116.stderr b/tests/typecheck/should_fail/tcfail116.stderr
index 8e7372413..d49438dd9 100644
--- a/tests/typecheck/should_fail/tcfail116.stderr
+++ b/tests/typecheck/should_fail/tcfail116.stderr
@@ -1,6 +1,6 @@
 
 tcfail116.hs:5:1:
-    The class method `bug'
+    The class method ‛bug’
     mentions none of the type variables of the class Foo a
     When checking the class method: bug :: ()
-    In the class declaration for `Foo'
+    In the class declaration for ‛Foo’
diff --git a/tests/typecheck/should_fail/tcfail117.stderr b/tests/typecheck/should_fail/tcfail117.stderr
index c7be9199c..40a14e7f2 100644
--- a/tests/typecheck/should_fail/tcfail117.stderr
+++ b/tests/typecheck/should_fail/tcfail117.stderr
@@ -1,13 +1,13 @@
-
-tcfail117.hs:5:32:
-    Can't make a derived instance of `Enum N1':
-      `N1' must be an enumeration type
-      (an enumeration consists of one or more nullary, non-GADT constructors)
-      Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension
-    In the newtype declaration for `N1'
-
-tcfail117.hs:6:32:
-    Can't make a derived instance of `Enum N2':
-      `N2' must be an enumeration type
-      (an enumeration consists of one or more nullary, non-GADT constructors)
-    In the data declaration for `N2'
+
+tcfail117.hs:5:32:
+    Can't make a derived instance of ‛Enum N1’:
+      ‛N1’ must be an enumeration type
+      (an enumeration consists of one or more nullary, non-GADT constructors)
+      Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension
+    In the newtype declaration for ‛N1’
+
+tcfail117.hs:6:32:
+    Can't make a derived instance of ‛Enum N2’:
+      ‛N2’ must be an enumeration type
+      (an enumeration consists of one or more nullary, non-GADT constructors)
+    In the data declaration for ‛N2’
diff --git a/tests/typecheck/should_fail/tcfail119.stderr b/tests/typecheck/should_fail/tcfail119.stderr
index 1984617b2..45a1bc770 100644
--- a/tests/typecheck/should_fail/tcfail119.stderr
+++ b/tests/typecheck/should_fail/tcfail119.stderr
@@ -1,5 +1,5 @@
 
 tcfail119.hs:11:8:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the pattern: "Foo"
-    In an equation for `b': b x "Foo" = ()
+    In an equation for ‛b’: b x "Foo" = ()
diff --git a/tests/typecheck/should_fail/tcfail121.stderr b/tests/typecheck/should_fail/tcfail121.stderr
index 700dbb861..7ac388aa1 100644
--- a/tests/typecheck/should_fail/tcfail121.stderr
+++ b/tests/typecheck/should_fail/tcfail121.stderr
@@ -1,13 +1,12 @@
 
 tcfail121.hs:13:9:
-    Overlapping instances for Foo [a]
-      arising from a use of `op'
+    Overlapping instances for Foo [a] arising from a use of ‛op’
     Matching instances:
       instance [overlap ok] Foo a => Foo [a]
         -- Defined at tcfail121.hs:9:10
       instance [overlap ok] Foo [Int] -- Defined at tcfail121.hs:10:10
-    (The choice depends on the instantiation of `a'
+    (The choice depends on the instantiation of ‛a’
      To pick the first instance above, use -XIncoherentInstances
      when compiling the other instance declarations)
     In the expression: op x
-    In an equation for `foo': foo x = op x
+    In an equation for ‛foo’: foo x = op x
diff --git a/tests/typecheck/should_fail/tcfail122.stderr b/tests/typecheck/should_fail/tcfail122.stderr
index d08332116..ec0f6a33b 100644
--- a/tests/typecheck/should_fail/tcfail122.stderr
+++ b/tests/typecheck/should_fail/tcfail122.stderr
@@ -1,6 +1,6 @@
 
 tcfail122.hs:8:9:
-    Couldn't match kind `* -> *' with `*'
+    Couldn't match kind ‛* -> *’ with ‛*’
     When matching types
       d0 :: * -> *
       b :: *
@@ -11,7 +11,7 @@ tcfail122.hs:8:9:
     In the expression:
       [undefined :: forall a b. a b,
        undefined :: forall (c :: (* -> *) -> *) (d :: * -> *). c d]
-    In an equation for `foo':
+    In an equation for ‛foo’:
         foo
           = [undefined :: forall a b. a b,
              undefined :: forall (c :: (* -> *) -> *) (d :: * -> *). c d]
diff --git a/tests/typecheck/should_fail/tcfail123.stderr b/tests/typecheck/should_fail/tcfail123.stderr
index 1ca291fd9..2a70414aa 100644
--- a/tests/typecheck/should_fail/tcfail123.stderr
+++ b/tests/typecheck/should_fail/tcfail123.stderr
@@ -1,9 +1,9 @@
 
 tcfail123.hs:11:9:
-    Couldn't match kind `*' with `#'
+    Couldn't match kind ‛*’ with ‛#’
     When matching types
       t0 :: *
       GHC.Prim.Int# :: #
-    In the first argument of `f', namely `3#'
+    In the first argument of ‛f’, namely ‛3#’
     In the expression: f 3#
-    In an equation for `h': h v = f 3#
+    In an equation for ‛h’: h v = f 3#
diff --git a/tests/typecheck/should_fail/tcfail125.stderr b/tests/typecheck/should_fail/tcfail125.stderr
index addd093bf..592698f7d 100644
--- a/tests/typecheck/should_fail/tcfail125.stderr
+++ b/tests/typecheck/should_fail/tcfail125.stderr
@@ -3,9 +3,9 @@ tcfail125.hs:1:14: Warning:
     -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
 tcfail125.hs:11:4:
-    No instance for (Show a) arising from a use of `LiftObs'
+    No instance for (Show a) arising from a use of ‛LiftObs’
     Possible fix:
       add (Show a) to the context of
         the type signature for f :: Obs a -> String
     In the pattern: LiftObs _ _
-    In an equation for `f': f (LiftObs _ _) = "yes"
+    In an equation for ‛f’: f (LiftObs _ _) = "yes"
diff --git a/tests/typecheck/should_fail/tcfail127.stderr b/tests/typecheck/should_fail/tcfail127.stderr
index 021120314..c7d41534a 100644
--- a/tests/typecheck/should_fail/tcfail127.stderr
+++ b/tests/typecheck/should_fail/tcfail127.stderr
@@ -2,4 +2,4 @@
 tcfail127.hs:3:8:
     Illegal polymorphic or qualified type: Num a => a -> a
     Perhaps you intended to use -XImpredicativeTypes
-    In the type signature for `foo': foo :: IO (Num a => a -> a)
+    In the type signature for ‛foo’: foo :: IO (Num a => a -> a)
diff --git a/tests/typecheck/should_fail/tcfail128.stderr b/tests/typecheck/should_fail/tcfail128.stderr
index 9a1564fb8..38ae102d9 100644
--- a/tests/typecheck/should_fail/tcfail128.stderr
+++ b/tests/typecheck/should_fail/tcfail128.stderr
@@ -1,21 +1,21 @@
-
-tcfail128.hs:18:16:
-    No instance for (Data.Array.Base.MArray b0 FlatVector IO)
-      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
-        -- Defined in `Data.Array.Base'
-    In a stmt of a 'do' block: v <- thaw tmp
-    In the expression:
-      do { let sL = ...
-               dim = length sL
-               ....;
-           v <- thaw tmp;
-           return () }
-    In an equation for `main':
-        main
-          = do { let sL = ...
-                     ....;
-                 v <- thaw tmp;
-                 return () }
+
+tcfail128.hs:18:16:
+    No instance for (Data.Array.Base.MArray b0 FlatVector IO)
+      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
+        -- Defined in ‛Data.Array.Base’
+    In a stmt of a 'do' block: v <- thaw tmp
+    In the expression:
+      do { let sL = ...
+               dim = length sL
+               ....;
+           v <- thaw tmp;
+           return () }
+    In an equation for ‛main’:
+        main
+          = do { let sL = ...
+                     ....;
+                 v <- thaw tmp;
+                 return () }
diff --git a/tests/typecheck/should_fail/tcfail129.stderr b/tests/typecheck/should_fail/tcfail129.stderr
index f6ee765ce..0bffcbf76 100644
--- a/tests/typecheck/should_fail/tcfail129.stderr
+++ b/tests/typecheck/should_fail/tcfail129.stderr
@@ -1,12 +1,12 @@
 
 tcfail129.hs:12:21:
-    Type synonym `Foo' should have 1 argument, but has been given none
+    Type synonym ‛Foo’ should have 1 argument, but has been given none
     In an expression type signature: Bar Foo
     In the expression: undefined :: Bar Foo
-    In an equation for `blah': blah = undefined :: Bar Foo
+    In an equation for ‛blah’: blah = undefined :: Bar Foo
 
 tcfail129.hs:17:22:
-    Type synonym `Foo1' should have 1 argument, but has been given none
+    Type synonym ‛Foo1’ should have 1 argument, but has been given none
     In an expression type signature: Bar1 Foo1
     In the expression: undefined :: Bar1 Foo1
-    In an equation for `blah1': blah1 = undefined :: Bar1 Foo1
+    In an equation for ‛blah1’: blah1 = undefined :: Bar1 Foo1
diff --git a/tests/typecheck/should_fail/tcfail130.stderr b/tests/typecheck/should_fail/tcfail130.stderr
index 3534dba67..37f3614b5 100644
--- a/tests/typecheck/should_fail/tcfail130.stderr
+++ b/tests/typecheck/should_fail/tcfail130.stderr
@@ -1,6 +1,5 @@
 
 tcfail130.hs:10:7:
-    Unbound implicit parameter (?x::Int)
-      arising from a use of `woggle'
+    Unbound implicit parameter (?x::Int) arising from a use of ‛woggle’
     In the expression: woggle 3
-    In an equation for `foo': foo = woggle 3
+    In an equation for ‛foo’: foo = woggle 3
diff --git a/tests/typecheck/should_fail/tcfail131.stderr b/tests/typecheck/should_fail/tcfail131.stderr
index db2a954d5..7cdcb6f2f 100644
--- a/tests/typecheck/should_fail/tcfail131.stderr
+++ b/tests/typecheck/should_fail/tcfail131.stderr
@@ -4,11 +4,11 @@ tcfail131.hs:7:9:
     from the context (Num b)
       bound by the type signature for g :: Num b => b -> b
       at tcfail131.hs:6:8-22
-      `b' is a rigid type variable bound by
+      ‛b’ is a rigid type variable bound by
           the type signature for g :: Num b => b -> b at tcfail131.hs:6:8
     Relevant bindings include
       g :: b -> b (bound at tcfail131.hs:7:3)
       x :: b (bound at tcfail131.hs:7:5)
-    In the return type of a call of `f'
+    In the return type of a call of ‛f’
     In the expression: f x x
-    In an equation for `g': g x = f x x
+    In an equation for ‛g’: g x = f x x
diff --git a/tests/typecheck/should_fail/tcfail132.stderr b/tests/typecheck/should_fail/tcfail132.stderr
index 91228b86b..8440cc89a 100644
--- a/tests/typecheck/should_fail/tcfail132.stderr
+++ b/tests/typecheck/should_fail/tcfail132.stderr
@@ -1,6 +1,6 @@
 
 tcfail132.hs:17:37:
-    The first argument of `T' should have kind `* -> * -> * -> *',
-      but `Object f' f t' has kind `* -> * -> *'
-    In the type `T (Object f' f t) (DUnit t)'
-    In the type declaration for `LiftObject'
+    The first argument of ‛T’ should have kind ‛* -> * -> * -> *’,
+      but ‛Object f' f t’ has kind ‛* -> * -> *’
+    In the type ‛T (Object f' f t) (DUnit t)’
+    In the type declaration for ‛LiftObject’
diff --git a/tests/typecheck/should_fail/tcfail133.stderr b/tests/typecheck/should_fail/tcfail133.stderr
index 4a7c564b3..72eafd88d 100644
--- a/tests/typecheck/should_fail/tcfail133.stderr
+++ b/tests/typecheck/should_fail/tcfail133.stderr
@@ -1,26 +1,26 @@
-
-tcfail133.hs:2:61: Warning:
-    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
-
-tcfail133.hs:68:7:
-    No instance for (Show s0) arising from a use of `show'
-    The type variable `s0' is ambiguous
-    Note: there are several potential instances:
-      instance Show Zero -- Defined at tcfail133.hs:8:29
-      instance Show One -- Defined at tcfail133.hs:9:28
-      instance (Show a, Show b, Number a, Digit b) => Show (a :@ b)
-        -- Defined at tcfail133.hs:11:54
-      ...plus 26 others
-    In the expression: show
-    In the expression: show $ add (One :@ Zero) (One :@ One)
-    In an equation for `foo':
-        foo = show $ add (One :@ Zero) (One :@ One)
-
-tcfail133.hs:68:14:
-    No instance for (AddDigit (Zero :@ (One :@ One)) One s0)
-      arising from a use of `add'
-    In the second argument of `($)', namely
-      `add (One :@ Zero) (One :@ One)'
-    In the expression: show $ add (One :@ Zero) (One :@ One)
-    In an equation for `foo':
-        foo = show $ add (One :@ Zero) (One :@ One)
+
+tcfail133.hs:2:61: Warning:
+    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
+
+tcfail133.hs:68:7:
+    No instance for (Show s0) arising from a use of ‛show’
+    The type variable ‛s0’ is ambiguous
+    Note: there are several potential instances:
+      instance Show Zero -- Defined at tcfail133.hs:8:29
+      instance Show One -- Defined at tcfail133.hs:9:28
+      instance (Show a, Show b, Number a, Digit b) => Show (a :@ b)
+        -- Defined at tcfail133.hs:11:54
+      ...plus 26 others
+    In the expression: show
+    In the expression: show $ add (One :@ Zero) (One :@ One)
+    In an equation for ‛foo’:
+        foo = show $ add (One :@ Zero) (One :@ One)
+
+tcfail133.hs:68:14:
+    No instance for (AddDigit (Zero :@ (One :@ One)) One s0)
+      arising from a use of ‛add’
+    In the second argument of ‛($)’, namely
+      ‛add (One :@ Zero) (One :@ One)’
+    In the expression: show $ add (One :@ Zero) (One :@ One)
+    In an equation for ‛foo’:
+        foo = show $ add (One :@ Zero) (One :@ One)
diff --git a/tests/typecheck/should_fail/tcfail134.stderr b/tests/typecheck/should_fail/tcfail134.stderr
index 721a2f331..7ba962009 100644
--- a/tests/typecheck/should_fail/tcfail134.stderr
+++ b/tests/typecheck/should_fail/tcfail134.stderr
@@ -1,6 +1,6 @@
 
 tcfail134.hs:5:33:
-    Expecting one more argument to `XML'
-    Expected a type, but `XML' has kind `* -> Constraint'
-    In the type `a -> XML'
-    In the class declaration for `XML'
+    Expecting one more argument to ‛XML’
+    Expected a type, but ‛XML’ has kind ‛* -> Constraint’
+    In the type ‛a -> XML’
+    In the class declaration for ‛XML’
diff --git a/tests/typecheck/should_fail/tcfail135.stderr b/tests/typecheck/should_fail/tcfail135.stderr
index 6e6379f63..33712e3a9 100644
--- a/tests/typecheck/should_fail/tcfail135.stderr
+++ b/tests/typecheck/should_fail/tcfail135.stderr
@@ -1,6 +1,6 @@
 
 tcfail135.hs:6:23:
-    Expecting one more argument to `f'
-    Expected a type, but `f' has kind `k0 -> *'
-    In the type `f a -> f'
-    In the class declaration for `Foo'
+    Expecting one more argument to ‛f’
+    Expected a type, but ‛f’ has kind ‛k0 -> *’
+    In the type ‛f a -> f’
+    In the class declaration for ‛Foo’
diff --git a/tests/typecheck/should_fail/tcfail136.stderr b/tests/typecheck/should_fail/tcfail136.stderr
index 745aac23c..c2cb9d9cf 100644
--- a/tests/typecheck/should_fail/tcfail136.stderr
+++ b/tests/typecheck/should_fail/tcfail136.stderr
@@ -1,7 +1,7 @@
 
 tcfail136.hs:9:35:
-    Expecting one more argument to `SymDict'
-    Expected a type, but `SymDict' has kind `* -> *'
-    In the type `SymDict'
-    In the definition of data constructor `SymTable'
-    In the data declaration for `SymTable'
+    Expecting one more argument to ‛SymDict’
+    Expected a type, but ‛SymDict’ has kind ‛* -> *’
+    In the type ‛SymDict’
+    In the definition of data constructor ‛SymTable’
+    In the data declaration for ‛SymTable’
diff --git a/tests/typecheck/should_fail/tcfail137.stderr b/tests/typecheck/should_fail/tcfail137.stderr
index b84fff1df..05890e0b7 100644
--- a/tests/typecheck/should_fail/tcfail137.stderr
+++ b/tests/typecheck/should_fail/tcfail137.stderr
@@ -3,6 +3,6 @@ tcfail137.hs:1:14: Warning:
     -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
 tcfail137.hs:8:5:
-    No instance for (Floating Bool) arising from a use of `Test'
+    No instance for (Floating Bool) arising from a use of ‛Test’
     In the expression: Test [False, True]
-    In an equation for `x': x = Test [False, True]
+    In an equation for ‛x’: x = Test [False, True]
diff --git a/tests/typecheck/should_fail/tcfail139.stderr b/tests/typecheck/should_fail/tcfail139.stderr
index 91559a9f6..bfdc89b4f 100644
--- a/tests/typecheck/should_fail/tcfail139.stderr
+++ b/tests/typecheck/should_fail/tcfail139.stderr
@@ -1,7 +1,7 @@
 
 tcfail139.hs:6:10:
-    Illegal instance declaration for `Bounded Foo'
-        (All instance types must be of the form (T t1 ... tn)
-         where T is not a synonym.
-         Use -XTypeSynonymInstances if you want to disable this.)
-    In the instance declaration for `Bounded Foo'
+    Illegal instance declaration for ‛Bounded Foo’
+      (All instance types must be of the form (T t1 ... tn)
+       where T is not a synonym.
+       Use -XTypeSynonymInstances if you want to disable this.)
+    In the instance declaration for ‛Bounded Foo’
diff --git a/tests/typecheck/should_fail/tcfail140.stderr b/tests/typecheck/should_fail/tcfail140.stderr
index 4315837a2..aff19cb16 100644
--- a/tests/typecheck/should_fail/tcfail140.stderr
+++ b/tests/typecheck/should_fail/tcfail140.stderr
@@ -1,38 +1,38 @@
 
 tcfail140.hs:10:7:
-    Couldn't match expected type `a0 -> t' with actual type `Int'
+    Couldn't match expected type ‛a0 -> t’ with actual type ‛Int’
     Relevant bindings include bar :: t (bound at tcfail140.hs:10:1)
-    The function `f' is applied to two arguments,
-    but its type `Int -> Int' has only one
+    The function ‛f’ is applied to two arguments,
+    but its type ‛Int -> Int’ has only one
     In the expression: f 3 9
-    In an equation for `bar': bar = f 3 9
+    In an equation for ‛bar’: bar = f 3 9
 
 tcfail140.hs:12:10:
-    Couldn't match expected type `a1 -> t1' with actual type `Int'
+    Couldn't match expected type ‛a1 -> t1’ with actual type ‛Int’
     Relevant bindings include
       rot :: t -> t1 (bound at tcfail140.hs:12:1)
-    The operator `f' takes two arguments,
-    but its type `Int -> Int' has only one
+    The operator ‛f’ takes two arguments,
+    but its type ‛Int -> Int’ has only one
     In the expression: 3 `f` 4
-    In an equation for `rot': rot xs = 3 `f` 4
+    In an equation for ‛rot’: rot xs = 3 `f` 4
 
 tcfail140.hs:14:15:
-    Couldn't match expected type `a -> b' with actual type `Int'
+    Couldn't match expected type ‛a -> b’ with actual type ‛Int’
     Relevant bindings include
       bot :: [a] -> [b] (bound at tcfail140.hs:14:1)
       xs :: [a] (bound at tcfail140.hs:14:5)
-    The operator `f' takes two arguments,
-    but its type `Int -> Int' has only one
-    In the first argument of `map', namely `(3 `f`)'
+    The operator ‛f’ takes two arguments,
+    but its type ‛Int -> Int’ has only one
+    In the first argument of ‛map’, namely ‛(3 `f`)’
     In the expression: map (3 `f`) xs
 
 tcfail140.hs:16:8:
-    Constructor `Just' should have 1 argument, but has been given none
+    Constructor ‛Just’ should have 1 argument, but has been given none
     In the pattern: Just
     In the expression: (\ Just x -> x) :: Maybe a -> a
     In the expression: ((\ Just x -> x) :: Maybe a -> a) (Just 1)
 
 tcfail140.hs:19:1:
-    Couldn't match expected type `t0 -> Bool' with actual type `Int'
-    The equation(s) for `g' have two arguments,
-    but its type `Int -> Int' has only one
+    Couldn't match expected type ‛t0 -> Bool’ with actual type ‛Int’
+    The equation(s) for ‛g’ have two arguments,
+    but its type ‛Int -> Int’ has only one
diff --git a/tests/typecheck/should_fail/tcfail142.stderr b/tests/typecheck/should_fail/tcfail142.stderr
index e0ec8f4ca..767598e2b 100644
--- a/tests/typecheck/should_fail/tcfail142.stderr
+++ b/tests/typecheck/should_fail/tcfail142.stderr
@@ -1,10 +1,10 @@
-
-tcfail142.hs:18:8:
-    Could not deduce (Bar a0 r)
-      arising from the ambiguity check for `bar'
-    from the context (Bar a r)
-      bound by the type signature for bar :: Bar a r => r -> ()
-      at tcfail142.hs:18:8-25
-    The type variable `a0' is ambiguous
-    In the ambiguity check for: forall r a. Bar a r => r -> ()
-    In the type signature for `bar': bar :: Bar a r => r -> ()
+
+tcfail142.hs:18:8:
+    Could not deduce (Bar a0 r)
+      arising from the ambiguity check for ‛bar’
+    from the context (Bar a r)
+      bound by the type signature for bar :: Bar a r => r -> ()
+      at tcfail142.hs:18:8-25
+    The type variable ‛a0’ is ambiguous
+    In the ambiguity check for: forall r a. Bar a r => r -> ()
+    In the type signature for ‛bar’: bar :: Bar a r => r -> ()
diff --git a/tests/typecheck/should_fail/tcfail143.stderr b/tests/typecheck/should_fail/tcfail143.stderr
index 846f8c025..dadccbe78 100644
--- a/tests/typecheck/should_fail/tcfail143.stderr
+++ b/tests/typecheck/should_fail/tcfail143.stderr
@@ -1,11 +1,11 @@
 
 tcfail143.hs:29:9:
-    Couldn't match type `S Z' with `Z'
+    Couldn't match type ‛S Z’ with ‛Z’
     When using functional dependencies to combine
       MinMax a Z Z a,
-        arising from the dependency `a b -> c d'
+        arising from the dependency ‛a b -> c d’
         in the instance declaration at tcfail143.hs:11:10
       MinMax (S Z) Z Z Z,
-        arising from a use of `extend' at tcfail143.hs:29:9-16
+        arising from a use of ‛extend’ at tcfail143.hs:29:9-16
     In the expression: n1 `extend` n0
-    In an equation for `t2': t2 = n1 `extend` n0
+    In an equation for ‛t2’: t2 = n1 `extend` n0
diff --git a/tests/typecheck/should_fail/tcfail146.stderr b/tests/typecheck/should_fail/tcfail146.stderr
index 5b835c1a3..b62824e8c 100644
--- a/tests/typecheck/should_fail/tcfail146.stderr
+++ b/tests/typecheck/should_fail/tcfail146.stderr
@@ -1,6 +1,6 @@
 
 tcfail146.hs:7:22:
-    Expected a type, but `SClass a' has kind `Constraint'
-    In the type `SClass a'
-    In the definition of data constructor `SCon'
-    In the data declaration for `SData'
+    Expected a type, but ‛SClass a’ has kind ‛Constraint’
+    In the type ‛SClass a’
+    In the definition of data constructor ‛SCon’
+    In the data declaration for ‛SData’
diff --git a/tests/typecheck/should_fail/tcfail147.stderr b/tests/typecheck/should_fail/tcfail147.stderr
index cda722392..b7e75b06b 100644
--- a/tests/typecheck/should_fail/tcfail147.stderr
+++ b/tests/typecheck/should_fail/tcfail147.stderr
@@ -1,7 +1,7 @@
 
 tcfail147.hs:7:19:
-    Expecting one more argument to `XClass'
-    Expected a type, but `XClass' has kind `k0 -> Constraint'
-    In the type `XClass'
-    In the definition of data constructor `XCon'
-    In the data declaration for `XData'
+    Expecting one more argument to ‛XClass’
+    Expected a type, but ‛XClass’ has kind ‛k0 -> Constraint’
+    In the type ‛XClass’
+    In the definition of data constructor ‛XCon’
+    In the data declaration for ‛XData’
diff --git a/tests/typecheck/should_fail/tcfail148.stderr b/tests/typecheck/should_fail/tcfail148.stderr
index 22073f51c..cfa81e5b0 100644
--- a/tests/typecheck/should_fail/tcfail148.stderr
+++ b/tests/typecheck/should_fail/tcfail148.stderr
@@ -1,7 +1,7 @@
-
-tcfail148.hs:5:28:
-    Expecting one more argument to `List'
-    Expected a type, but `List' has kind `* -> *'
-    In the type `List'
-    In the definition of data constructor `Cons'
-    In the data declaration for `List'
+
+tcfail148.hs:5:28:
+    Expecting one more argument to ‛List’
+    Expected a type, but ‛List’ has kind ‛* -> *’
+    In the type ‛List’
+    In the definition of data constructor ‛Cons’
+    In the data declaration for ‛List’
diff --git a/tests/typecheck/should_fail/tcfail151.stderr b/tests/typecheck/should_fail/tcfail151.stderr
index f1884f3d3..d0dd7960b 100644
--- a/tests/typecheck/should_fail/tcfail151.stderr
+++ b/tests/typecheck/should_fail/tcfail151.stderr
@@ -1,8 +1,8 @@
-
-tcfail151.hs:1:14: Warning:
-    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
-
-tcfail151.hs:8:6:
-    Expecting one more argument to `Name a'
-    Expected a constraint, but `Name a' has kind `* -> Constraint'
-    In the data declaration for `Exp'
+
+tcfail151.hs:1:14: Warning:
+    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
+
+tcfail151.hs:8:6:
+    Expecting one more argument to ‛Name a’
+    Expected a constraint, but ‛Name a’ has kind ‛* -> Constraint’
+    In the data declaration for ‛Exp’
diff --git a/tests/typecheck/should_fail/tcfail152.stderr b/tests/typecheck/should_fail/tcfail152.stderr
index 24a872c9e..507587d07 100644
--- a/tests/typecheck/should_fail/tcfail152.stderr
+++ b/tests/typecheck/should_fail/tcfail152.stderr
@@ -1,7 +1,7 @@
 
 tcfail152.hs:10:14:
-    No instance for (Integral a) arising from a use of `toInteger'
+    No instance for (Integral a) arising from a use of ‛toInteger’
     Possible fix:
-      add (Integral a) to the context of the data constructor `C'
+      add (Integral a) to the context of the data constructor ‛C’
     In the expression: toInteger x
-    In an equation for `test': test (C x) = toInteger x
+    In an equation for ‛test’: test (C x) = toInteger x
diff --git a/tests/typecheck/should_fail/tcfail153.stderr b/tests/typecheck/should_fail/tcfail153.stderr
index 2647156f8..ba1da78d4 100644
--- a/tests/typecheck/should_fail/tcfail153.stderr
+++ b/tests/typecheck/should_fail/tcfail153.stderr
@@ -1,16 +1,16 @@
 
 tcfail153.hs:6:7:
-    Couldn't match type `a' with `Bool'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛Bool’
+      ‛a’ is a rigid type variable bound by
           the type signature for f :: a -> [a] at tcfail153.hs:5:6
     Expected type: [a]
       Actual type: [Bool]
     Relevant bindings include
       f :: a -> [a] (bound at tcfail153.hs:6:1)
       x :: a (bound at tcfail153.hs:6:3)
-    In the return type of a call of `g'
+    In the return type of a call of ‛g’
     In the expression: g x
-    In an equation for `f':
+    In an equation for ‛f’:
         f x
           = g x
           where
diff --git a/tests/typecheck/should_fail/tcfail154.stderr b/tests/typecheck/should_fail/tcfail154.stderr
index ca8a2978f..8977eacc7 100644
--- a/tests/typecheck/should_fail/tcfail154.stderr
+++ b/tests/typecheck/should_fail/tcfail154.stderr
@@ -1,6 +1,6 @@
-
-tcfail154.hs:12:10:
-    Variable `a' occurs more often than in the instance head
-      in the constraint: C a a
-    (Use -XUndecidableInstances to permit this)
-    In the instance declaration for `Eq (T a)'
+
+tcfail154.hs:12:10:
+    Variable ‛a’ occurs more often than in the instance head
+      in the constraint: C a a
+    (Use -XUndecidableInstances to permit this)
+    In the instance declaration for ‛Eq (T a)’
diff --git a/tests/typecheck/should_fail/tcfail155.stderr b/tests/typecheck/should_fail/tcfail155.stderr
index 1b5f1f3b0..58426f415 100644
--- a/tests/typecheck/should_fail/tcfail155.stderr
+++ b/tests/typecheck/should_fail/tcfail155.stderr
@@ -1,6 +1,6 @@
-
-tcfail155.hs:8:6:
-    Data constructor `P' returns type `L2'
-      instead of an instance of its parent type `T a'
-    In the definition of data constructor `P'
-    In the data declaration for `T'
+
+tcfail155.hs:8:6:
+    Data constructor ‛P’ returns type ‛L2’
+      instead of an instance of its parent type ‛T a’
+    In the definition of data constructor ‛P’
+    In the data declaration for ‛T’
diff --git a/tests/typecheck/should_fail/tcfail156.stderr b/tests/typecheck/should_fail/tcfail156.stderr
index d93549e13..7e84020fb 100644
--- a/tests/typecheck/should_fail/tcfail156.stderr
+++ b/tests/typecheck/should_fail/tcfail156.stderr
@@ -1,6 +1,6 @@
 
 tcfail156.hs:7:26:
     A newtype constructor cannot have an existential context,
-      but `Foo' does
-    In the definition of data constructor `Foo'
-    In the newtype declaration for `Foo'
+      but ‛Foo’ does
+    In the definition of data constructor ‛Foo’
+    In the newtype declaration for ‛Foo’
diff --git a/tests/typecheck/should_fail/tcfail157.stderr b/tests/typecheck/should_fail/tcfail157.stderr
index 304b76511..cfca878ed 100644
--- a/tests/typecheck/should_fail/tcfail157.stderr
+++ b/tests/typecheck/should_fail/tcfail157.stderr
@@ -1,12 +1,12 @@
-
-tcfail157.hs:27:10:
-    Variable `b' occurs more often than in the instance head
-      in the constraint: E m a b
-    (Use -XUndecidableInstances to permit this)
-    In the instance declaration for `Foo m (a -> ())'
-
-tcfail157.hs:27:10:
-    Variable `b' occurs more often than in the instance head
-      in the constraint: Foo m b
-    (Use -XUndecidableInstances to permit this)
-    In the instance declaration for `Foo m (a -> ())'
+
+tcfail157.hs:27:10:
+    Variable ‛b’ occurs more often than in the instance head
+      in the constraint: E m a b
+    (Use -XUndecidableInstances to permit this)
+    In the instance declaration for ‛Foo m (a -> ())’
+
+tcfail157.hs:27:10:
+    Variable ‛b’ occurs more often than in the instance head
+      in the constraint: Foo m b
+    (Use -XUndecidableInstances to permit this)
+    In the instance declaration for ‛Foo m (a -> ())’
diff --git a/tests/typecheck/should_fail/tcfail158.stderr b/tests/typecheck/should_fail/tcfail158.stderr
index 46385716f..47e05a5c7 100644
--- a/tests/typecheck/should_fail/tcfail158.stderr
+++ b/tests/typecheck/should_fail/tcfail158.stderr
@@ -1,5 +1,5 @@
 
 tcfail158.hs:14:19:
-    Expecting one more argument to `Val v'
-    Expected a type, but `Val v' has kind `* -> *'
-    In the type signature for `bar': bar :: forall v. Val v
+    Expecting one more argument to ‛Val v’
+    Expected a type, but ‛Val v’ has kind ‛* -> *’
+    In the type signature for ‛bar’: bar :: forall v. Val v
diff --git a/tests/typecheck/should_fail/tcfail159.stderr b/tests/typecheck/should_fail/tcfail159.stderr
index 3576c7e24..3ff73d8c7 100644
--- a/tests/typecheck/should_fail/tcfail159.stderr
+++ b/tests/typecheck/should_fail/tcfail159.stderr
@@ -1,6 +1,6 @@
 
 tcfail159.hs:9:11:
-    Couldn't match kind `*' with `#'
+    Couldn't match kind ‛*’ with ‛#’
     When matching types
       t0 :: *
       (# Int, Int #) :: #
diff --git a/tests/typecheck/should_fail/tcfail160.stderr b/tests/typecheck/should_fail/tcfail160.stderr
index 1be65a603..4d3a01fe1 100644
--- a/tests/typecheck/should_fail/tcfail160.stderr
+++ b/tests/typecheck/should_fail/tcfail160.stderr
@@ -1,5 +1,5 @@
 
 tcfail160.hs:7:8:
-    The first argument of `T' should have kind `* -> *',
-      but `Int' has kind `*'
-    In the type signature for `g': g :: T Int
+    The first argument of ‛T’ should have kind ‛* -> *’,
+      but ‛Int’ has kind ‛*’
+    In the type signature for ‛g’: g :: T Int
diff --git a/tests/typecheck/should_fail/tcfail161.stderr b/tests/typecheck/should_fail/tcfail161.stderr
index 21d8c1b06..79ca81dfa 100644
--- a/tests/typecheck/should_fail/tcfail161.stderr
+++ b/tests/typecheck/should_fail/tcfail161.stderr
@@ -1,5 +1,5 @@
 
 tcfail161.hs:5:7:
-    Expecting one more argument to `Maybe'
-    Expected kind `*', but `Maybe' has kind `* -> *'
-    In the type signature for `f': f :: [Maybe]
+    Expecting one more argument to ‛Maybe’
+    Expected kind ‛*’, but ‛Maybe’ has kind ‛* -> *’
+    In the type signature for ‛f’: f :: [Maybe]
diff --git a/tests/typecheck/should_fail/tcfail162.stderr b/tests/typecheck/should_fail/tcfail162.stderr
index 2563233b7..c14956e6b 100644
--- a/tests/typecheck/should_fail/tcfail162.stderr
+++ b/tests/typecheck/should_fail/tcfail162.stderr
@@ -1,7 +1,7 @@
-
-tcfail162.hs:10:33:
-    Expecting one more argument to `ForeignPtr'
-    Expected a type, but `ForeignPtr' has kind `* -> *'
-    In the type `ForeignPtr'
-    In the definition of data constructor `Foo'
-    In the data declaration for `Foo'
+
+tcfail162.hs:10:33:
+    Expecting one more argument to ‛ForeignPtr’
+    Expected a type, but ‛ForeignPtr’ has kind ‛* -> *’
+    In the type ‛ForeignPtr’
+    In the definition of data constructor ‛Foo’
+    In the data declaration for ‛Foo’
diff --git a/tests/typecheck/should_fail/tcfail164.stderr b/tests/typecheck/should_fail/tcfail164.stderr
index 65f9c9f9a..4a3be9027 100644
--- a/tests/typecheck/should_fail/tcfail164.stderr
+++ b/tests/typecheck/should_fail/tcfail164.stderr
@@ -4,12 +4,12 @@ tcfail164.hs:11:5:
       Specify the type by giving a type signature
       e.g. (tagToEnum# x) :: Bool
     In the expression: tagToEnum# 0#
-    In an equation for `f': f = tagToEnum# 0#
+    In an equation for ‛f’: f = tagToEnum# 0#
 
 tcfail164.hs:17:34:
     Bad call to tagToEnum# at type Int
       Result type must be an enumeration type
     In the expression: tagToEnum# value#
-    In an equation for `readUnboxable':
+    In an equation for ‛readUnboxable’:
         readUnboxable (I# value#) = tagToEnum# value#
-    In the instance declaration for `Unboxable Int'
+    In the instance declaration for ‛Unboxable Int’
diff --git a/tests/typecheck/should_fail/tcfail165.stderr b/tests/typecheck/should_fail/tcfail165.stderr
index 878a70712..09f359f83 100644
--- a/tests/typecheck/should_fail/tcfail165.stderr
+++ b/tests/typecheck/should_fail/tcfail165.stderr
@@ -1,11 +1,11 @@
 
 tcfail165.hs:15:23:
-    Couldn't match expected type `forall a. Show a => a -> String'
-                with actual type `b0 -> String'
-    In the second argument of `putMVar', namely
-      `(show :: forall b. Show b => b -> String)'
+    Couldn't match expected type ‛forall a. Show a => a -> String’
+                with actual type ‛b0 -> String’
+    In the second argument of ‛putMVar’, namely
+      ‛(show :: forall b. Show b => b -> String)’
     In a stmt of a 'do' block:
-        putMVar var (show :: forall b. Show b => b -> String)
+      putMVar var (show :: forall b. Show b => b -> String)
     In the expression:
       do { var <- newEmptyMVar ::
                     IO (MVar (forall a. Show a => a -> String));
diff --git a/tests/typecheck/should_fail/tcfail167.stderr b/tests/typecheck/should_fail/tcfail167.stderr
index f62f524eb..1613d4efa 100644
--- a/tests/typecheck/should_fail/tcfail167.stderr
+++ b/tests/typecheck/should_fail/tcfail167.stderr
@@ -1,9 +1,9 @@
 
 tcfail167.hs:14:14:
-    Couldn't match type `Char' with `Float'
+    Couldn't match type ‛Char’ with ‛Float’
     Inaccessible code in
       a pattern with constructor
         C2 :: T Float,
-      in an equation for `inaccessible'
+      in an equation for ‛inaccessible’
     In the pattern: C2
-    In an equation for `inaccessible': inaccessible C2 = ' '
+    In an equation for ‛inaccessible’: inaccessible C2 = ' '
diff --git a/tests/typecheck/should_fail/tcfail168.stderr b/tests/typecheck/should_fail/tcfail168.stderr
index a6a506456..99cd5a129 100644
--- a/tests/typecheck/should_fail/tcfail168.stderr
+++ b/tests/typecheck/should_fail/tcfail168.stderr
@@ -1,7 +1,7 @@
 
 tcfail168.hs:7:11:
-    Couldn't match expected type `IO a0'
-                with actual type `Char -> IO ()'
+    Couldn't match expected type ‛IO a0’
+                with actual type ‛Char -> IO ()’
     In a stmt of a 'do' block: putChar
     In the expression:
       do { putChar;
@@ -9,7 +9,7 @@ tcfail168.hs:7:11:
            putChar 'a';
            putChar 'a';
            .... }
-    In an equation for `foo':
+    In an equation for ‛foo’:
         foo
           = do { putChar;
                  putChar 'a';
diff --git a/tests/typecheck/should_fail/tcfail170.stderr b/tests/typecheck/should_fail/tcfail170.stderr
index 914ab0cde..7e8f0116e 100644
--- a/tests/typecheck/should_fail/tcfail170.stderr
+++ b/tests/typecheck/should_fail/tcfail170.stderr
@@ -1,6 +1,6 @@
 
 tcfail170.hs:7:10:
-    Illegal instance declaration for `C [p] [q]'
-        (the Coverage Condition fails for one of the functional dependencies;
-         Use -XUndecidableInstances to permit this)
-    In the instance declaration for `C [p] [q]'
+    Illegal instance declaration for ‛C [p] [q]’
+      (the Coverage Condition fails for one of the functional dependencies;
+       Use -XUndecidableInstances to permit this)
+    In the instance declaration for ‛C [p] [q]’
diff --git a/tests/typecheck/should_fail/tcfail171.stderr b/tests/typecheck/should_fail/tcfail171.stderr
index 79ed5f80b..e42b06ad0 100644
--- a/tests/typecheck/should_fail/tcfail171.stderr
+++ b/tests/typecheck/should_fail/tcfail171.stderr
@@ -1,8 +1,8 @@
 
 tcfail171.hs:9:10:
-    No instance for (PrintfArg a) arising from a use of `printf'
+    No instance for (PrintfArg a) arising from a use of ‛printf’
     Possible fix:
       add (PrintfArg a) to the context of
         the type signature for phex :: a -> b
     In the expression: printf "0x%x" x
-    In an equation for `phex': phex x = printf "0x%x" x
+    In an equation for ‛phex’: phex x = printf "0x%x" x
diff --git a/tests/typecheck/should_fail/tcfail173.stderr b/tests/typecheck/should_fail/tcfail173.stderr
index 4bda7d5c4..362f3ca28 100644
--- a/tests/typecheck/should_fail/tcfail173.stderr
+++ b/tests/typecheck/should_fail/tcfail173.stderr
@@ -1,4 +1,4 @@
 
 tcfail173.hs:5:12:
-    Illegal declaration of a type or class operator `<.>'
+    Illegal declaration of a type or class operator ‛<.>’
       Use -XTypeOperators to declare operators in type and declarations
diff --git a/tests/typecheck/should_fail/tcfail174.stderr b/tests/typecheck/should_fail/tcfail174.stderr
index d093e3238..56442b867 100644
--- a/tests/typecheck/should_fail/tcfail174.stderr
+++ b/tests/typecheck/should_fail/tcfail174.stderr
@@ -1,7 +1,7 @@
 
 tcfail174.hs:9:10:
-    Couldn't match expected type `forall a. a -> a'
-                with actual type `a0 -> a0'
-    In the first argument of `Base', namely `id'
+    Couldn't match expected type ‛forall a. a -> a’
+                with actual type ‛a0 -> a0’
+    In the first argument of ‛Base’, namely ‛id’
     In the expression: Base id
-    In an equation for `g': g = Base id
+    In an equation for ‛g’: g = Base id
diff --git a/tests/typecheck/should_fail/tcfail175.stderr b/tests/typecheck/should_fail/tcfail175.stderr
index 65f4cb9e4..6d0c10315 100644
--- a/tests/typecheck/should_fail/tcfail175.stderr
+++ b/tests/typecheck/should_fail/tcfail175.stderr
@@ -1,10 +1,10 @@
 
 tcfail175.hs:11:1:
-    Couldn't match expected type `String -> String -> String'
-                with actual type `a'
-      `a' is a rigid type variable bound by
+    Couldn't match expected type ‛String -> String -> String’
+                with actual type ‛a’
+      ‛a’ is a rigid type variable bound by
           the type signature for evalRHS :: Int -> a at tcfail175.hs:10:12
     Relevant bindings include
       evalRHS :: Int -> a (bound at tcfail175.hs:11:1)
-    The equation(s) for `evalRHS' have three arguments,
-    but its type `Int -> a' has only one
+    The equation(s) for ‛evalRHS’ have three arguments,
+    but its type ‛Int -> a’ has only one
diff --git a/tests/typecheck/should_fail/tcfail176.stderr b/tests/typecheck/should_fail/tcfail176.stderr
index f804b000c..cb829b43a 100644
--- a/tests/typecheck/should_fail/tcfail176.stderr
+++ b/tests/typecheck/should_fail/tcfail176.stderr
@@ -1,6 +1,6 @@
 
 tcfail176.hs:7:21:
-    Data constructor `Bug' returns type `Maybe a'
-      instead of an instance of its parent type `Bug a'
-    In the definition of data constructor `Bug'
-    In the newtype declaration for `Bug'
+    Data constructor ‛Bug’ returns type ‛Maybe a’
+      instead of an instance of its parent type ‛Bug a’
+    In the definition of data constructor ‛Bug’
+    In the newtype declaration for ‛Bug’
diff --git a/tests/typecheck/should_fail/tcfail177.stderr b/tests/typecheck/should_fail/tcfail177.stderr
index dc622daaf..5ef31f8d3 100644
--- a/tests/typecheck/should_fail/tcfail177.stderr
+++ b/tests/typecheck/should_fail/tcfail177.stderr
@@ -1,171 +1,171 @@
 
 tcfail177.hs:10:12:
-    Couldn't match expected type `Bool' with actual type `Int'
-    In the return type of a call of `foo'
+    Couldn't match expected type ‛Bool’ with actual type ‛Int’
+    In the return type of a call of ‛foo’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
-    In an equation for `allTests':
+    In an equation for ‛allTests’:
         allTests = foo [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", ....]
 
 tcfail177.hs:20:13:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:20:20:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:20:27:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:21:13:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:21:20:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:21:27:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:22:13:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:22:20:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:22:27:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:23:13:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:23:20:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:23:27:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:24:13:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:24:20:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:24:27:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:25:13:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:25:20:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
 
 tcfail177.hs:25:27:
-    Couldn't match expected type `Bool' with actual type `[Char]'
+    Couldn't match expected type ‛Bool’ with actual type ‛[Char]’
     In the expression: "Two"
-    In the first argument of `foo', namely
-      `[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]'
+    In the first argument of ‛foo’, namely
+      ‛[a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]’
     In the expression:
       foo
         [a ~?= b, "Three" ~?= "3", "Four" ~?= "4", "Five" ~?= "5", ....]
diff --git a/tests/typecheck/should_fail/tcfail178.stderr b/tests/typecheck/should_fail/tcfail178.stderr
index b0b6360df..fe0ffa71c 100644
--- a/tests/typecheck/should_fail/tcfail178.stderr
+++ b/tests/typecheck/should_fail/tcfail178.stderr
@@ -1,16 +1,16 @@
 
 tcfail178.hs:15:7:
-    Couldn't match type `()' with `[a]'
+    Couldn't match type ‛()’ with ‛[a]’
     Expected type: Bool -> [a]
       Actual type: Bool -> ()
     Relevant bindings include c :: [a] (bound at tcfail178.hs:15:1)
-    In the first argument of `a', namely `y'
+    In the first argument of ‛a’, namely ‛y’
     In the expression: a y
-    In an equation for `c': c = a y
+    In an equation for ‛c’: c = a y
 
 tcfail178.hs:18:7:
-    Couldn't match expected type `Bool -> [a]' with actual type `()'
+    Couldn't match expected type ‛Bool -> [a]’ with actual type ‛()’
     Relevant bindings include d :: [a] (bound at tcfail178.hs:18:1)
-    In the first argument of `a', namely `()'
+    In the first argument of ‛a’, namely ‛()’
     In the expression: a ()
-    In an equation for `d': d = a ()
+    In an equation for ‛d’: d = a ()
diff --git a/tests/typecheck/should_fail/tcfail179.stderr b/tests/typecheck/should_fail/tcfail179.stderr
index ed0325acd..89cd80437 100644
--- a/tests/typecheck/should_fail/tcfail179.stderr
+++ b/tests/typecheck/should_fail/tcfail179.stderr
@@ -1,18 +1,18 @@
 
 tcfail179.hs:14:39:
-    Couldn't match expected type `s' with actual type `x'
-      `x' is a rigid type variable bound by
+    Couldn't match expected type ‛s’ with actual type ‛x’
+      ‛x’ is a rigid type variable bound by
           a pattern with constructor
             T :: forall s x. (s -> (x -> s) -> (x, s, Int)) -> T s,
           in a case alternative
           at tcfail179.hs:14:14
-      `s' is a rigid type variable bound by
+      ‛s’ is a rigid type variable bound by
           the type signature for run :: T s -> Int at tcfail179.hs:12:8
     Relevant bindings include
       run :: T s -> Int (bound at tcfail179.hs:13:1)
       ts :: T s (bound at tcfail179.hs:13:5)
       g :: s -> (x -> s) -> (x, s, Int) (bound at tcfail179.hs:14:16)
       x :: x (bound at tcfail179.hs:14:26)
-    In the first argument of `g', namely `x'
+    In the first argument of ‛g’, namely ‛x’
     In the expression: g x id
     In a pattern binding: (x, _, b) = g x id
diff --git a/tests/typecheck/should_fail/tcfail180.stderr b/tests/typecheck/should_fail/tcfail180.stderr
index 96d76100e..8baeb4ed5 100644
--- a/tests/typecheck/should_fail/tcfail180.stderr
+++ b/tests/typecheck/should_fail/tcfail180.stderr
@@ -1,6 +1,6 @@
 
 tcfail180.hs:10:9:
-    Couldn't match expected type `f0 b0' with actual type `Bool'
+    Couldn't match expected type ‛f0 b0’ with actual type ‛Bool’
     In the pattern: True
     In a case alternative: True -> ()
     In the expression: case p of { True -> () }
diff --git a/tests/typecheck/should_fail/tcfail181.stderr b/tests/typecheck/should_fail/tcfail181.stderr
index d6e622cb3..33b75ff75 100644
--- a/tests/typecheck/should_fail/tcfail181.stderr
+++ b/tests/typecheck/should_fail/tcfail181.stderr
@@ -1,15 +1,15 @@
-
-tcfail181.hs:17:9:
-    Could not deduce (Monad m0) arising from a use of `foo'
-    from the context (Monad m)
-      bound by the inferred type of
-               wog :: Monad m => t -> Something (m Bool) e
-      at tcfail181.hs:17:1-30
-    The type variable `m0' is ambiguous
-    Note: there are several potential instances:
-      instance Monad ((->) r) -- Defined in `GHC.Base'
-      instance Monad IO -- Defined in `GHC.Base'
-      instance Monad [] -- Defined in `GHC.Base'
-    In the expression: foo
-    In the expression: foo {bar = return True}
-    In an equation for `wog': wog x = foo {bar = return True}
+
+tcfail181.hs:17:9:
+    Could not deduce (Monad m0) arising from a use of ‛foo’
+    from the context (Monad m)
+      bound by the inferred type of
+               wog :: Monad m => t -> Something (m Bool) e
+      at tcfail181.hs:17:1-30
+    The type variable ‛m0’ is ambiguous
+    Note: there are several potential instances:
+      instance Monad ((->) r) -- Defined in ‛GHC.Base’
+      instance Monad IO -- Defined in ‛GHC.Base’
+      instance Monad [] -- Defined in ‛GHC.Base’
+    In the expression: foo
+    In the expression: foo {bar = return True}
+    In an equation for ‛wog’: wog x = foo {bar = return True}
diff --git a/tests/typecheck/should_fail/tcfail182.stderr b/tests/typecheck/should_fail/tcfail182.stderr
index e02198723..36768f674 100644
--- a/tests/typecheck/should_fail/tcfail182.stderr
+++ b/tests/typecheck/should_fail/tcfail182.stderr
@@ -1,8 +1,8 @@
 
 tcfail182.hs:9:3:
-    Couldn't match expected type `Prelude.Maybe a'
-                with actual type `Maybe t0'
+    Couldn't match expected type ‛Prelude.Maybe a’
+                with actual type ‛Maybe t0’
     Relevant bindings include
       f :: Prelude.Maybe a -> Int (bound at tcfail182.hs:9:1)
     In the pattern: Foo
-    In an equation for `f': f Foo = 3
+    In an equation for ‛f’: f Foo = 3
diff --git a/tests/typecheck/should_fail/tcfail184.stderr b/tests/typecheck/should_fail/tcfail184.stderr
index 20920d822..cfb89422d 100644
--- a/tests/typecheck/should_fail/tcfail184.stderr
+++ b/tests/typecheck/should_fail/tcfail184.stderr
@@ -1,7 +1,7 @@
-
-tcfail184.hs:8:19:
-    Illegal polymorphic or qualified type:
-      forall a. Ord a => [a] -> [a]
-    Perhaps you intended to use -XRankNTypes or -XRank2Types
-    In the definition of data constructor `MkSwizzle'
-    In the newtype declaration for `Swizzle'
+
+tcfail184.hs:8:19:
+    Illegal polymorphic or qualified type:
+      forall a. Ord a => [a] -> [a]
+    Perhaps you intended to use -XRankNTypes or -XRank2Types
+    In the definition of data constructor ‛MkSwizzle’
+    In the newtype declaration for ‛Swizzle’
diff --git a/tests/typecheck/should_fail/tcfail185.stderr b/tests/typecheck/should_fail/tcfail185.stderr
index 1e4c8d718..f46211e4f 100644
--- a/tests/typecheck/should_fail/tcfail185.stderr
+++ b/tests/typecheck/should_fail/tcfail185.stderr
@@ -1,17 +1,17 @@
 
 tcfail185.hs:7:46:
-    Couldn't match expected type `Int -> Int' with actual type `Bool'
+    Couldn't match expected type ‛Int -> Int’ with actual type ‛Bool’
     In the expression: x
     In the expression:
-        let
-          y1 = y
-          y2 = y1
-          y3 = y2
-          ....
-        in x
+      let
+        y1 = y
+        y2 = y1
+        y3 = y2
+        ....
+      in x
     In the expression:
-        \ x y
-            -> let
-                 y1 = ...
-                 ....
-               in x
+      \ x y
+        -> let
+             y1 = ...
+             ....
+           in x
diff --git a/tests/typecheck/should_fail/tcfail186.stderr b/tests/typecheck/should_fail/tcfail186.stderr
index b22e672ae..f9ced11d3 100644
--- a/tests/typecheck/should_fail/tcfail186.stderr
+++ b/tests/typecheck/should_fail/tcfail186.stderr
@@ -1,8 +1,8 @@
 
 tcfail186.hs:7:9:
-    Couldn't match type `[Char]' with `Int'
+    Couldn't match type ‛[Char]’ with ‛Int’
     Expected type: PhantomSyn a0
       Actual type: [Char]
-    In the first argument of `f', namely `"hoo"'
+    In the first argument of ‛f’, namely ‛"hoo"’
     In the expression: f "hoo"
-    In an equation for `foo': foo = f "hoo"
+    In an equation for ‛foo’: foo = f "hoo"
diff --git a/tests/typecheck/should_fail/tcfail187.stderr b/tests/typecheck/should_fail/tcfail187.stderr
index 07a741d02..10a9115ff 100644
--- a/tests/typecheck/should_fail/tcfail187.stderr
+++ b/tests/typecheck/should_fail/tcfail187.stderr
@@ -1,5 +1,5 @@
 
 tcfail187.hs:7:6:
-    Constructor `:::' should have no arguments, but has been given 2
+    Constructor ‛:::’ should have no arguments, but has been given 2
     In the pattern: x ::: y
-    In an equation for `foo': foo (x ::: y) = ()
+    In an equation for ‛foo’: foo (x ::: y) = ()
diff --git a/tests/typecheck/should_fail/tcfail189.stderr b/tests/typecheck/should_fail/tcfail189.stderr
index 6364cc2d5..a7105907a 100644
--- a/tests/typecheck/should_fail/tcfail189.stderr
+++ b/tests/typecheck/should_fail/tcfail189.stderr
@@ -1,9 +1,9 @@
 
 tcfail189.hs:10:31:
-    Couldn't match type `[a0]' with `a -> a1'
+    Couldn't match type ‛[a0]’ with ‛a -> a1’
     Expected type: (a -> a1) -> [a] -> [[a]]
       Actual type: [a0] -> [a0]
-    In the return type of a call of `take'
-    Probable cause: `take' is applied to too many arguments
+    In the return type of a call of ‛take’
+    Probable cause: ‛take’ is applied to too many arguments
     In the expression: take 2
     In a stmt of a list comprehension: then group by x using take 2
diff --git a/tests/typecheck/should_fail/tcfail190.stderr b/tests/typecheck/should_fail/tcfail190.stderr
index db2d842f5..df56a79a7 100644
--- a/tests/typecheck/should_fail/tcfail190.stderr
+++ b/tests/typecheck/should_fail/tcfail190.stderr
@@ -1,6 +1,6 @@
 
 tcfail190.hs:14:31:
-    No instance for (Ord Unorderable) arising from a use of `groupWith'
+    No instance for (Ord Unorderable) arising from a use of ‛groupWith’
     In the expression: groupWith
     In a stmt of a list comprehension: then group by x using groupWith
     In the expression:
diff --git a/tests/typecheck/should_fail/tcfail191.stderr b/tests/typecheck/should_fail/tcfail191.stderr
index a276a04ea..b84f6f770 100644
--- a/tests/typecheck/should_fail/tcfail191.stderr
+++ b/tests/typecheck/should_fail/tcfail191.stderr
@@ -1,10 +1,10 @@
 
 tcfail191.hs:11:26:
-    Couldn't match type `a' with `[a]'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛[a]’
+      ‛a’ is a rigid type variable bound by
           a type expected by the context: [a] -> [[a]] at tcfail191.hs:11:9
     Expected type: [a] -> [[a]]
       Actual type: [a] -> [a]
-    In the return type of a call of `take'
+    In the return type of a call of ‛take’
     In the expression: take 5
     In a stmt of a list comprehension: then group using take 5
diff --git a/tests/typecheck/should_fail/tcfail192.stderr b/tests/typecheck/should_fail/tcfail192.stderr
index caf7ef140..0fcced9cc 100644
--- a/tests/typecheck/should_fail/tcfail192.stderr
+++ b/tests/typecheck/should_fail/tcfail192.stderr
@@ -1,10 +1,10 @@
 
 tcfail192.hs:10:26:
-    Couldn't match type `a' with `[a]'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛[a]’
+      ‛a’ is a rigid type variable bound by
           a type expected by the context: [a] -> [[a]] at tcfail192.hs:10:9
     Expected type: [a] -> [[a]]
       Actual type: [a] -> [a]
-    In the return type of a call of `take'
+    In the return type of a call of ‛take’
     In the expression: take 5
     In a stmt of a list comprehension: then group using take 5
diff --git a/tests/typecheck/should_fail/tcfail193.stderr b/tests/typecheck/should_fail/tcfail193.stderr
index 47375e840..9c9e94b15 100644
--- a/tests/typecheck/should_fail/tcfail193.stderr
+++ b/tests/typecheck/should_fail/tcfail193.stderr
@@ -1,7 +1,7 @@
 
 tcfail193.hs:10:31:
-    Couldn't match type `a' with `[a]'
-      `a' is a rigid type variable bound by
+    Couldn't match type ‛a’ with ‛[a]’
+      ‛a’ is a rigid type variable bound by
           a type expected by the context: [a] -> [a] at tcfail193.hs:10:26
     Expected type: [a] -> [a]
       Actual type: [a] -> [[a]]
diff --git a/tests/typecheck/should_fail/tcfail194.stderr b/tests/typecheck/should_fail/tcfail194.stderr
index 7190a884c..9140c1642 100644
--- a/tests/typecheck/should_fail/tcfail194.stderr
+++ b/tests/typecheck/should_fail/tcfail194.stderr
@@ -1,10 +1,10 @@
 
 tcfail194.hs:9:29:
-    Couldn't match type `[a0]' with `a -> t'
+    Couldn't match type ‛[a0]’ with ‛a -> t’
     Expected type: (a -> t) -> [a] -> [a]
       Actual type: [a0] -> [a0]
     Relevant bindings include z :: [t] (bound at tcfail194.hs:9:1)
-    In the return type of a call of `take'
-    Probable cause: `take' is applied to too many arguments
+    In the return type of a call of ‛take’
+    Probable cause: ‛take’ is applied to too many arguments
     In the expression: take 5
     In a stmt of a list comprehension: then take 5 by x
diff --git a/tests/typecheck/should_fail/tcfail195.stderr b/tests/typecheck/should_fail/tcfail195.stderr
index d690ebac8..4800e7564 100644
--- a/tests/typecheck/should_fail/tcfail195.stderr
+++ b/tests/typecheck/should_fail/tcfail195.stderr
@@ -1,5 +1,5 @@
-
-tcfail195.hs:6:3:
-    Illegal polymorphic or qualified type: forall a. a
-    In the definition of data constructor `Foo'
-    In the data declaration for `Foo'
+
+tcfail195.hs:6:3:
+    Illegal polymorphic or qualified type: forall a. a
+    In the definition of data constructor ‛Foo’
+    In the data declaration for ‛Foo’
diff --git a/tests/typecheck/should_fail/tcfail196.stderr b/tests/typecheck/should_fail/tcfail196.stderr
index ea6f16fd9..ffedbdf1b 100644
--- a/tests/typecheck/should_fail/tcfail196.stderr
+++ b/tests/typecheck/should_fail/tcfail196.stderr
@@ -1,5 +1,5 @@
 
 tcfail196.hs:5:8:
     Illegal polymorphic or qualified type: forall a. a
-    In the type signature for `bar':
+    In the type signature for ‛bar’:
       bar :: Num (forall a. a) => Int -> Int
diff --git a/tests/typecheck/should_fail/tcfail197.stderr b/tests/typecheck/should_fail/tcfail197.stderr
index 464dacb07..30bf9583f 100644
--- a/tests/typecheck/should_fail/tcfail197.stderr
+++ b/tests/typecheck/should_fail/tcfail197.stderr
@@ -2,4 +2,4 @@
 tcfail197.hs:5:8:
     Illegal polymorphic or qualified type: forall a. a
     Perhaps you intended to use -XImpredicativeTypes
-    In the type signature for `foo': foo :: [forall a. a] -> Int
+    In the type signature for ‛foo’: foo :: [forall a. a] -> Int
diff --git a/tests/typecheck/should_fail/tcfail198.stderr b/tests/typecheck/should_fail/tcfail198.stderr
index 22a09f59f..a2c66aa4b 100644
--- a/tests/typecheck/should_fail/tcfail198.stderr
+++ b/tests/typecheck/should_fail/tcfail198.stderr
@@ -1,7 +1,7 @@
 
 tcfail198.hs:6:36:
-    Couldn't match expected type `a1' with actual type `a'
-      because type variable `a1' would escape its scope
+    Couldn't match expected type ‛a1’ with actual type ‛a’
+      because type variable ‛a1’ would escape its scope
     This (rigid, skolem) type variable is bound by
       an expression type signature: a1
       at tcfail198.hs:6:36-41
@@ -10,5 +10,5 @@ tcfail198.hs:6:36:
       x :: a (bound at tcfail198.hs:6:19)
       xs :: [a] (bound at tcfail198.hs:6:21)
     In the expression: x :: a
-    In the second argument of `(++)', namely `[x :: a]'
+    In the second argument of ‛(++)’, namely ‛[x :: a]’
     In the expression: xs ++ [x :: a]
diff --git a/tests/typecheck/should_fail/tcfail199.stderr b/tests/typecheck/should_fail/tcfail199.stderr
index 6866a2645..3e1df5e80 100644
--- a/tests/typecheck/should_fail/tcfail199.stderr
+++ b/tests/typecheck/should_fail/tcfail199.stderr
@@ -1,5 +1,5 @@
 
 tcfail199.hs:5:1:
-    Couldn't match expected type `IO t0' with actual type `[Char]'
+    Couldn't match expected type ‛IO t0’ with actual type ‛[Char]’
     In the expression: main
-    When checking the type of the function `main'
+    When checking the type of the function ‛main’
diff --git a/tests/typecheck/should_fail/tcfail200.stderr b/tests/typecheck/should_fail/tcfail200.stderr
index 731f906fd..57c174d10 100644
--- a/tests/typecheck/should_fail/tcfail200.stderr
+++ b/tests/typecheck/should_fail/tcfail200.stderr
@@ -1,9 +1,9 @@
 
 tcfail200.hs:5:15:
-    Couldn't match kind `*' with `#'
+    Couldn't match kind ‛*’ with ‛#’
     When matching types
       t1 :: *
       GHC.Prim.Int# :: #
     In the expression: 1#
     In the expression: (1#, 'c')
-    In an equation for `x': x = (1#, 'c')
+    In an equation for ‛x’: x = (1#, 'c')
diff --git a/tests/typecheck/should_fail/tcfail201.stderr b/tests/typecheck/should_fail/tcfail201.stderr
index 4d93f9fad..ada710e43 100644
--- a/tests/typecheck/should_fail/tcfail201.stderr
+++ b/tests/typecheck/should_fail/tcfail201.stderr
@@ -1,7 +1,7 @@
 
 tcfail201.hs:17:27:
-    Couldn't match expected type `a' with actual type `HsDoc t0'
-      `a' is a rigid type variable bound by
+    Couldn't match expected type ‛a’ with actual type ‛HsDoc t0’
+      ‛a’ is a rigid type variable bound by
           the type signature for
             gfoldl' :: (forall a1 b. c (a1 -> b) -> a1 -> c b)
                        -> (forall g. g -> c g) -> a -> c a
diff --git a/tests/typecheck/should_fail/tcfail203.stderr b/tests/typecheck/should_fail/tcfail203.stderr
index 29cf84095..7635b68b4 100644
--- a/tests/typecheck/should_fail/tcfail203.stderr
+++ b/tests/typecheck/should_fail/tcfail203.stderr
@@ -1,35 +1,35 @@
 
-tcfail203.hs:28:11:
-    Warning: Pattern bindings containing unlifted types should use an outermost bang pattern:
-               (I# x) = 5
-    In an equation for `fail2':
+tcfail203.hs:28:11: Warning:
+    Pattern bindings containing unlifted types should use an outermost bang pattern:
+      (I# x) = 5
+    In an equation for ‛fail2’:
         fail2
           = 'a'
           where
               (I# x) = 5
 
-tcfail203.hs:31:11:
-    Warning: Pattern bindings containing unlifted types should use an outermost bang pattern:
-               (b, I# x) = (True, 5)
-    In an equation for `fail3':
+tcfail203.hs:31:11: Warning:
+    Pattern bindings containing unlifted types should use an outermost bang pattern:
+      (b, I# x) = (True, 5)
+    In an equation for ‛fail3’:
         fail3
           = 'a'
           where
               (b, I# x) = (True, 5)
 
-tcfail203.hs:40:11:
-    Warning: Pattern bindings containing unlifted types should use an outermost bang pattern:
-               (I# !x) = 5
-    In an equation for `fail6':
+tcfail203.hs:40:11: Warning:
+    Pattern bindings containing unlifted types should use an outermost bang pattern:
+      (I# !x) = 5
+    In an equation for ‛fail6’:
         fail6
           = 'a'
           where
               (I# !x) = 5
 
-tcfail203.hs:43:11:
-    Warning: Pattern bindings containing unlifted types should use an outermost bang pattern:
-               (b, !(I# x)) = (True, 5)
-    In an equation for `fail7':
+tcfail203.hs:43:11: Warning:
+    Pattern bindings containing unlifted types should use an outermost bang pattern:
+      (b, !(I# x)) = (True, 5)
+    In an equation for ‛fail7’:
         fail7
           = 'a'
           where
diff --git a/tests/typecheck/should_fail/tcfail204.stderr b/tests/typecheck/should_fail/tcfail204.stderr
index e9d9bb739..bfbac5443 100644
--- a/tests/typecheck/should_fail/tcfail204.stderr
+++ b/tests/typecheck/should_fail/tcfail204.stderr
@@ -1,13 +1,13 @@
 
-tcfail204.hs:10:15:
-    Warning: Defaulting the following constraint(s) to type `Double'
-               (Fractional a0) arising from the literal `6.3'
-                               at tcfail204.hs:10:15-17
-               (RealFrac a0) arising from a use of `ceiling'
-                             at tcfail204.hs:10:7-13
-    In the first argument of `ceiling', namely `6.3'
+tcfail204.hs:10:15: Warning:
+    Defaulting the following constraint(s) to type ‛Double’
+      (Fractional a0)
+        arising from the literal ‛6.3’ at tcfail204.hs:10:15-17
+      (RealFrac a0)
+        arising from a use of ‛ceiling’ at tcfail204.hs:10:7-13
+    In the first argument of ‛ceiling’, namely ‛6.3’
     In the expression: ceiling 6.3
-    In an equation for `foo': foo = ceiling 6.3
+    In an equation for ‛foo’: foo = ceiling 6.3
 
 <no location info>: 
 Failing due to -Werror.
diff --git a/tests/typecheck/should_fail/tcfail206.stderr b/tests/typecheck/should_fail/tcfail206.stderr
index b5b9aef83..d503b1620 100644
--- a/tests/typecheck/should_fail/tcfail206.stderr
+++ b/tests/typecheck/should_fail/tcfail206.stderr
@@ -1,28 +1,28 @@
 
 tcfail206.hs:5:5:
-    Couldn't match type `Bool' with `Int'
+    Couldn't match type ‛Bool’ with ‛Int’
     Expected type: Bool -> (Int, Bool)
       Actual type: Bool -> (Bool, Bool)
     In the expression: (, True)
-    In an equation for `a': a = (, True)
+    In an equation for ‛a’: a = (, True)
 
 tcfail206.hs:8:5:
-    Couldn't match type `(t0, Int)' with `Bool -> (Int, Bool)'
+    Couldn't match type ‛(t0, Int)’ with ‛Bool -> (Int, Bool)’
     Expected type: Int -> Bool -> (Int, Bool)
       Actual type: Int -> (t0, Int)
     In the expression: (1,)
-    In an equation for `b': b = (1,)
+    In an equation for ‛b’: b = (1,)
 
 tcfail206.hs:14:5:
-    Couldn't match type `Bool' with `Int'
+    Couldn't match type ‛Bool’ with ‛Int’
     Expected type: Bool -> (# Int, Bool #)
       Actual type: Bool -> (# Bool, Bool #)
     In the expression: (# , True #)
-    In an equation for `d': d = (# , True #)
+    In an equation for ‛d’: d = (# , True #)
 
 tcfail206.hs:17:5:
-    Couldn't match type `(# a0, Int #)' with `Bool -> (# Int, Bool #)'
+    Couldn't match type ‛(# a0, Int #)’ with ‛Bool -> (# Int, Bool #)’
     Expected type: Int -> Bool -> (# Int, Bool #)
       Actual type: Int -> (# a0, Int #)
     In the expression: (# 1, #)
-    In an equation for `e': e = (# 1, #)
+    In an equation for ‛e’: e = (# 1, #)
diff --git a/tests/typecheck/should_fail/tcfail207.stderr b/tests/typecheck/should_fail/tcfail207.stderr
index 3e96a0994..f647a324b 100644
--- a/tests/typecheck/should_fail/tcfail207.stderr
+++ b/tests/typecheck/should_fail/tcfail207.stderr
@@ -1,16 +1,16 @@
 
 tcfail207.hs:5:7:
-    Couldn't match expected type `[Int] -> [Int]'
-                with actual type `[a1]'
-    In the return type of a call of `take'
-    Probable cause: `take' is applied to too many arguments
+    Couldn't match expected type ‛[Int] -> [Int]’
+                with actual type ‛[a1]’
+    In the return type of a call of ‛take’
+    Probable cause: ‛take’ is applied to too many arguments
     In the expression: take x []
-    In an equation for `f': f x = take x []
+    In an equation for ‛f’: f x = take x []
 
 tcfail207.hs:9:5:
-    Couldn't match expected type `[Int]'
-                with actual type `[a0] -> [a0]'
-    In the return type of a call of `take'
-    Probable cause: `take' is applied to too few arguments
+    Couldn't match expected type ‛[Int]’
+                with actual type ‛[a0] -> [a0]’
+    In the return type of a call of ‛take’
+    Probable cause: ‛take’ is applied to too few arguments
     In the expression: take 3
-    In an equation for `g': g = take 3
+    In an equation for ‛g’: g = take 3
diff --git a/tests/typecheck/should_fail/tcfail208.stderr b/tests/typecheck/should_fail/tcfail208.stderr
index d3172b6a9..7419e90c5 100644
--- a/tests/typecheck/should_fail/tcfail208.stderr
+++ b/tests/typecheck/should_fail/tcfail208.stderr
@@ -1,9 +1,9 @@
 
 tcfail208.hs:4:19:
-    Could not deduce (Eq (m a)) arising from a use of `=='
+    Could not deduce (Eq (m a)) arising from a use of ‛==’
     from the context (Monad m, Eq a)
       bound by the type signature for
                  f :: (Monad m, Eq a) => a -> m a -> Bool
       at tcfail208.hs:3:6-40
     In the expression: (return x == y)
-    In an equation for `f': f x y = (return x == y)
+    In an equation for ‛f’: f x y = (return x == y)
diff --git a/tests/typecheck/should_fail/tcfail209.stderr b/tests/typecheck/should_fail/tcfail209.stderr
index d0a59e970..65bc8de45 100644
--- a/tests/typecheck/should_fail/tcfail209.stderr
+++ b/tests/typecheck/should_fail/tcfail209.stderr
@@ -1,5 +1,5 @@
-
-tcfail209.hs:3:1:
-    Illegal constraint synonym of kind: `* -> Constraint'
-      (Use -XConstraintKinds to permit this)
-    In the type declaration for `Showish'
+
+tcfail209.hs:3:1:
+    Illegal constraint synonym of kind: ‛* -> Constraint’
+      (Use -XConstraintKinds to permit this)
+    In the type declaration for ‛Showish’
diff --git a/tests/typecheck/should_fail/tcfail209a.stderr b/tests/typecheck/should_fail/tcfail209a.stderr
index 1b56c8672..9acacaaac 100644
--- a/tests/typecheck/should_fail/tcfail209a.stderr
+++ b/tests/typecheck/should_fail/tcfail209a.stderr
@@ -2,5 +2,5 @@
 tcfail209a.hs:3:6:
     Illegal tuple constraint: (Show a, Num a)
       (Use -XConstraintKinds to permit this)
-    In the type signature for `g':
+    In the type signature for ‛g’:
       g :: ((Show a, Num a), Eq a) => a -> a
diff --git a/tests/typecheck/should_fail/tcfail210.stderr b/tests/typecheck/should_fail/tcfail210.stderr
index 95aba8e61..9b998d425 100644
--- a/tests/typecheck/should_fail/tcfail210.stderr
+++ b/tests/typecheck/should_fail/tcfail210.stderr
@@ -1,3 +1,3 @@
 
 tcfail210.hs:4:31:
-    Not in scope: type constructor or class `Constraint'
+    Not in scope: type constructor or class ‛Constraint’
diff --git a/tests/typecheck/should_fail/tcfail211.stderr b/tests/typecheck/should_fail/tcfail211.stderr
index 81e04d670..491349b12 100644
--- a/tests/typecheck/should_fail/tcfail211.stderr
+++ b/tests/typecheck/should_fail/tcfail211.stderr
@@ -1,7 +1,6 @@
 
 tcfail211.hs:16:13:
-    Unbound implicit parameter (?imp::Int)
-      arising from a use of `test'
-    In the first argument of `print', namely `test'
+    Unbound implicit parameter (?imp::Int) arising from a use of ‛test’
+    In the first argument of ‛print’, namely ‛test’
     In the expression: print test
-    In an equation for `use': use = print test
+    In an equation for ‛use’: use = print test
diff --git a/tests/typecheck/should_fail/tcfail212.stderr b/tests/typecheck/should_fail/tcfail212.stderr
index a94496181..b116fd1d9 100644
--- a/tests/typecheck/should_fail/tcfail212.stderr
+++ b/tests/typecheck/should_fail/tcfail212.stderr
@@ -1,10 +1,10 @@
 
 tcfail212.hs:10:7:
-    Expecting one more argument to `Maybe'
-    The first argument of a tuple should have kind `*',
-      but `Maybe' has kind `* -> *'
-    In the type signature for `f': f :: (Maybe, Either Int)
+    Expecting one more argument to ‛Maybe’
+    The first argument of a tuple should have kind ‛*’,
+      but ‛Maybe’ has kind ‛* -> *’
+    In the type signature for ‛f’: f :: (Maybe, Either Int)
 
 tcfail212.hs:13:7:
-    Expecting a lifted type, but `Int#' is unlifted
-    In the type signature for `g': g :: (Int#, Int#)
+    Expecting a lifted type, but ‛Int#’ is unlifted
+    In the type signature for ‛g’: g :: (Int#, Int#)
diff --git a/tests/typecheck/should_fail/tcfail213.stderr b/tests/typecheck/should_fail/tcfail213.stderr
index 920871138..bef0507b8 100644
--- a/tests/typecheck/should_fail/tcfail213.stderr
+++ b/tests/typecheck/should_fail/tcfail213.stderr
@@ -1,7 +1,7 @@
-
-tcfail213.hs:8:1:
-    Illegal constraint `F a' in a superclass/instance context
-      (Use -XUndecidableInstances to permit this)
-    In the context: (F a)
-    While checking the super-classes of class `C'
-    In the class declaration for `C'
+
+tcfail213.hs:8:1:
+    Illegal constraint ‛F a’ in a superclass/instance context
+      (Use -XUndecidableInstances to permit this)
+    In the context: (F a)
+    While checking the super-classes of class ‛C’
+    In the class declaration for ‛C’
diff --git a/tests/typecheck/should_fail/tcfail214.stderr b/tests/typecheck/should_fail/tcfail214.stderr
index d8df299f5..983d4b39a 100644
--- a/tests/typecheck/should_fail/tcfail214.stderr
+++ b/tests/typecheck/should_fail/tcfail214.stderr
@@ -1,7 +1,7 @@
-
-tcfail214.hs:9:10:
-    Illegal constraint `F a' in a superclass/instance context
-      (Use -XUndecidableInstances to permit this)
-    In the context: (F a)
-    While checking an instance declaration
-    In the instance declaration for `C [a]'
+
+tcfail214.hs:9:10:
+    Illegal constraint ‛F a’ in a superclass/instance context
+      (Use -XUndecidableInstances to permit this)
+    In the context: (F a)
+    While checking an instance declaration
+    In the instance declaration for ‛C [a]’
diff --git a/tests/typecheck/should_fail/tcfail215.stderr b/tests/typecheck/should_fail/tcfail215.stderr
index 75c894eda..a9fe4da24 100644
--- a/tests/typecheck/should_fail/tcfail215.stderr
+++ b/tests/typecheck/should_fail/tcfail215.stderr
@@ -1,4 +1,4 @@
 
 tcfail215.hs:8:15:
-    Expecting a lifted type, but `Int#' is unlifted
-    In the type signature for `foo': foo :: ?x :: Int# => Int
+    Expecting a lifted type, but ‛Int#’ is unlifted
+    In the type signature for ‛foo’: foo :: ?x :: Int# => Int
diff --git a/tests/typecheck/should_fail/tcfail216.stderr b/tests/typecheck/should_fail/tcfail216.stderr
index bcb07b8f1..11b077e7e 100644
--- a/tests/typecheck/should_fail/tcfail216.stderr
+++ b/tests/typecheck/should_fail/tcfail216.stderr
@@ -1,4 +1,4 @@
 
 tcfail216.hs:5:1:
     Cycle in class declaration (via superclasses): A -> A
-    In the class declaration for `A'
+    In the class declaration for ‛A’
diff --git a/tests/typecheck/should_fail/tcfail217.stderr b/tests/typecheck/should_fail/tcfail217.stderr
index 79f3b0e0a..64584169e 100644
--- a/tests/typecheck/should_fail/tcfail217.stderr
+++ b/tests/typecheck/should_fail/tcfail217.stderr
@@ -1,4 +1,4 @@
 
 tcfail217.hs:7:1:
     Cycle in class declaration (via superclasses): A -> Aish -> A
-    In the class declaration for `A'
+    In the class declaration for ‛A’
diff --git a/tests/typecheck/should_run/tcrun035.stderr b/tests/typecheck/should_run/tcrun035.stderr
index f0fc2d53b..9c7a3c748 100644
--- a/tests/typecheck/should_run/tcrun035.stderr
+++ b/tests/typecheck/should_run/tcrun035.stderr
@@ -1,11 +1,11 @@
-
-tcrun035.hs:13:7:
-    Couldn't match type `IO a'
-                  with `forall (m :: * -> *). Monad m => m a'
-    Expected type: (forall (m :: * -> *). Monad m => m a) -> IO a
-      Actual type: IO a -> IO a
-    Relevant bindings include
-      foo :: (forall (m :: * -> *). Monad m => m a) -> IO a
-        (bound at tcrun035.hs:13:1)
-    In the expression: id . id
-    In an equation for `foo': foo = id . id
+
+tcrun035.hs:13:7:
+    Couldn't match type ‛IO a’
+                  with ‛forall (m :: * -> *). Monad m => m a’
+    Expected type: (forall (m :: * -> *). Monad m => m a) -> IO a
+      Actual type: IO a -> IO a
+    Relevant bindings include
+      foo :: (forall (m :: * -> *). Monad m => m a) -> IO a
+        (bound at tcrun035.hs:13:1)
+    In the expression: id . id
+    In an equation for ‛foo’: foo = id . id
-- 
GitLab


From 618af5b38b94cd5f59ebec607a4ca18555e6aa0f Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 24 Feb 2013 15:30:48 +0000
Subject: [PATCH 211/223] Fix line endings in Defer02.stderr

---
 tests/ghci/scripts/Defer02.stderr | 370 +++++++++++++++---------------
 1 file changed, 185 insertions(+), 185 deletions(-)

diff --git a/tests/ghci/scripts/Defer02.stderr b/tests/ghci/scripts/Defer02.stderr
index b0937a7bd..966a00f04 100644
--- a/tests/ghci/scripts/Defer02.stderr
+++ b/tests/ghci/scripts/Defer02.stderr
@@ -1,185 +1,185 @@
-
-..\..\typecheck\should_run\Defer01.hs:11:40: Warning:
-    Couldn't match type `Char' with `[Char]'
-    Expected type: String
-      Actual type: Char
-    In the first argument of `putStr', namely ','
-    In the second argument of `(>>)', namely putStr ','
-    In the expression: putStr "Hello World" >> putStr ','
-
-..\..\typecheck\should_run\Defer01.hs:14:5: Warning:
-    Couldn't match expected type `Int' with actual type `Char'
-    In the expression: 'p'
-    In an equation for `a': a = 'p'
-
-..\..\typecheck\should_run\Defer01.hs:18:9: Warning:
-    No instance for (Eq B) arising from a use of `=='
-    In the expression: x == x
-    In an equation for `b': b x = x == x
-
-..\..\typecheck\should_run\Defer01.hs:25:4: Warning:
-    Couldn't match type `Int' with `Bool'
-    Inaccessible code in
-      a pattern with constructor
-        C2 :: Bool -> C Bool,
-      in an equation for `c'
-    In the pattern: C2 x
-    In an equation for `c': c (C2 x) = True
-
-..\..\typecheck\should_run\Defer01.hs:28:5: Warning:
-    No instance for (Num (a -> a)) arising from the literal `1'
-    In the expression: 1
-    In an equation for `d': d = 1
-
-..\..\typecheck\should_run\Defer01.hs:31:5: Warning:
-    Couldn't match expected type `Char -> t' with actual type `Char'
-    Relevant bindings include
-      f :: t (bound at ..\..\typecheck\should_run\Defer01.hs:31:1)
-    The function `e' is applied to one argument,
-    but its type `Char' has none
-    In the expression: e 'q'
-    In an equation for `f': f = e 'q'
-
-..\..\typecheck\should_run\Defer01.hs:34:8: Warning:
-    Couldn't match expected type `Char' with actual type `a'
-      `a' is a rigid type variable bound by
-          the type signature for h :: a -> (Char, Char)
-          at ..\..\typecheck\should_run\Defer01.hs:33:6
-    Relevant bindings include
-      h :: a -> (Char, Char)
-        (bound at ..\..\typecheck\should_run\Defer01.hs:34:1)
-      x :: a (bound at ..\..\typecheck\should_run\Defer01.hs:34:3)
-    In the expression: x
-    In the expression: (x, 'c')
-    In an equation for `h': h x = (x, 'c')
-
-..\..\typecheck\should_run\Defer01.hs:39:17: Warning:
-    Couldn't match expected type `Bool' with actual type `T a'
-    Relevant bindings include
-      i :: a -> () (bound at ..\..\typecheck\should_run\Defer01.hs:39:1)
-      a :: a (bound at ..\..\typecheck\should_run\Defer01.hs:39:3)
-    In the return type of a call of `K'
-    In the first argument of `not', namely `(K a)'
-    In the expression: (not (K a))
-
-..\..\typecheck\should_run\Defer01.hs:43:5: Warning:
-    No instance for (MyClass a1) arising from a use of `myOp'
-    In the expression: myOp 23
-    In an equation for `j': j = myOp 23
-
-..\..\typecheck\should_run\Defer01.hs:43:10: Warning:
-    No instance for (Num a1) arising from the literal `23'
-    The type variable `a1' is ambiguous
-    Note: there are several potential instances:
-      instance Num Double -- Defined in `GHC.Float'
-      instance Num Float -- Defined in `GHC.Float'
-      instance Integral a => Num (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
-      ...plus three others
-    In the first argument of `myOp', namely `23'
-    In the expression: myOp 23
-    In an equation for `j': j = myOp 23
-
-..\..\typecheck\should_run\Defer01.hs:45:6: Warning:
-    Couldn't match type `Int' with `Bool'
-    Inaccessible code in
-      the type signature for k :: Int ~ Bool => Int -> Bool
-    In the ambiguity check for: Int ~ Bool => Int -> Bool
-    In the type signature for `k': k :: Int ~ Bool => Int -> Bool
-
-..\..\typecheck\should_run\Defer01.hs:45:6: Warning:
-    Couldn't match type `Int' with `Bool'
-    Inaccessible code in
-      the type signature for k :: Int ~ Bool => Int -> Bool
-
-..\..\typecheck\should_run\Defer01.hs:46:7: Warning:
-    Couldn't match expected type `Bool' with actual type `Int'
-    In the expression: x
-    In an equation for `k': k x = x
-
-..\..\typecheck\should_run\Defer01.hs:49:5: Warning:
-    Couldn't match expected type `IO a0'
-                with actual type `Char -> IO ()'
-    In the first argument of `(>>)', namely `putChar'
-    In the expression: putChar >> putChar 'p'
-    In an equation for `l': l = putChar >> putChar 'p'
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:11:40:
-    Couldn't match type `Char' with `[Char]'
-    Expected type: String
-      Actual type: Char
-    In the first argument of `putStr', namely ','
-    In the second argument of `(>>)', namely putStr ','
-    In the expression: putStr "Hello World" >> putStr ','
-(deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:14:5:
-    Couldn't match expected type `Int' with actual type `Char'
-    In the expression: 'p'
-    In an equation for `a': a = 'p'
-(deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:18:9:
-    No instance for (Eq B) arising from a use of `=='
-    In the expression: x == x
-    In an equation for `b': b x = x == x
-(deferred type error)
-
-<interactive>:8:11:
-    Couldn't match type `Bool' with `Int'
-    Expected type: C Int
-      Actual type: C Bool
-    In the return type of a call of `C2'
-    In the first argument of `c', namely `(C2 True)'
-    In the first argument of `print', namely `(c (C2 True))'
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:28:5:
-    No instance for (Num (a -> a)) arising from the literal `1'
-    In the expression: 1
-    In an equation for `d': d = 1
-(deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:31:5:
-    Couldn't match expected type `Char -> t' with actual type `Char'
-    Relevant bindings include
-      f :: t (bound at ..\..\typecheck\should_run\Defer01.hs:31:1)
-    The function `e' is applied to one argument,
-    but its type `Char' has none
-    In the expression: e 'q'
-    In an equation for `f': f = e 'q'
-(deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:34:8:
-    Couldn't match expected type `Char' with actual type `a'
-      `a' is a rigid type variable bound by
-          the type signature for h :: a -> (Char, Char)
-          at ..\..\typecheck\should_run\Defer01.hs:33:6
-    Relevant bindings include
-      h :: a -> (Char, Char)
-        (bound at ..\..\typecheck\should_run\Defer01.hs:34:1)
-      x :: a (bound at ..\..\typecheck\should_run\Defer01.hs:34:3)
-    In the expression: x
-    In the expression: (x, 'c')
-    In an equation for `h': h x = (x, 'c')
-(deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:39:17:
-    Couldn't match expected type `Bool' with actual type `T a'
-    Relevant bindings include
-      i :: a -> () (bound at ..\..\typecheck\should_run\Defer01.hs:39:1)
-      a :: a (bound at ..\..\typecheck\should_run\Defer01.hs:39:3)
-    In the return type of a call of `K'
-    In the first argument of `not', namely `(K a)'
-    In the expression: (not (K a))
-(deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:43:5:
-    No instance for (MyClass a1) arising from a use of `myOp'
-    In the expression: myOp 23
-    In an equation for `j': j = myOp 23
-(deferred type error)
-
-<interactive>:14:8:
-    Couldn't match expected type `Bool' with actual type `Int'
-    In the first argument of `print', namely `(k 2)'
-    In the expression: print (k 2)
-    In an equation for `it': it = print (k 2)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:49:5:
-    Couldn't match expected type `IO a0'
-                with actual type `Char -> IO ()'
-    In the first argument of `(>>)', namely `putChar'
-    In the expression: putChar >> putChar 'p'
-    In an equation for `l': l = putChar >> putChar 'p'
-(deferred type error)
+
+..\..\typecheck\should_run\Defer01.hs:11:40: Warning:
+    Couldn't match type `Char' with `[Char]'
+    Expected type: String
+      Actual type: Char
+    In the first argument of `putStr', namely ','
+    In the second argument of `(>>)', namely putStr ','
+    In the expression: putStr "Hello World" >> putStr ','
+
+..\..\typecheck\should_run\Defer01.hs:14:5: Warning:
+    Couldn't match expected type `Int' with actual type `Char'
+    In the expression: 'p'
+    In an equation for `a': a = 'p'
+
+..\..\typecheck\should_run\Defer01.hs:18:9: Warning:
+    No instance for (Eq B) arising from a use of `=='
+    In the expression: x == x
+    In an equation for `b': b x = x == x
+
+..\..\typecheck\should_run\Defer01.hs:25:4: Warning:
+    Couldn't match type `Int' with `Bool'
+    Inaccessible code in
+      a pattern with constructor
+        C2 :: Bool -> C Bool,
+      in an equation for `c'
+    In the pattern: C2 x
+    In an equation for `c': c (C2 x) = True
+
+..\..\typecheck\should_run\Defer01.hs:28:5: Warning:
+    No instance for (Num (a -> a)) arising from the literal `1'
+    In the expression: 1
+    In an equation for `d': d = 1
+
+..\..\typecheck\should_run\Defer01.hs:31:5: Warning:
+    Couldn't match expected type `Char -> t' with actual type `Char'
+    Relevant bindings include
+      f :: t (bound at ..\..\typecheck\should_run\Defer01.hs:31:1)
+    The function `e' is applied to one argument,
+    but its type `Char' has none
+    In the expression: e 'q'
+    In an equation for `f': f = e 'q'
+
+..\..\typecheck\should_run\Defer01.hs:34:8: Warning:
+    Couldn't match expected type `Char' with actual type `a'
+      `a' is a rigid type variable bound by
+          the type signature for h :: a -> (Char, Char)
+          at ..\..\typecheck\should_run\Defer01.hs:33:6
+    Relevant bindings include
+      h :: a -> (Char, Char)
+        (bound at ..\..\typecheck\should_run\Defer01.hs:34:1)
+      x :: a (bound at ..\..\typecheck\should_run\Defer01.hs:34:3)
+    In the expression: x
+    In the expression: (x, 'c')
+    In an equation for `h': h x = (x, 'c')
+
+..\..\typecheck\should_run\Defer01.hs:39:17: Warning:
+    Couldn't match expected type `Bool' with actual type `T a'
+    Relevant bindings include
+      i :: a -> () (bound at ..\..\typecheck\should_run\Defer01.hs:39:1)
+      a :: a (bound at ..\..\typecheck\should_run\Defer01.hs:39:3)
+    In the return type of a call of `K'
+    In the first argument of `not', namely `(K a)'
+    In the expression: (not (K a))
+
+..\..\typecheck\should_run\Defer01.hs:43:5: Warning:
+    No instance for (MyClass a1) arising from a use of `myOp'
+    In the expression: myOp 23
+    In an equation for `j': j = myOp 23
+
+..\..\typecheck\should_run\Defer01.hs:43:10: Warning:
+    No instance for (Num a1) arising from the literal `23'
+    The type variable `a1' is ambiguous
+    Note: there are several potential instances:
+      instance Num Double -- Defined in `GHC.Float'
+      instance Num Float -- Defined in `GHC.Float'
+      instance Integral a => Num (GHC.Real.Ratio a)
+        -- Defined in `GHC.Real'
+      ...plus three others
+    In the first argument of `myOp', namely `23'
+    In the expression: myOp 23
+    In an equation for `j': j = myOp 23
+
+..\..\typecheck\should_run\Defer01.hs:45:6: Warning:
+    Couldn't match type `Int' with `Bool'
+    Inaccessible code in
+      the type signature for k :: Int ~ Bool => Int -> Bool
+    In the ambiguity check for: Int ~ Bool => Int -> Bool
+    In the type signature for `k': k :: Int ~ Bool => Int -> Bool
+
+..\..\typecheck\should_run\Defer01.hs:45:6: Warning:
+    Couldn't match type `Int' with `Bool'
+    Inaccessible code in
+      the type signature for k :: Int ~ Bool => Int -> Bool
+
+..\..\typecheck\should_run\Defer01.hs:46:7: Warning:
+    Couldn't match expected type `Bool' with actual type `Int'
+    In the expression: x
+    In an equation for `k': k x = x
+
+..\..\typecheck\should_run\Defer01.hs:49:5: Warning:
+    Couldn't match expected type `IO a0'
+                with actual type `Char -> IO ()'
+    In the first argument of `(>>)', namely `putChar'
+    In the expression: putChar >> putChar 'p'
+    In an equation for `l': l = putChar >> putChar 'p'
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:11:40:
+    Couldn't match type `Char' with `[Char]'
+    Expected type: String
+      Actual type: Char
+    In the first argument of `putStr', namely ','
+    In the second argument of `(>>)', namely putStr ','
+    In the expression: putStr "Hello World" >> putStr ','
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:14:5:
+    Couldn't match expected type `Int' with actual type `Char'
+    In the expression: 'p'
+    In an equation for `a': a = 'p'
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:18:9:
+    No instance for (Eq B) arising from a use of `=='
+    In the expression: x == x
+    In an equation for `b': b x = x == x
+(deferred type error)
+
+<interactive>:8:11:
+    Couldn't match type `Bool' with `Int'
+    Expected type: C Int
+      Actual type: C Bool
+    In the return type of a call of `C2'
+    In the first argument of `c', namely `(C2 True)'
+    In the first argument of `print', namely `(c (C2 True))'
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:28:5:
+    No instance for (Num (a -> a)) arising from the literal `1'
+    In the expression: 1
+    In an equation for `d': d = 1
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:31:5:
+    Couldn't match expected type `Char -> t' with actual type `Char'
+    Relevant bindings include
+      f :: t (bound at ..\..\typecheck\should_run\Defer01.hs:31:1)
+    The function `e' is applied to one argument,
+    but its type `Char' has none
+    In the expression: e 'q'
+    In an equation for `f': f = e 'q'
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:34:8:
+    Couldn't match expected type `Char' with actual type `a'
+      `a' is a rigid type variable bound by
+          the type signature for h :: a -> (Char, Char)
+          at ..\..\typecheck\should_run\Defer01.hs:33:6
+    Relevant bindings include
+      h :: a -> (Char, Char)
+        (bound at ..\..\typecheck\should_run\Defer01.hs:34:1)
+      x :: a (bound at ..\..\typecheck\should_run\Defer01.hs:34:3)
+    In the expression: x
+    In the expression: (x, 'c')
+    In an equation for `h': h x = (x, 'c')
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:39:17:
+    Couldn't match expected type `Bool' with actual type `T a'
+    Relevant bindings include
+      i :: a -> () (bound at ..\..\typecheck\should_run\Defer01.hs:39:1)
+      a :: a (bound at ..\..\typecheck\should_run\Defer01.hs:39:3)
+    In the return type of a call of `K'
+    In the first argument of `not', namely `(K a)'
+    In the expression: (not (K a))
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:43:5:
+    No instance for (MyClass a1) arising from a use of `myOp'
+    In the expression: myOp 23
+    In an equation for `j': j = myOp 23
+(deferred type error)
+
+<interactive>:14:8:
+    Couldn't match expected type `Bool' with actual type `Int'
+    In the first argument of `print', namely `(k 2)'
+    In the expression: print (k 2)
+    In an equation for `it': it = print (k 2)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:49:5:
+    Couldn't match expected type `IO a0'
+                with actual type `Char -> IO ()'
+    In the first argument of `(>>)', namely `putChar'
+    In the expression: putChar >> putChar 'p'
+    In an equation for `l': l = putChar >> putChar 'p'
+(deferred type error)
-- 
GitLab


From c126524e1c8067e67150abd2bbcc52f252e9db0e Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 24 Feb 2013 15:34:16 +0000
Subject: [PATCH 212/223] Accept Defer02 output following unicode quotes change

---
 tests/ghci/scripts/Defer02.stderr | 214 +++++++++++++++---------------
 1 file changed, 107 insertions(+), 107 deletions(-)

diff --git a/tests/ghci/scripts/Defer02.stderr b/tests/ghci/scripts/Defer02.stderr
index 966a00f04..26cac5774 100644
--- a/tests/ghci/scripts/Defer02.stderr
+++ b/tests/ghci/scripts/Defer02.stderr
@@ -1,185 +1,185 @@
 
-..\..\typecheck\should_run\Defer01.hs:11:40: Warning:
-    Couldn't match type `Char' with `[Char]'
+../../typecheck/should_run/Defer01.hs:11:40: Warning:
+    Couldn't match type ‛Char’ with ‛[Char]’
     Expected type: String
       Actual type: Char
-    In the first argument of `putStr', namely ','
-    In the second argument of `(>>)', namely putStr ','
+    In the first argument of ‛putStr’, namely ‛','’
+    In the second argument of ‛(>>)’, namely ‛putStr ','’
     In the expression: putStr "Hello World" >> putStr ','
 
-..\..\typecheck\should_run\Defer01.hs:14:5: Warning:
-    Couldn't match expected type `Int' with actual type `Char'
+../../typecheck/should_run/Defer01.hs:14:5: Warning:
+    Couldn't match expected type ‛Int’ with actual type ‛Char’
     In the expression: 'p'
-    In an equation for `a': a = 'p'
+    In an equation for ‛a’: a = 'p'
 
-..\..\typecheck\should_run\Defer01.hs:18:9: Warning:
-    No instance for (Eq B) arising from a use of `=='
+../../typecheck/should_run/Defer01.hs:18:9: Warning:
+    No instance for (Eq B) arising from a use of ‛==’
     In the expression: x == x
-    In an equation for `b': b x = x == x
+    In an equation for ‛b’: b x = x == x
 
-..\..\typecheck\should_run\Defer01.hs:25:4: Warning:
-    Couldn't match type `Int' with `Bool'
+../../typecheck/should_run/Defer01.hs:25:4: Warning:
+    Couldn't match type ‛Int’ with ‛Bool’
     Inaccessible code in
       a pattern with constructor
         C2 :: Bool -> C Bool,
-      in an equation for `c'
+      in an equation for ‛c’
     In the pattern: C2 x
-    In an equation for `c': c (C2 x) = True
+    In an equation for ‛c’: c (C2 x) = True
 
-..\..\typecheck\should_run\Defer01.hs:28:5: Warning:
-    No instance for (Num (a -> a)) arising from the literal `1'
+../../typecheck/should_run/Defer01.hs:28:5: Warning:
+    No instance for (Num (a -> a)) arising from the literal ‛1’
     In the expression: 1
-    In an equation for `d': d = 1
+    In an equation for ‛d’: d = 1
 
-..\..\typecheck\should_run\Defer01.hs:31:5: Warning:
-    Couldn't match expected type `Char -> t' with actual type `Char'
+../../typecheck/should_run/Defer01.hs:31:5: Warning:
+    Couldn't match expected type ‛Char -> t’ with actual type ‛Char’
     Relevant bindings include
-      f :: t (bound at ..\..\typecheck\should_run\Defer01.hs:31:1)
-    The function `e' is applied to one argument,
-    but its type `Char' has none
+      f :: t (bound at ../../typecheck/should_run/Defer01.hs:31:1)
+    The function ‛e’ is applied to one argument,
+    but its type ‛Char’ has none
     In the expression: e 'q'
-    In an equation for `f': f = e 'q'
+    In an equation for ‛f’: f = e 'q'
 
-..\..\typecheck\should_run\Defer01.hs:34:8: Warning:
-    Couldn't match expected type `Char' with actual type `a'
-      `a' is a rigid type variable bound by
+../../typecheck/should_run/Defer01.hs:34:8: Warning:
+    Couldn't match expected type ‛Char’ with actual type ‛a’
+      ‛a’ is a rigid type variable bound by
           the type signature for h :: a -> (Char, Char)
-          at ..\..\typecheck\should_run\Defer01.hs:33:6
+          at ../../typecheck/should_run/Defer01.hs:33:6
     Relevant bindings include
       h :: a -> (Char, Char)
-        (bound at ..\..\typecheck\should_run\Defer01.hs:34:1)
-      x :: a (bound at ..\..\typecheck\should_run\Defer01.hs:34:3)
+        (bound at ../../typecheck/should_run/Defer01.hs:34:1)
+      x :: a (bound at ../../typecheck/should_run/Defer01.hs:34:3)
     In the expression: x
     In the expression: (x, 'c')
-    In an equation for `h': h x = (x, 'c')
+    In an equation for ‛h’: h x = (x, 'c')
 
-..\..\typecheck\should_run\Defer01.hs:39:17: Warning:
-    Couldn't match expected type `Bool' with actual type `T a'
+../../typecheck/should_run/Defer01.hs:39:17: Warning:
+    Couldn't match expected type ‛Bool’ with actual type ‛T a’
     Relevant bindings include
-      i :: a -> () (bound at ..\..\typecheck\should_run\Defer01.hs:39:1)
-      a :: a (bound at ..\..\typecheck\should_run\Defer01.hs:39:3)
-    In the return type of a call of `K'
-    In the first argument of `not', namely `(K a)'
+      i :: a -> () (bound at ../../typecheck/should_run/Defer01.hs:39:1)
+      a :: a (bound at ../../typecheck/should_run/Defer01.hs:39:3)
+    In the return type of a call of ‛K’
+    In the first argument of ‛not’, namely ‛(K a)’
     In the expression: (not (K a))
 
-..\..\typecheck\should_run\Defer01.hs:43:5: Warning:
-    No instance for (MyClass a1) arising from a use of `myOp'
+../../typecheck/should_run/Defer01.hs:43:5: Warning:
+    No instance for (MyClass a1) arising from a use of ‛myOp’
     In the expression: myOp 23
-    In an equation for `j': j = myOp 23
+    In an equation for ‛j’: j = myOp 23
 
-..\..\typecheck\should_run\Defer01.hs:43:10: Warning:
-    No instance for (Num a1) arising from the literal `23'
-    The type variable `a1' is ambiguous
+../../typecheck/should_run/Defer01.hs:43:10: Warning:
+    No instance for (Num a1) arising from the literal ‛23’
+    The type variable ‛a1’ is ambiguous
     Note: there are several potential instances:
-      instance Num Double -- Defined in `GHC.Float'
-      instance Num Float -- Defined in `GHC.Float'
+      instance Num Double -- Defined in ‛GHC.Float’
+      instance Num Float -- Defined in ‛GHC.Float’
       instance Integral a => Num (GHC.Real.Ratio a)
-        -- Defined in `GHC.Real'
+        -- Defined in ‛GHC.Real’
       ...plus three others
-    In the first argument of `myOp', namely `23'
+    In the first argument of ‛myOp’, namely ‛23’
     In the expression: myOp 23
-    In an equation for `j': j = myOp 23
+    In an equation for ‛j’: j = myOp 23
 
-..\..\typecheck\should_run\Defer01.hs:45:6: Warning:
-    Couldn't match type `Int' with `Bool'
+../../typecheck/should_run/Defer01.hs:45:6: Warning:
+    Couldn't match type ‛Int’ with ‛Bool’
     Inaccessible code in
       the type signature for k :: Int ~ Bool => Int -> Bool
     In the ambiguity check for: Int ~ Bool => Int -> Bool
-    In the type signature for `k': k :: Int ~ Bool => Int -> Bool
+    In the type signature for ‛k’: k :: Int ~ Bool => Int -> Bool
 
-..\..\typecheck\should_run\Defer01.hs:45:6: Warning:
-    Couldn't match type `Int' with `Bool'
+../../typecheck/should_run/Defer01.hs:45:6: Warning:
+    Couldn't match type ‛Int’ with ‛Bool’
     Inaccessible code in
       the type signature for k :: Int ~ Bool => Int -> Bool
 
-..\..\typecheck\should_run\Defer01.hs:46:7: Warning:
-    Couldn't match expected type `Bool' with actual type `Int'
+../../typecheck/should_run/Defer01.hs:46:7: Warning:
+    Couldn't match expected type ‛Bool’ with actual type ‛Int’
     In the expression: x
-    In an equation for `k': k x = x
+    In an equation for ‛k’: k x = x
 
-..\..\typecheck\should_run\Defer01.hs:49:5: Warning:
-    Couldn't match expected type `IO a0'
-                with actual type `Char -> IO ()'
-    In the first argument of `(>>)', namely `putChar'
+../../typecheck/should_run/Defer01.hs:49:5: Warning:
+    Couldn't match expected type ‛IO a0’
+                with actual type ‛Char -> IO ()’
+    In the first argument of ‛(>>)’, namely ‛putChar’
     In the expression: putChar >> putChar 'p'
-    In an equation for `l': l = putChar >> putChar 'p'
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:11:40:
-    Couldn't match type `Char' with `[Char]'
+    In an equation for ‛l’: l = putChar >> putChar 'p'
+*** Exception: ../../typecheck/should_run/Defer01.hs:11:40:
+    Couldn't match type ‛Char’ with ‛[Char]’
     Expected type: String
       Actual type: Char
-    In the first argument of `putStr', namely ','
-    In the second argument of `(>>)', namely putStr ','
+    In the first argument of ‛putStr’, namely ‛','’
+    In the second argument of ‛(>>)’, namely ‛putStr ','’
     In the expression: putStr "Hello World" >> putStr ','
 (deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:14:5:
-    Couldn't match expected type `Int' with actual type `Char'
+*** Exception: ../../typecheck/should_run/Defer01.hs:14:5:
+    Couldn't match expected type ‛Int’ with actual type ‛Char’
     In the expression: 'p'
-    In an equation for `a': a = 'p'
+    In an equation for ‛a’: a = 'p'
 (deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:18:9:
-    No instance for (Eq B) arising from a use of `=='
+*** Exception: ../../typecheck/should_run/Defer01.hs:18:9:
+    No instance for (Eq B) arising from a use of ‛==’
     In the expression: x == x
-    In an equation for `b': b x = x == x
+    In an equation for ‛b’: b x = x == x
 (deferred type error)
 
 <interactive>:8:11:
-    Couldn't match type `Bool' with `Int'
+    Couldn't match type ‛Bool’ with ‛Int’
     Expected type: C Int
       Actual type: C Bool
-    In the return type of a call of `C2'
-    In the first argument of `c', namely `(C2 True)'
-    In the first argument of `print', namely `(c (C2 True))'
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:28:5:
-    No instance for (Num (a -> a)) arising from the literal `1'
+    In the return type of a call of ‛C2’
+    In the first argument of ‛c’, namely ‛(C2 True)’
+    In the first argument of ‛print’, namely ‛(c (C2 True))’
+*** Exception: ../../typecheck/should_run/Defer01.hs:28:5:
+    No instance for (Num (a -> a)) arising from the literal ‛1’
     In the expression: 1
-    In an equation for `d': d = 1
+    In an equation for ‛d’: d = 1
 (deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:31:5:
-    Couldn't match expected type `Char -> t' with actual type `Char'
+*** Exception: ../../typecheck/should_run/Defer01.hs:31:5:
+    Couldn't match expected type ‛Char -> t’ with actual type ‛Char’
     Relevant bindings include
-      f :: t (bound at ..\..\typecheck\should_run\Defer01.hs:31:1)
-    The function `e' is applied to one argument,
-    but its type `Char' has none
+      f :: t (bound at ../../typecheck/should_run/Defer01.hs:31:1)
+    The function ‛e’ is applied to one argument,
+    but its type ‛Char’ has none
     In the expression: e 'q'
-    In an equation for `f': f = e 'q'
+    In an equation for ‛f’: f = e 'q'
 (deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:34:8:
-    Couldn't match expected type `Char' with actual type `a'
-      `a' is a rigid type variable bound by
+*** Exception: ../../typecheck/should_run/Defer01.hs:34:8:
+    Couldn't match expected type ‛Char’ with actual type ‛a’
+      ‛a’ is a rigid type variable bound by
           the type signature for h :: a -> (Char, Char)
-          at ..\..\typecheck\should_run\Defer01.hs:33:6
+          at ../../typecheck/should_run/Defer01.hs:33:6
     Relevant bindings include
       h :: a -> (Char, Char)
-        (bound at ..\..\typecheck\should_run\Defer01.hs:34:1)
-      x :: a (bound at ..\..\typecheck\should_run\Defer01.hs:34:3)
+        (bound at ../../typecheck/should_run/Defer01.hs:34:1)
+      x :: a (bound at ../../typecheck/should_run/Defer01.hs:34:3)
     In the expression: x
     In the expression: (x, 'c')
-    In an equation for `h': h x = (x, 'c')
+    In an equation for ‛h’: h x = (x, 'c')
 (deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:39:17:
-    Couldn't match expected type `Bool' with actual type `T a'
+*** Exception: ../../typecheck/should_run/Defer01.hs:39:17:
+    Couldn't match expected type ‛Bool’ with actual type ‛T a’
     Relevant bindings include
-      i :: a -> () (bound at ..\..\typecheck\should_run\Defer01.hs:39:1)
-      a :: a (bound at ..\..\typecheck\should_run\Defer01.hs:39:3)
-    In the return type of a call of `K'
-    In the first argument of `not', namely `(K a)'
+      i :: a -> () (bound at ../../typecheck/should_run/Defer01.hs:39:1)
+      a :: a (bound at ../../typecheck/should_run/Defer01.hs:39:3)
+    In the return type of a call of ‛K’
+    In the first argument of ‛not’, namely ‛(K a)’
     In the expression: (not (K a))
 (deferred type error)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:43:5:
-    No instance for (MyClass a1) arising from a use of `myOp'
+*** Exception: ../../typecheck/should_run/Defer01.hs:43:5:
+    No instance for (MyClass a1) arising from a use of ‛myOp’
     In the expression: myOp 23
-    In an equation for `j': j = myOp 23
+    In an equation for ‛j’: j = myOp 23
 (deferred type error)
 
 <interactive>:14:8:
-    Couldn't match expected type `Bool' with actual type `Int'
-    In the first argument of `print', namely `(k 2)'
+    Couldn't match expected type ‛Bool’ with actual type ‛Int’
+    In the first argument of ‛print’, namely ‛(k 2)’
     In the expression: print (k 2)
-    In an equation for `it': it = print (k 2)
-*** Exception: ..\..\typecheck\should_run\Defer01.hs:49:5:
-    Couldn't match expected type `IO a0'
-                with actual type `Char -> IO ()'
-    In the first argument of `(>>)', namely `putChar'
+    In an equation for ‛it’: it = print (k 2)
+*** Exception: ../../typecheck/should_run/Defer01.hs:49:5:
+    Couldn't match expected type ‛IO a0’
+                with actual type ‛Char -> IO ()’
+    In the first argument of ‛(>>)’, namely ‛putChar’
     In the expression: putChar >> putChar 'p'
-    In an equation for `l': l = putChar >> putChar 'p'
+    In an equation for ‛l’: l = putChar >> putChar 'p'
 (deferred type error)
-- 
GitLab


From cedc5c70c3ec8f879b71ac73f873ef650de8165e Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 24 Feb 2013 15:35:24 +0000
Subject: [PATCH 213/223] Accept T3208b output following unicode quotes change

---
 .../should_compile/T3208b.stderr              | 60 +++++++++----------
 1 file changed, 30 insertions(+), 30 deletions(-)

diff --git a/tests/indexed-types/should_compile/T3208b.stderr b/tests/indexed-types/should_compile/T3208b.stderr
index 5eee19a1a..1bf275e85 100644
--- a/tests/indexed-types/should_compile/T3208b.stderr
+++ b/tests/indexed-types/should_compile/T3208b.stderr
@@ -1,30 +1,30 @@
-
-T3208b.hs:15:10:
-    Could not deduce (STerm o0 ~ STerm a)
-    from the context (OTerm a ~ STerm a, OBJECT a, SUBST a)
-      bound by the type signature for
-                 fce' :: (OTerm a ~ STerm a, OBJECT a, SUBST a) => a -> c
-      at T3208b.hs:14:9-56
-    NB: `STerm' is a type function, and may not be injective
-    The type variable `o0' is ambiguous
-    Expected type: STerm o0
-      Actual type: OTerm o0
-    Relevant bindings include
-      fce' :: a -> c (bound at T3208b.hs:15:1)
-      f :: a (bound at T3208b.hs:15:6)
-    In the expression: fce (apply f)
-    In an equation for fce': fce' f = fce (apply f)
-
-T3208b.hs:15:15:
-    Could not deduce (OTerm o0 ~ STerm a)
-    from the context (OTerm a ~ STerm a, OBJECT a, SUBST a)
-      bound by the type signature for
-                 fce' :: (OTerm a ~ STerm a, OBJECT a, SUBST a) => a -> c
-      at T3208b.hs:14:9-56
-    The type variable `o0' is ambiguous
-    Relevant bindings include
-      fce' :: a -> c (bound at T3208b.hs:15:1)
-      f :: a (bound at T3208b.hs:15:6)
-    In the first argument of `fce', namely `(apply f)'
-    In the expression: fce (apply f)
-    In an equation for fce': fce' f = fce (apply f)
+
+T3208b.hs:15:10:
+    Could not deduce (STerm o0 ~ STerm a)
+    from the context (OTerm a ~ STerm a, OBJECT a, SUBST a)
+      bound by the type signature for
+                 fce' :: (OTerm a ~ STerm a, OBJECT a, SUBST a) => a -> c
+      at T3208b.hs:14:9-56
+    NB: ‛STerm’ is a type function, and may not be injective
+    The type variable ‛o0’ is ambiguous
+    Expected type: STerm o0
+      Actual type: OTerm o0
+    Relevant bindings include
+      fce' :: a -> c (bound at T3208b.hs:15:1)
+      f :: a (bound at T3208b.hs:15:6)
+    In the expression: fce (apply f)
+    In an equation for ‛fce'’: fce' f = fce (apply f)
+
+T3208b.hs:15:15:
+    Could not deduce (OTerm o0 ~ STerm a)
+    from the context (OTerm a ~ STerm a, OBJECT a, SUBST a)
+      bound by the type signature for
+                 fce' :: (OTerm a ~ STerm a, OBJECT a, SUBST a) => a -> c
+      at T3208b.hs:14:9-56
+    The type variable ‛o0’ is ambiguous
+    Relevant bindings include
+      fce' :: a -> c (bound at T3208b.hs:15:1)
+      f :: a (bound at T3208b.hs:15:6)
+    In the first argument of ‛fce’, namely ‛(apply f)’
+    In the expression: fce (apply f)
+    In an equation for ‛fce'’: fce' f = fce (apply f)
-- 
GitLab


From 4d8220f2ffe46c5dbfe94774605e26149d40dbf5 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 24 Feb 2013 15:36:45 +0000
Subject: [PATCH 214/223] Accept T3950 output following unicode quotes change

---
 tests/typecheck/should_fail/T3950.stderr | 6 +++---
 1 file changed, 3 insertions(+), 3 deletions(-)

diff --git a/tests/typecheck/should_fail/T3950.stderr b/tests/typecheck/should_fail/T3950.stderr
index 07b1d32f9..b95b4f817 100644
--- a/tests/typecheck/should_fail/T3950.stderr
+++ b/tests/typecheck/should_fail/T3950.stderr
@@ -1,14 +1,14 @@
 
 T3950.hs:15:13:
-    Couldn't match kind `* -> *' with `*'
+    Couldn't match kind ‛* -> *’ with ‛*’
     When matching types
       w :: (* -> * -> *) -> *
       Sealed :: (* -> *) -> *
     Expected type: w (Id p)
       Actual type: Sealed (Id p0 x0)
-    In the first argument of `Just', namely rp'
+    In the first argument of ‛Just’, namely ‛rp'’
     In the expression: Just rp'
-    In an equation for `rp':
+    In an equation for ‛rp’:
         rp _
           = Just rp'
           where
-- 
GitLab


From 6aa6dea102cd00d51c796272eec76dc5d7b2b226 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 24 Feb 2013 15:38:56 +0000
Subject: [PATCH 215/223] Update T3103.stderr following unicode quote change

---
 tests/rename/should_compile/T3103/T3103.stderr | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/rename/should_compile/T3103/T3103.stderr b/tests/rename/should_compile/T3103/T3103.stderr
index a36e4484b..ed041023e 100644
--- a/tests/rename/should_compile/T3103/T3103.stderr
+++ b/tests/rename/should_compile/T3103/T3103.stderr
@@ -1,3 +1,3 @@
 
 GHC/Word.hs:10:23:
-    Warning: {-# SOURCE #-} unnecessary in import of  `GHC.Unicode'
+    Warning: {-# SOURCE #-} unnecessary in import of  ‛GHC.Unicode’
-- 
GitLab


From 968912411dbaa18d60235bb7039ae6c47cdd2845 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 24 Feb 2013 15:54:20 +0000
Subject: [PATCH 216/223] Add a test for #2507; we should get `' quotes if
 unicode quotes don't work

---
 tests/driver/Makefile     | 4 ++++
 tests/driver/T2507.hs     | 5 +++++
 tests/driver/T2507.stderr | 5 +++++
 tests/driver/all.T        | 1 +
 4 files changed, 15 insertions(+)
 create mode 100644 tests/driver/T2507.hs
 create mode 100644 tests/driver/T2507.stderr

diff --git a/tests/driver/Makefile b/tests/driver/Makefile
index e4120023e..2a06257cf 100644
--- a/tests/driver/Makefile
+++ b/tests/driver/Makefile
@@ -540,3 +540,7 @@ T7563:
 T6037:
 	-LC_ALL=C "$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) -c T6037.hs
 
+.PHONY: T2507
+T2507:
+	-LC_ALL=C "$(TEST_HC)" $(TEST_HC_OPTS_NO_RECOMP) -c T2507.hs
+
diff --git a/tests/driver/T2507.hs b/tests/driver/T2507.hs
new file mode 100644
index 000000000..8f6c0c007
--- /dev/null
+++ b/tests/driver/T2507.hs
@@ -0,0 +1,5 @@
+
+module T2507 where
+
+foo :: Int
+foo = ()
diff --git a/tests/driver/T2507.stderr b/tests/driver/T2507.stderr
new file mode 100644
index 000000000..925a8709d
--- /dev/null
+++ b/tests/driver/T2507.stderr
@@ -0,0 +1,5 @@
+
+T2507.hs:5:7:
+    Couldn't match expected type `Int' with actual type `()'
+    In the expression: ()
+    In an equation for `foo': foo = ()
diff --git a/tests/driver/all.T b/tests/driver/all.T
index 4c81ba5cb..609e8ea39 100644
--- a/tests/driver/all.T
+++ b/tests/driver/all.T
@@ -366,4 +366,5 @@ test('T7563', when(unregisterised(), skip), run_command,
      ['$MAKE -s --no-print-directory T7563'])
 test('T6037', expect_broken(6037), run_command,
      ['$MAKE -s --no-print-directory T6037'])
+test('T2507', normal, run_command, ['$MAKE -s --no-print-directory T2507'])
 
-- 
GitLab


From 0054168f1f56e2adb69376627c1f4a76f5fda0a1 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 24 Feb 2013 15:55:00 +0000
Subject: [PATCH 217/223] Fix T6037.stderr; it uses LC_ALL=C, so won't actually
 get unicode quotes

---
 tests/driver/T6037.stderr | 4 ++--
 1 file changed, 2 insertions(+), 2 deletions(-)

diff --git a/tests/driver/T6037.stderr b/tests/driver/T6037.stderr
index 7b7d07ecb..3059288d1 100644
--- a/tests/driver/T6037.stderr
+++ b/tests/driver/T6037.stderr
@@ -1,5 +1,5 @@
 
 T6037.hs:5:7:
-    Couldn't match expected type ‛Int’ with actual type ‛()’
+    Couldn't match expected type `Int' with actual type `()'
     In the expression: ()
-    In an equation for ‛f?o’: f?o = ()
+    In an equation for `f?o': f?o = ()
-- 
GitLab


From d92f4c76f6ba5a817786f91bc663c656b101def4 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Mon, 25 Feb 2013 21:39:59 +0000
Subject: [PATCH 218/223] Add a couple of tests for #7627

---
 tests/ghci/scripts/T7627.script  | 16 ++++++++++++++++
 tests/ghci/scripts/T7627.stdout  | 25 +++++++++++++++++++++++++
 tests/ghci/scripts/T7627b.script |  8 ++++++++
 tests/ghci/scripts/T7627b.stderr | 12 ++++++++++++
 tests/ghci/scripts/all.T         |  2 ++
 5 files changed, 63 insertions(+)
 create mode 100644 tests/ghci/scripts/T7627.script
 create mode 100644 tests/ghci/scripts/T7627.stdout
 create mode 100644 tests/ghci/scripts/T7627b.script
 create mode 100644 tests/ghci/scripts/T7627b.stderr

diff --git a/tests/ghci/scripts/T7627.script b/tests/ghci/scripts/T7627.script
new file mode 100644
index 000000000..13f52a538
--- /dev/null
+++ b/tests/ghci/scripts/T7627.script
@@ -0,0 +1,16 @@
+
+:set -XUnboxedTuples
+
+:i ()
+:i (##)
+:t ()
+:t (##)
+:t (   )
+:t (#   #)
+:i (,)
+:i (#,#)
+:t (,)
+:t (#,#)
+:t (  ,  )
+:t (#  ,  #)
+
diff --git a/tests/ghci/scripts/T7627.stdout b/tests/ghci/scripts/T7627.stdout
new file mode 100644
index 000000000..a23781a9d
--- /dev/null
+++ b/tests/ghci/scripts/T7627.stdout
@@ -0,0 +1,25 @@
+data () = () 	-- Defined in ‛GHC.Tuple’
+instance Bounded () -- Defined in ‛GHC.Enum’
+instance Enum () -- Defined in ‛GHC.Enum’
+instance Eq () -- Defined in ‛GHC.Classes’
+instance Ord () -- Defined in ‛GHC.Classes’
+instance Read () -- Defined in ‛GHC.Read’
+instance Show () -- Defined in ‛GHC.Show’
+data (##) = (##) 	-- Defined in ‛GHC.Prim’
+() :: ()
+(##) :: (# #)
+(   ) :: ()
+(#   #) :: (# #)
+data (,) a b = (,) a b 	-- Defined in ‛GHC.Tuple’
+instance (Bounded a, Bounded b) => Bounded (a, b)
+  -- Defined in ‛GHC.Enum’
+instance (Eq a, Eq b) => Eq (a, b) -- Defined in ‛GHC.Classes’
+instance Functor ((,) a) -- Defined in ‛GHC.Base’
+instance (Ord a, Ord b) => Ord (a, b) -- Defined in ‛GHC.Classes’
+instance (Read a, Read b) => Read (a, b) -- Defined in ‛GHC.Read’
+instance (Show a, Show b) => Show (a, b) -- Defined in ‛GHC.Show’
+data (#,#) a b = (#,#) a b 	-- Defined in ‛GHC.Prim’
+(,) :: a -> b -> (a, b)
+(#,#) :: a -> b -> (# a, b #)
+(  ,  ) :: a -> b -> (a, b)
+(#  ,  #) :: a -> b -> (# a, b #)
diff --git a/tests/ghci/scripts/T7627b.script b/tests/ghci/scripts/T7627b.script
new file mode 100644
index 000000000..9c0a404fc
--- /dev/null
+++ b/tests/ghci/scripts/T7627b.script
@@ -0,0 +1,8 @@
+
+:set -XUnboxedTuples
+
+:i (   )
+:i (#   #)
+:i (  ,  )
+:i (#  ,  #)
+
diff --git a/tests/ghci/scripts/T7627b.stderr b/tests/ghci/scripts/T7627b.stderr
new file mode 100644
index 000000000..87997e798
--- /dev/null
+++ b/tests/ghci/scripts/T7627b.stderr
@@ -0,0 +1,12 @@
+
+<interactive>:1:2:
+    parse error (possibly incorrect indentation or mismatched brackets)
+
+<interactive>:1:3:
+    parse error (possibly incorrect indentation or mismatched brackets)
+
+<interactive>:1:2:
+    parse error (possibly incorrect indentation or mismatched brackets)
+
+<interactive>:1:3:
+    parse error (possibly incorrect indentation or mismatched brackets)
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index e02a9783c..7af3bf997 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -142,4 +142,6 @@ test('ghci058',
      ['ghci058.script'])
 test('T7587', normal, ghci_script, ['T7587.script'])
 test('T7688', normal, ghci_script, ['T7688.script'])
+test('T7627', normal, ghci_script, ['T7627.script'])
+test('T7627b', normal, ghci_script, ['T7627b.script'])
 
-- 
GitLab


From f5e474d38e1bd4c6f4e2859cc36d7f2f0df101a7 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Tue, 26 Feb 2013 01:26:26 +0000
Subject: [PATCH 219/223] T7671 / #7671 is now fixed

---
 tests/parser/unicode/all.T | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/parser/unicode/all.T b/tests/parser/unicode/all.T
index 71db26ff5..a8e19ebec 100644
--- a/tests/parser/unicode/all.T
+++ b/tests/parser/unicode/all.T
@@ -20,4 +20,4 @@ test('T1744', normal, compile_and_run, [''])
 test('T1103', normal, compile, [''])
 test('T2302', only_ways(['normal']), compile_fail, [''])
 test('T4373', normal, compile, [''])
-test('T7671', expect_broken(7671), compile, [''])
+test('T7671', normal, compile, [''])
-- 
GitLab


From 7e0824966d6bc5485e2264abd99d1cf20f75eaf0 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Fri, 1 Mar 2013 15:18:22 +0000
Subject: [PATCH 220/223] Remove redundant SafeHaskell tests

---
 tests/safeHaskell/unsafeLibs/Dep01.hs     | 13 -------------
 tests/safeHaskell/unsafeLibs/Dep01.stderr |  4 ----
 tests/safeHaskell/unsafeLibs/Dep02.hs     | 16 ----------------
 tests/safeHaskell/unsafeLibs/Dep02.stderr |  4 ----
 tests/safeHaskell/unsafeLibs/all.T        |  2 --
 5 files changed, 39 deletions(-)
 delete mode 100644 tests/safeHaskell/unsafeLibs/Dep01.hs
 delete mode 100644 tests/safeHaskell/unsafeLibs/Dep01.stderr
 delete mode 100644 tests/safeHaskell/unsafeLibs/Dep02.hs
 delete mode 100644 tests/safeHaskell/unsafeLibs/Dep02.stderr

diff --git a/tests/safeHaskell/unsafeLibs/Dep01.hs b/tests/safeHaskell/unsafeLibs/Dep01.hs
deleted file mode 100644
index 5ee1cd028..000000000
--- a/tests/safeHaskell/unsafeLibs/Dep01.hs
+++ /dev/null
@@ -1,13 +0,0 @@
-module Dep01 where
-
-import Control.Monad
-import Control.Monad.ST
-import Data.STRef
-
-sumST :: Num a => [a] -> IO a
-sumST xs = unsafeSTToIO $ do
-    n <- newSTRef 0
-    forM_ xs $ \x -> do
-        modifySTRef n (+x)
-    readSTRef n
-
diff --git a/tests/safeHaskell/unsafeLibs/Dep01.stderr b/tests/safeHaskell/unsafeLibs/Dep01.stderr
deleted file mode 100644
index 656408bc4..000000000
--- a/tests/safeHaskell/unsafeLibs/Dep01.stderr
+++ /dev/null
@@ -1,4 +0,0 @@
-
-Dep01.hs:8:12: Warning:
-    In the use of ‛unsafeSTToIO’ (imported from Control.Monad.ST):
-    Deprecated: "Please import from Control.Monad.ST.Unsafe instead; This will be removed in the next release"
diff --git a/tests/safeHaskell/unsafeLibs/Dep02.hs b/tests/safeHaskell/unsafeLibs/Dep02.hs
deleted file mode 100644
index f9dbb2606..000000000
--- a/tests/safeHaskell/unsafeLibs/Dep02.hs
+++ /dev/null
@@ -1,16 +0,0 @@
-module Dep02 where
-
-import Control.Monad
-import Control.Monad.ST.Lazy
-import Data.STRef.Lazy
-
-sumST :: Num a => [a] -> a
-sumST xs = runST $ do
-    n <- newSTRef 0
-    forM_ xs $ \x -> do
-        modifySTRef n (+x)
-    readSTRef n
-
-badST :: ()
-badST = runST $ unsafeIOToST $ putStrLn "Hello World"
-
diff --git a/tests/safeHaskell/unsafeLibs/Dep02.stderr b/tests/safeHaskell/unsafeLibs/Dep02.stderr
deleted file mode 100644
index 4ea40a834..000000000
--- a/tests/safeHaskell/unsafeLibs/Dep02.stderr
+++ /dev/null
@@ -1,4 +0,0 @@
-
-Dep02.hs:15:17: Warning:
-    In the use of ‛unsafeIOToST’ (imported from Control.Monad.ST.Lazy):
-    Deprecated: "Please import from Control.Monad.ST.Lazy.Unsafe instead; This will be removed in the next release"
diff --git a/tests/safeHaskell/unsafeLibs/all.T b/tests/safeHaskell/unsafeLibs/all.T
index 81fd18a08..605f7de3c 100644
--- a/tests/safeHaskell/unsafeLibs/all.T
+++ b/tests/safeHaskell/unsafeLibs/all.T
@@ -10,8 +10,6 @@ def f( name, opts ):
 setTestOpts(f)
 
 # Check correct methods are deprecated
-test('Dep01', normal, compile, [''])
-test('Dep02', normal, compile, [''])
 test('Dep05', normal, compile_fail, [''])
 test('Dep06', normal, compile_fail, [''])
 test('Dep07', normal, compile_fail, [''])
-- 
GitLab


From 516107ea087e281eef8efb1ee3db40fbeac5e137 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones <simonpj@microsoft.com>
Date: Fri, 1 Mar 2013 18:04:35 +0000
Subject: [PATCH 221/223] Test Trac #7729

---
 tests/indexed-types/should_fail/T7729.hs      | 28 +++++++++++++++++++
 tests/indexed-types/should_fail/T7729.stderr  | 17 +++++++++++
 tests/indexed-types/should_fail/T7729a.hs     | 28 +++++++++++++++++++
 tests/indexed-types/should_fail/T7729a.stderr |  8 ++++++
 tests/indexed-types/should_fail/all.T         |  4 ++-
 5 files changed, 84 insertions(+), 1 deletion(-)
 create mode 100644 tests/indexed-types/should_fail/T7729.hs
 create mode 100644 tests/indexed-types/should_fail/T7729.stderr
 create mode 100644 tests/indexed-types/should_fail/T7729a.hs
 create mode 100644 tests/indexed-types/should_fail/T7729a.stderr

diff --git a/tests/indexed-types/should_fail/T7729.hs b/tests/indexed-types/should_fail/T7729.hs
new file mode 100644
index 000000000..c542cf055
--- /dev/null
+++ b/tests/indexed-types/should_fail/T7729.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE FlexibleContexts, TypeFamilies #-}
+module T7729 where
+
+class Monad m => PrimMonad m where
+  type PrimState m
+
+class MonadTrans t where
+  lift :: Monad m => m a -> t m a
+
+class (PrimMonad (BasePrimMonad m), Monad m) => MonadPrim m where
+  type BasePrimMonad m :: * -> *
+  liftPrim :: BasePrimMonad m a -> m a
+
+
+newtype Rand m a = Rand {
+  runRand :: Maybe (m ()) -> m a
+  }
+
+instance (Monad m) => Monad (Rand m) where
+  return           = Rand . const . return
+  (Rand rnd) >>= f = Rand $ \g -> (\x -> runRand (f x) g) =<< rnd g
+
+instance MonadTrans Rand where
+  lift = Rand . const
+
+instance MonadPrim m => MonadPrim (Rand m) where
+  type BasePrimMonad (Rand m) = BasePrimMonad m
+  liftPrim = liftPrim . lift
\ No newline at end of file
diff --git a/tests/indexed-types/should_fail/T7729.stderr b/tests/indexed-types/should_fail/T7729.stderr
new file mode 100644
index 000000000..4b12b29d9
--- /dev/null
+++ b/tests/indexed-types/should_fail/T7729.stderr
@@ -0,0 +1,17 @@
+
+T7729.hs:28:14:
+    Could not deduce (BasePrimMonad (Rand m)
+                      ~ t0 (BasePrimMonad (Rand m)))
+    from the context (PrimMonad (BasePrimMonad (Rand m)),
+                      Monad (Rand m),
+                      MonadPrim m)
+      bound by the instance declaration at T7729.hs:26:10-42
+    The type variable ‛t0’ is ambiguous
+    Expected type: t0 (BasePrimMonad (Rand m)) a -> Rand m a
+      Actual type: BasePrimMonad (Rand m) a -> Rand m a
+    Relevant bindings include
+      liftPrim :: BasePrimMonad (Rand m) a -> Rand m a
+        (bound at T7729.hs:28:3)
+    In the first argument of ‛(.)’, namely ‛liftPrim’
+    In the expression: liftPrim . lift
+    In an equation for ‛liftPrim’: liftPrim = liftPrim . lift
diff --git a/tests/indexed-types/should_fail/T7729a.hs b/tests/indexed-types/should_fail/T7729a.hs
new file mode 100644
index 000000000..53c163992
--- /dev/null
+++ b/tests/indexed-types/should_fail/T7729a.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE FlexibleContexts, TypeFamilies #-}
+module T7729a where
+
+class Monad m => PrimMonad m where
+  type PrimState m
+
+class MonadTrans t where
+  lift :: Monad m => m a -> t m a
+
+class (PrimMonad (BasePrimMonad m), Monad m) => MonadPrim m where
+  type BasePrimMonad m :: * -> *
+  liftPrim :: BasePrimMonad m a -> m a
+
+
+newtype Rand m a = Rand {
+  runRand :: Maybe (m ()) -> m a
+  }
+
+instance (Monad m) => Monad (Rand m) where
+  return           = Rand . const . return
+  (Rand rnd) >>= f = Rand $ \g -> (\x -> runRand (f x) g) =<< rnd g
+
+instance MonadTrans Rand where
+  lift = Rand . const
+
+instance MonadPrim m => MonadPrim (Rand m) where
+  type BasePrimMonad (Rand m) = BasePrimMonad m
+  liftPrim x = liftPrim (lift x)   -- This line changed from T7729
\ No newline at end of file
diff --git a/tests/indexed-types/should_fail/T7729a.stderr b/tests/indexed-types/should_fail/T7729a.stderr
new file mode 100644
index 000000000..54eeea02f
--- /dev/null
+++ b/tests/indexed-types/should_fail/T7729a.stderr
@@ -0,0 +1,8 @@
+
+T7729a.hs:28:31:
+    Occurs check: cannot construct the infinite type: m0 ~ t0 m0
+    Expected type: m0 a
+      Actual type: BasePrimMonad (Rand m) a
+    In the first argument of ‛lift’, namely ‛x’
+    In the first argument of ‛liftPrim’, namely ‛(lift x)’
+    In the expression: liftPrim (lift x)
diff --git a/tests/indexed-types/should_fail/all.T b/tests/indexed-types/should_fail/all.T
index 0196f543e..2b608f21a 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -94,4 +94,6 @@ test('T7354a',
      ['$MAKE -s --no-print-directory T7354a'])
 test('T7536', normal, compile_fail, [''])
 
-test('T7560', normal, compile_fail, [''])
\ No newline at end of file
+test('T7560', normal, compile_fail, [''])
+test('T7729', normal, compile_fail, [''])
+test('T7729a', normal, compile_fail, [''])
-- 
GitLab


From 4adbade9437f48500d2ff2a0a38089e4f329d704 Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 3 Mar 2013 16:05:43 +0000
Subject: [PATCH 222/223] Add a test for #7734

---
 tests/typecheck/should_fail/T7734.hs     |  5 +++++
 tests/typecheck/should_fail/T7734.stderr | 18 ++++++++++++++++++
 tests/typecheck/should_fail/all.T        |  1 +
 3 files changed, 24 insertions(+)
 create mode 100644 tests/typecheck/should_fail/T7734.hs
 create mode 100644 tests/typecheck/should_fail/T7734.stderr

diff --git a/tests/typecheck/should_fail/T7734.hs b/tests/typecheck/should_fail/T7734.hs
new file mode 100644
index 000000000..85f83f528
--- /dev/null
+++ b/tests/typecheck/should_fail/T7734.hs
@@ -0,0 +1,5 @@
+
+module T7734 where
+
+x `f` y = x x
+(&) x y = x x
diff --git a/tests/typecheck/should_fail/T7734.stderr b/tests/typecheck/should_fail/T7734.stderr
new file mode 100644
index 000000000..d90d136a1
--- /dev/null
+++ b/tests/typecheck/should_fail/T7734.stderr
@@ -0,0 +1,18 @@
+
+T7734.hs:4:13:
+    Occurs check: cannot construct the infinite type: t2 ~ t2 -> t1
+    Relevant bindings include
+      f :: (t2 -> t1) -> t -> t1 (bound at T7734.hs:4:1)
+      x :: t2 -> t1 (bound at T7734.hs:4:1)
+    In the first argument of ‛x’, namely ‛x’
+    In the expression: x x
+    In an equation for ‛f’: x `f` y = x x
+
+T7734.hs:5:13:
+    Occurs check: cannot construct the infinite type: t2 ~ t2 -> t1
+    Relevant bindings include
+      & :: (t2 -> t1) -> t -> t1 (bound at T7734.hs:5:1)
+      x :: t2 -> t1 (bound at T7734.hs:5:5)
+    In the first argument of ‛x’, namely ‛x’
+    In the expression: x x
+    In an equation for ‛&’: (&) x y = x x
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index 0750c57a8..dfa0668be 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -297,3 +297,4 @@ test('T2247', normal, compile_fail, [''])
 test('T7609', normal, compile_fail, [''])
 test('T7645', normal, compile_fail, [''])
 test('T2354', normal, compile_fail, ['-O'])
+test('T7734', normal, compile_fail, [''])
-- 
GitLab


From a6adff8ed9fefdec73bf347a5666d7d380ec660a Mon Sep 17 00:00:00 2001
From: Ian Lynagh <ian@well-typed.com>
Date: Sun, 3 Mar 2013 16:31:52 +0000
Subject: [PATCH 223/223] Update drvfail011.stderr following #7734 fix; patch
 from monoidal

---
 tests/deriving/should_fail/drvfail011.stderr | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

diff --git a/tests/deriving/should_fail/drvfail011.stderr b/tests/deriving/should_fail/drvfail011.stderr
index 6ec1df7a0..f4b27e9d2 100644
--- a/tests/deriving/should_fail/drvfail011.stderr
+++ b/tests/deriving/should_fail/drvfail011.stderr
@@ -3,7 +3,7 @@ drvfail011.hs:8:1:
     No instance for (Eq a) arising from a use of ‛==’
     Possible fix: add (Eq a) to the context of the instance declaration
     In the expression: ((a1 == b1))
-    In an equation for ‛==’: == (T1 a1) (T1 b1) = ((a1 == b1))
+    In an equation for ‛==’: (==) (T1 a1) (T1 b1) = ((a1 == b1))
     When typechecking the code for  ‛==’
       in a standalone derived instance for ‛Eq (T a)’:
       To see the code I am typechecking, use -ddump-deriv
-- 
GitLab