[commit: ghc] master: Data.Complex: Derive Generic (3541f73)
git at git.haskell.org
git at git.haskell.org
Fri Apr 3 05:49:55 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/3541f736486d08df36863fd8e29deb1ca637a498/ghc
>---------------------------------------------------------------
commit 3541f736486d08df36863fd8e29deb1ca637a498
Author: Ben Gamari <ben at smart-cactus.org>
Date: Fri Apr 3 00:48:51 2015 -0500
Data.Complex: Derive Generic
Reviewed By: hvr, austin
Differential Revision: https://phabricator.haskell.org/D770
>---------------------------------------------------------------
3541f736486d08df36863fd8e29deb1ca637a498
libraries/base/Data/Complex.hs | 4 +++-
libraries/base/changelog.md | 1 +
testsuite/tests/generics/T5884.hs | 5 ++---
testsuite/tests/generics/T5884Other.hs | 3 +++
testsuite/tests/generics/all.T | 3 ++-
5 files changed, 11 insertions(+), 5 deletions(-)
diff --git a/libraries/base/Data/Complex.hs b/libraries/base/Data/Complex.hs
index 88aa597..c6420cd 100644
--- a/libraries/base/Data/Complex.hs
+++ b/libraries/base/Data/Complex.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE DeriveGeneric #-}
-----------------------------------------------------------------------------
-- |
@@ -34,6 +35,7 @@ module Data.Complex
) where
+import GHC.Generics (Generic)
import Data.Data (Data)
import Foreign (Storable, castPtr, peek, poke, pokeElemOff, peekElemOff, sizeOf,
alignment)
@@ -51,7 +53,7 @@ infix 6 :+
data Complex a
= !a :+ !a -- ^ forms a complex number from its real and imaginary
-- rectangular components.
- deriving (Eq, Show, Read, Data)
+ deriving (Eq, Show, Read, Data, Generic)
-- -----------------------------------------------------------------------------
-- Functions over Complex
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index f402189..ea509af 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -29,6 +29,7 @@
* New `GHC.Stack.CallStack` data type
+ * `Complex` now has a `Generic` instance
## 4.8.0.0 *Mar 2015*
diff --git a/testsuite/tests/generics/T5884.hs b/testsuite/tests/generics/T5884.hs
index 6dfad25..92b5087 100644
--- a/testsuite/tests/generics/T5884.hs
+++ b/testsuite/tests/generics/T5884.hs
@@ -3,7 +3,6 @@
module T5884 where
import GHC.Generics
+import T5884Other
-import Data.Complex
-
-deriving instance Generic (Complex v)
+deriving instance Generic (Pair a)
diff --git a/testsuite/tests/generics/T5884Other.hs b/testsuite/tests/generics/T5884Other.hs
new file mode 100644
index 0000000..2cf8250
--- /dev/null
+++ b/testsuite/tests/generics/T5884Other.hs
@@ -0,0 +1,3 @@
+module T5884Other where
+
+data Pair a = Pair a a
diff --git a/testsuite/tests/generics/all.T b/testsuite/tests/generics/all.T
index c51de18..98116ec 100644
--- a/testsuite/tests/generics/all.T
+++ b/testsuite/tests/generics/all.T
@@ -26,7 +26,8 @@ test('T5462Yes2', extra_clean(['T5462Yes2/GFunctor.hi'])
test('T5462No1', extra_clean(['T5462No1/GFunctor.hi'])
, multimod_compile_fail, ['T5462No1', '-iGFunctor -outputdir=T5462No1'])
-test('T5884', normal, compile, [''])
+test('T5884', extra_clean(['T5884Other.o', 'T5884Other.hi'])
+ , multimod_compile, ['T5884Other', '-v0'])
test('GenNewtype', normal, compile_and_run, [''])
test('GenDerivOutput1_0', normal, compile, ['-dsuppress-uniques'])
More information about the ghc-commits
mailing list