summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--testsuite/tests/driver/T7060.hs8
-rw-r--r--testsuite/tests/gadt/T3638.hs1
-rw-r--r--testsuite/tests/indexed-types/should_compile/Rules1.hs1
-rw-r--r--testsuite/tests/indexed-types/should_compile/T2291.hs4
-rw-r--r--testsuite/tests/safeHaskell/safeInfered/UnsafeInfered05_A.hs1
-rw-r--r--testsuite/tests/safeHaskell/safeInfered/UnsafeInfered11_A.hs2
-rw-r--r--testsuite/tests/simplCore/should_compile/simpl011.hs1
-rw-r--r--testsuite/tests/typecheck/should_compile/T2494-2.hs1
-rw-r--r--testsuite/tests/typecheck/should_compile/T2497.hs5
-rw-r--r--testsuite/tests/typecheck/should_compile/T2497.stderr2
-rw-r--r--testsuite/tests/typecheck/should_compile/tc111.hs1
11 files changed, 21 insertions, 6 deletions
diff --git a/testsuite/tests/driver/T7060.hs b/testsuite/tests/driver/T7060.hs
index 45dac515e4..885a9bc1c7 100644
--- a/testsuite/tests/driver/T7060.hs
+++ b/testsuite/tests/driver/T7060.hs
@@ -1,4 +1,8 @@
main :: IO ()
-main = print (3 + 4 :: Int)
+main = print (f (3 + 4 :: Int))
-{-# RULES "rule" forall xs . map id xs = xs #-}
+f :: Int -> Int
+f x = x
+{-# NOINLINE [1] f #-}
+
+{-# RULES "rule" forall x. f x = 8 #-}
diff --git a/testsuite/tests/gadt/T3638.hs b/testsuite/tests/gadt/T3638.hs
index abb6a86169..c299fa9637 100644
--- a/testsuite/tests/gadt/T3638.hs
+++ b/testsuite/tests/gadt/T3638.hs
@@ -5,6 +5,7 @@ module T3638 where
data T a where TInt :: T Int
foo :: T Int -> Int
+{-# NOINLINE [1] foo #-}
foo TInt = 0
{-# RULES "foo" forall x. foo x = case x of { TInt -> 0 } #-}
diff --git a/testsuite/tests/indexed-types/should_compile/Rules1.hs b/testsuite/tests/indexed-types/should_compile/Rules1.hs
index 497c5bbeb9..b936349475 100644
--- a/testsuite/tests/indexed-types/should_compile/Rules1.hs
+++ b/testsuite/tests/indexed-types/should_compile/Rules1.hs
@@ -12,6 +12,7 @@ mapT :: (C a, C b) => (a -> b) -> T a -> T b
mapT = undefined
zipT :: (C a, C b) => T a -> T b -> T (a,b)
+{-# NOINLINE [1] zipT #-}
zipT = undefined
{-# RULES
diff --git a/testsuite/tests/indexed-types/should_compile/T2291.hs b/testsuite/tests/indexed-types/should_compile/T2291.hs
index a6832b60ad..e9aa8777d0 100644
--- a/testsuite/tests/indexed-types/should_compile/T2291.hs
+++ b/testsuite/tests/indexed-types/should_compile/T2291.hs
@@ -10,6 +10,6 @@ class CoCCC k where
{-# RULES
"cocurry coapply" cocurry coapply = id
-"cocurry . uncocurry" cocurry . uncocurry = id
-"uncocurry . cocurry" uncocurry . cocurry = id
+"cocurry . uncocurry" forall x. cocurry (uncocurry x) = x
+"uncocurry . cocurry" forall x. uncocurry (cocurry x) = x
#-}
diff --git a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered05_A.hs b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered05_A.hs
index 4d147716f5..e0cabff549 100644
--- a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered05_A.hs
+++ b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered05_A.hs
@@ -5,6 +5,7 @@
module UnsafeInfered05_A where
{-# RULES "f" f = undefined #-}
+{-# NOINLINE [1] f #-}
f :: Int
f = 1
diff --git a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered11_A.hs b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered11_A.hs
index 9d1d2ecf31..d209dcf5fe 100644
--- a/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered11_A.hs
+++ b/testsuite/tests/safeHaskell/safeInfered/UnsafeInfered11_A.hs
@@ -15,6 +15,8 @@ lookupx ((t,a):xs) t' | t == t' = Just a
| otherwise = lookupx xs t'
{-# RULES "lookupx/T" lookupx = tLookup #-}
+{-# NOINLINE [1] lookupx #-}
+
tLookup :: [(T,a)] -> T -> Maybe a
tLookup [] _ = Nothing
tLookup ((t,a):xs) t' | t /= t' = Just a
diff --git a/testsuite/tests/simplCore/should_compile/simpl011.hs b/testsuite/tests/simplCore/should_compile/simpl011.hs
index c660394e92..63d1ad9a22 100644
--- a/testsuite/tests/simplCore/should_compile/simpl011.hs
+++ b/testsuite/tests/simplCore/should_compile/simpl011.hs
@@ -49,6 +49,7 @@ updateST= update'
update :: (MutHash arr ref m)
=> HashTable key val arr ref m -> key -> val -> m Bool
+{-# NOINLINE [1] update #-}
update = update'
update' :: (MutHash arr ref m)
diff --git a/testsuite/tests/typecheck/should_compile/T2494-2.hs b/testsuite/tests/typecheck/should_compile/T2494-2.hs
index 7e3bfc146b..b672cb0a47 100644
--- a/testsuite/tests/typecheck/should_compile/T2494-2.hs
+++ b/testsuite/tests/typecheck/should_compile/T2494-2.hs
@@ -5,6 +5,7 @@
module Foo where
foo :: (forall m. Monad m => Maybe (m a) -> Maybe (m a)) -> Maybe a -> Maybe a
+{-# NOINLINE [1] foo #-}
foo _ x = x
{-# RULES
diff --git a/testsuite/tests/typecheck/should_compile/T2497.hs b/testsuite/tests/typecheck/should_compile/T2497.hs
index 0e6ab4e9f7..24933e086f 100644
--- a/testsuite/tests/typecheck/should_compile/T2497.hs
+++ b/testsuite/tests/typecheck/should_compile/T2497.hs
@@ -2,9 +2,12 @@
module ShouldCompile() where
+foo x = x
+{-# NOINLINE [1] foo #-}
+
-- Trac #2497; test should compile without language
-- pragmas to swith on the forall
-{-# RULES "id" forall (x :: a). id x = x #-}
+{-# RULES "id" forall (x :: a). foo x = x #-}
diff --git a/testsuite/tests/typecheck/should_compile/T2497.stderr b/testsuite/tests/typecheck/should_compile/T2497.stderr
index 81b8fbcbb1..de6ca484b5 100644
--- a/testsuite/tests/typecheck/should_compile/T2497.stderr
+++ b/testsuite/tests/typecheck/should_compile/T2497.stderr
@@ -1,2 +1,2 @@
-T2497.hs:15:1: Warning: Defined but not used: `beq'
+T2497.hs:18:1: Warning: Defined but not used: `beq'
diff --git a/testsuite/tests/typecheck/should_compile/tc111.hs b/testsuite/tests/typecheck/should_compile/tc111.hs
index 26eb942970..f1636bfebf 100644
--- a/testsuite/tests/typecheck/should_compile/tc111.hs
+++ b/testsuite/tests/typecheck/should_compile/tc111.hs
@@ -7,6 +7,7 @@ module ShouldCompile where
-- The reason was that foobar is monomorphic, so the RULE
-- should not generalise over it.
+{-# NOINLINE [1] foo #-}
foo 1 = 2
bar 0 = 1