diff --git a/.travis.yml b/.travis.yml
index 30c8b1ec55b642beb0082b66f19706f58a131a24..4bfd798680f3d155e51d9b526527a351fdf94a87 100644
--- a/.travis.yml
+++ b/.travis.yml
@@ -155,8 +155,6 @@ install:
     echo "packages: ." >> cabal.project
     echo "packages: testsuite" >> cabal.project
   - |
-    echo "package testsuite" >> cabal.project
-    echo "  tests: true"     >> cabal.project
   - "for pkg in $($HCPKG list --simple-output); do echo $pkg | sed 's/-[^-]*$//' | (grep -vE -- '^(random|stm|testsuite)$' || true) | sed 's/^/constraints: /' | sed 's/$/ installed/' >> cabal.project.local; done"
   - cat cabal.project || true
   - cat cabal.project.local || true
@@ -185,8 +183,6 @@ script:
     echo "packages: ${PKGDIR_stm}" >> cabal.project
     echo "packages: ${PKGDIR_testsuite}" >> cabal.project
   - |
-    echo "package testsuite" >> cabal.project
-    echo "  tests: true"     >> cabal.project
   - "for pkg in $($HCPKG list --simple-output); do echo $pkg | sed 's/-[^-]*$//' | (grep -vE -- '^(random|stm|testsuite)$' || true) | sed 's/^/constraints: /' | sed 's/$/ installed/' >> cabal.project.local; done"
   - cat cabal.project || true
   - cat cabal.project.local || true
diff --git a/cabal.haskell-ci b/cabal.haskell-ci
index ea583ae3a128c66a7a4c177835ae208451d9d941..812858eacf7a2eef58fdce032a85c6a64d82a8be 100644
--- a/cabal.haskell-ci
+++ b/cabal.haskell-ci
@@ -1,3 +1,2 @@
-copy-fields: all
 tests:       <7.2.1 || >=7.2.2
 installed:   +all -random
diff --git a/testsuite/src/Stm065.hs b/testsuite/src/Stm065.hs
index 77371b8b9158ba4a6021145413801c9df889c0d1..5ae06f6336d79698f731064e7279c00e84dab173 100644
--- a/testsuite/src/Stm065.hs
+++ b/testsuite/src/Stm065.hs
@@ -1,9 +1,20 @@
+{-# LANGUAGE CPP #-}
+
+{- NB: This one fails for GHC 7.6.1 in particular due to GHC#7493.
+
+This was fixed in GHC via
+ a006ecdfd381fa75ab16ddb66c3a2b247f359eb8
+-}
+
 module Stm065 (main) where
 
 import           Control.Concurrent.STM
 import           Control.Monad          (unless)
 
 main :: IO ()
+#if defined(GHC_7_6_1)
+main = putStrLn "Warning: test disabled for GHC 7.6.1"
+#else
 main = do
   x <- atomically $ do
          r <- newTVar []
@@ -13,3 +24,4 @@ main = do
 
   unless (null x) $ do
     fail (show x)
+#endif
diff --git a/testsuite/testsuite.cabal b/testsuite/testsuite.cabal
index ca3e4ad880598f04b80ad21b40d20fcfd8e5c47c..8f8fcac6314f002626c18077b51cf392d7e24a6b 100644
--- a/testsuite/testsuite.cabal
+++ b/testsuite/testsuite.cabal
@@ -47,5 +47,12 @@ test-suite stm
     , array ^>= 0.3.0.2 || ^>= 0.4.0.0 || ^>= 0.5.0.0
     , random ^>= 1.1
 
+  -- The __GLASGOW_HASKELL_PATCHLEVEL1__ macro wasn't available until GHC 7.10.1,
+  -- so we must use the .cabal file to detect if we're compiling with GHC 7.6.1
+  -- in particular. See the comments in Stm065 for more information about why we
+  -- must single out this version of GHC.
+  if impl(ghc==7.6.1)
+    cpp-options: "-DGHC_7_6_1"
+
   ghc-options: -Wall -fno-warn-unused-imports
   ghc-options: -threaded