Skip to content
Snippets Groups Projects
Commit 0afe74de authored by jpm@cs.ox.ac.uk's avatar jpm@cs.ox.ac.uk Committed by bos
Browse files

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.
parent 1bc792e0
No related branches found
No related tags found
No related merge requests found
......@@ -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
......
{-# 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
......
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