[commit: testsuite] master: Adapt test to avoid Typeable instance error (7c11d93)
git at git.haskell.org
git at git.haskell.org
Wed Sep 4 17:29:42 CEST 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/7c11d93441d5fd6251417f01d3ca897d64471973/testsuite
>---------------------------------------------------------------
commit 7c11d93441d5fd6251417f01d3ca897d64471973
Author: Jose Pedro Magalhaes <jpm at cs.uu.nl>
Date: Wed Sep 4 10:04:29 2013 +0200
Adapt test to avoid Typeable instance error
>---------------------------------------------------------------
7c11d93441d5fd6251417f01d3ca897d64471973
tests/annotations/should_fail/annfail06.hs | 5 +++--
tests/annotations/should_fail/annfail06.stderr | 2 +-
2 files changed, 4 insertions(+), 3 deletions(-)
diff --git a/tests/annotations/should_fail/annfail06.hs b/tests/annotations/should_fail/annfail06.hs
index 671f0c7..ce1c46f 100644
--- a/tests/annotations/should_fail/annfail06.hs
+++ b/tests/annotations/should_fail/annfail06.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE StandaloneDeriving #-}
+
module Annfail06 where
-- Testing that we don't accept Typeable or Data instances defined in the same module
@@ -6,8 +8,7 @@ import Annfail06_Help
import Data.Data
import Data.Typeable
-instance Typeable InstancesInWrongModule where
- typeRep _ = undefined
+deriving instance Typeable InstancesInWrongModule
instance Data InstancesInWrongModule where
gfoldl = undefined
diff --git a/tests/annotations/should_fail/annfail06.stderr b/tests/annotations/should_fail/annfail06.stderr
index aec329d..332f35d 100644
--- a/tests/annotations/should_fail/annfail06.stderr
+++ b/tests/annotations/should_fail/annfail06.stderr
@@ -1,5 +1,5 @@
-annfail06.hs:21:1:
+annfail06.hs:22:1:
GHC stage restriction:
instance for ‛Data
InstancesInWrongModule’ is used in a top-level splice or annotation,
More information about the ghc-commits
mailing list