[commit: packages/binary] master: Don't use * as Type in the presence of TypeOperators (d0912c8)

git at git.haskell.org git at git.haskell.org
Thu Jun 14 21:28:40 UTC 2018


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

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

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

commit d0912c8dda8b17c75e6020a970f93d27200d118c
Author: Vladislav Zavialov <vlad.z.4096 at gmail.com>
Date:   Tue May 29 12:19:31 2018 +0300

    Don't use * as Type in the presence of TypeOperators


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

d0912c8dda8b17c75e6020a970f93d27200d118c
 src/Data/Binary/Generic.hs | 13 ++++++++++++-
 1 file changed, 12 insertions(+), 1 deletion(-)

diff --git a/src/Data/Binary/Generic.hs b/src/Data/Binary/Generic.hs
index 7282ff6..feb85d7 100644
--- a/src/Data/Binary/Generic.hs
+++ b/src/Data/Binary/Generic.hs
@@ -3,6 +3,10 @@
 {-# LANGUAGE Safe #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 
+#if __GLASGOW_HASKELL__ >= 800
+#define HAS_DATA_KIND
+#endif
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      : Data.Binary.Generic
@@ -27,6 +31,9 @@ import Data.Binary.Put
 import Data.Bits
 import Data.Word
 import Data.Monoid ((<>))
+#ifdef HAS_DATA_KIND
+import Data.Kind
+#endif
 import GHC.Generics
 import Prelude -- Silence AMP warning.
 
@@ -136,7 +143,11 @@ instance GBinaryPut a => GSumPut (C1 c a) where
 class SumSize f where
     sumSize :: Tagged f Word64
 
-newtype Tagged (s :: * -> *) b = Tagged {unTagged :: b}
+#ifdef HAS_DATA_KIND
+newtype Tagged (s :: Type -> Type) b = Tagged {unTagged :: b}
+#else
+newtype Tagged (s :: * -> *)       b = Tagged {unTagged :: b}
+#endif
 
 instance (SumSize a, SumSize b) => SumSize (a :+: b) where
     sumSize = Tagged $ unTagged (sumSize :: Tagged a Word64) +



More information about the ghc-commits mailing list