[commit: packages/binary] master: Add Binary instance for Complex a (5158968)

git at git.haskell.org git at git.haskell.org
Mon Apr 4 11:05:25 UTC 2016


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

On branch  : master
Link       : http://git.haskell.org/packages/binary.git/commitdiff/5158968fb3579e55bf7356a6e8a2d617e5c10b41

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

commit 5158968fb3579e55bf7356a6e8a2d617e5c10b41
Author: Sidharth Kapur <sidharthkapur1 at gmail.com>
Date:   Tue Mar 15 10:53:52 2016 -0500

    Add Binary instance for Complex a


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

5158968fb3579e55bf7356a6e8a2d617e5c10b41
 src/Data/Binary/Class.hs | 7 +++++++
 1 file changed, 7 insertions(+)

diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs
index 2e8c239..bfb49ed 100644
--- a/src/Data/Binary/Class.hs
+++ b/src/Data/Binary/Class.hs
@@ -53,6 +53,7 @@ module Data.Binary.Class (
 import Data.Word
 import Data.Bits
 import Data.Int
+import Data.Complex (Complex(..))
 #ifdef HAS_VOID
 import Data.Void
 #endif
@@ -410,6 +411,12 @@ instance (Binary a,Integral a) => Binary (R.Ratio a) where
     put r = put (R.numerator r) >> put (R.denominator r)
     get = liftM2 (R.%) get get
 
+instance Binary a => Binary (Complex a) where
+    {-# INLINE put #-}
+    put (r :+ i) = put (r, i)
+    {-# INLINE get #-}
+    get = (\(r,i) -> r :+ i) <$> get
+
 ------------------------------------------------------------------------
 
 -- Char is serialised as UTF-8



More information about the ghc-commits mailing list