[commit: ghc] master: Fix validation issue due to Coercible move (#8894) (7511d5b)

git at git.haskell.org git at git.haskell.org
Mon Mar 17 13:43:47 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/7511d5bf708f38bbdf5733f42dc8a025c76cc684/ghc

>---------------------------------------------------------------

commit 7511d5bf708f38bbdf5733f42dc8a025c76cc684
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Mon Mar 17 14:43:31 2014 +0100

    Fix validation issue due to Coercible move (#8894)


>---------------------------------------------------------------

7511d5bf708f38bbdf5733f42dc8a025c76cc684
 testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs  |    2 +-
 testsuite/tests/typecheck/should_fail/TcCoercibleFail2.hs |    2 +-
 testsuite/tests/typecheck/should_fail/TcCoercibleFail3.hs |    2 +-
 testsuite/tests/typecheck/should_run/TcCoercible.hs       |    2 +-
 4 files changed, 4 insertions(+), 4 deletions(-)

diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs
index 1ad76d4..0431eee 100644
--- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs
+++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE RoleAnnotations, RankNTypes, ScopedTypeVariables #-}
 
-import GHC.Prim (coerce, Coercible)
+import Data.Coerce (coerce, Coercible)
 import Data.Ord (Down)
 
 newtype Age = Age Int deriving Show
diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail2.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFail2.hs
index 13a3234..8d89b52 100644
--- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail2.hs
+++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail2.hs
@@ -1,4 +1,4 @@
-import GHC.Prim (Coercible)
+import Data.Coerce (Coercible)
 
 instance Coercible () ()
 
diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail3.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFail3.hs
index 4caf1c2..eb9b725 100644
--- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail3.hs
+++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail3.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE RoleAnnotations, RankNTypes, ScopedTypeVariables #-}
 
-import GHC.Prim (coerce, Coercible)
+import Data.Coerce (coerce, Coercible)
 
 newtype List a = List [a]
 data T f = T (f Int)
diff --git a/testsuite/tests/typecheck/should_run/TcCoercible.hs b/testsuite/tests/typecheck/should_run/TcCoercible.hs
index e3b29af..7bb8e48 100644
--- a/testsuite/tests/typecheck/should_run/TcCoercible.hs
+++ b/testsuite/tests/typecheck/should_run/TcCoercible.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE RoleAnnotations, StandaloneDeriving, FlexibleContexts, UndecidableInstances, GADTs, TypeFamilies #-}
 
-import GHC.Prim (Coercible, coerce)
+import Data.Coerce (Coercible, coerce)
 import Data.Monoid (mempty, First(First), Last())
 
 newtype Age = Age Int deriving Show



More information about the ghc-commits mailing list