Skip to content
Snippets Groups Projects
Commit d0912c8d authored by Vladislav Zavialov's avatar Vladislav Zavialov
Browse files

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

parent b660e3d2
No related branches found
Tags ghc-7.10.2-rc2
No related merge requests found
...@@ -3,6 +3,10 @@ ...@@ -3,6 +3,10 @@
{-# LANGUAGE Safe #-} {-# LANGUAGE Safe #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
#if __GLASGOW_HASKELL__ >= 800
#define HAS_DATA_KIND
#endif
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : Data.Binary.Generic -- Module : Data.Binary.Generic
...@@ -27,6 +31,9 @@ import Data.Binary.Put ...@@ -27,6 +31,9 @@ import Data.Binary.Put
import Data.Bits import Data.Bits
import Data.Word import Data.Word
import Data.Monoid ((<>)) import Data.Monoid ((<>))
#ifdef HAS_DATA_KIND
import Data.Kind
#endif
import GHC.Generics import GHC.Generics
import Prelude -- Silence AMP warning. import Prelude -- Silence AMP warning.
...@@ -136,7 +143,11 @@ instance GBinaryPut a => GSumPut (C1 c a) where ...@@ -136,7 +143,11 @@ instance GBinaryPut a => GSumPut (C1 c a) where
class SumSize f where class SumSize f where
sumSize :: Tagged f Word64 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 instance (SumSize a, SumSize b) => SumSize (a :+: b) where
sumSize = Tagged $ unTagged (sumSize :: Tagged a Word64) + sumSize = Tagged $ unTagged (sumSize :: Tagged a Word64) +
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment