[commit: packages/vector] ghc-head: Implement poly-kinded Typeable (0afe74d)

git at git.haskell.org git at git.haskell.org
Thu Sep 26 11:54:47 CEST 2013


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

On branch  : ghc-head
Link       : http://git.haskell.org/packages/vector.git/commitdiff/0afe74de73806d647c39341e47ebdaed04868b70

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

commit 0afe74de73806d647c39341e47ebdaed04868b70
Author: Jose Pedro Magalhaes <jpm at cs.ox.ac.uk>
Date:   Thu Feb 7 14:00:33 2013 +0000

    Implement poly-kinded Typeable
    
    This patch makes the Data.Typeable.Typeable class work with arguments of any
    kind. In particular, this removes the Typeable1..7 class hierarchy, greatly
    simplyfing the whole Typeable story. Also added is the AutoDeriveTypeable
    language extension, which will automatically derive Typeable for all types and
    classes declared in that module. Since there is now no good reason to give
    handwritten instances of the Typeable class, those are ignored (for backwards
    compatibility), and a warning is emitted.
    
    The old, kind-* Typeable class is now called OldTypeable, and lives in the
    Data.OldTypeable module. It is deprecated, and should be removed in some future
    version of GHC.


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

0afe74de73806d647c39341e47ebdaed04868b70
 Data/Vector/Generic.hs      |    9 +++++++++
 Data/Vector/Unboxed/Base.hs |   14 +++++++++++++-
 2 files changed, 22 insertions(+), 1 deletion(-)

diff --git a/Data/Vector/Generic.hs b/Data/Vector/Generic.hs
index 78f7260..0d3a88e 100644
--- a/Data/Vector/Generic.hs
+++ b/Data/Vector/Generic.hs
@@ -194,7 +194,12 @@ import Prelude hiding ( length, null,
                         showsPrec )
 
 import qualified Text.Read as Read
+
+#if __GLASGOW_HASKELL__ >= 707
+import Data.Typeable ( Typeable, gcast1 )
+#else
 import Data.Typeable ( Typeable1, gcast1 )
+#endif
 
 #include "vector.h"
 
@@ -2020,7 +2025,11 @@ mkType :: String -> DataType
 {-# INLINE mkType #-}
 mkType = mkNoRepType
 
+#if __GLASGOW_HASKELL__ >= 707
+dataCast :: (Vector v a, Data a, Typeable v, Typeable t)
+#else
 dataCast :: (Vector v a, Data a, Typeable1 v, Typeable1 t)
+#endif
          => (forall d. Data  d => c (t d)) -> Maybe  (c (v a))
 {-# INLINE dataCast #-}
 dataCast f = gcast1 f
diff --git a/Data/Vector/Unboxed/Base.hs b/Data/Vector/Unboxed/Base.hs
index 00350cb..3fcc4f0 100644
--- a/Data/Vector/Unboxed/Base.hs
+++ b/Data/Vector/Unboxed/Base.hs
@@ -1,4 +1,7 @@
 {-# LANGUAGE MultiParamTypeClasses, TypeFamilies, FlexibleContexts #-}
+#if __GLASGOW_HASKELL__ >= 707
+{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
+#endif
 {-# OPTIONS_HADDOCK hide #-}
 
 -- |
@@ -31,6 +34,9 @@ import Data.Word ( Word, Word8, Word16, Word32, Word64 )
 import Data.Int  ( Int8, Int16, Int32, Int64 )
 import Data.Complex
 
+#if __GLASGOW_HASKELL__ >= 707
+import Data.Typeable ( Typeable )
+#else
 import Data.Typeable ( Typeable1(..), Typeable2(..), mkTyConApp,
 #if MIN_VERSION_base(4,4,0)
                        mkTyCon3
@@ -38,6 +44,8 @@ import Data.Typeable ( Typeable1(..), Typeable2(..), mkTyConApp,
                        mkTyCon
 #endif
                      )
+#endif
+
 import Data.Data     ( Data(..) )
 
 #include "vector.h"
@@ -58,7 +66,10 @@ instance NFData (MVector s a)
 -- -----------------
 -- Data and Typeable
 -- -----------------
-
+#if __GLASGOW_HASKELL__ >= 707
+deriving instance Typeable Vector
+deriving instance Typeable MVector
+#else
 #if MIN_VERSION_base(4,4,0)
 vectorTyCon = mkTyCon3 "vector"
 #else
@@ -70,6 +81,7 @@ instance Typeable1 Vector where
 
 instance Typeable2 MVector where
   typeOf2 _ = mkTyConApp (vectorTyCon "Data.Vector.Unboxed.Mutable" "MVector") []
+#endif
 
 instance (Data a, Unbox a) => Data (Vector a) where
   gfoldl       = G.gfoldl




More information about the ghc-commits mailing list