From af259b521574b734a7a0b1b3e9e6868df33ebdb9 Mon Sep 17 00:00:00 2001 From: foo Date: Sat, 21 Sep 2013 23:47:47 +0000 Subject: [PATCH] hack to build with new ghc --- Data/Vector.hs | 1 - Data/Vector/Fusion/Stream/Monadic.hs | 1 - Data/Vector/Generic.hs | 10 ++-------- Data/Vector/Primitive.hs | 1 - Data/Vector/Storable.hs | 1 - Data/Vector/Unboxed/Base.hs | 15 +-------------- 6 files changed, 3 insertions(+), 26 deletions(-) diff --git a/Data/Vector.hs b/Data/Vector.hs index 138b2db..92c4387 100644 --- a/Data/Vector.hs +++ b/Data/Vector.hs @@ -215,7 +215,6 @@ instance Data a => Data (Vector a) where toConstr _ = error "toConstr" gunfold _ _ = error "gunfold" dataTypeOf _ = G.mkType "Data.Vector.Vector" - dataCast1 = G.dataCast type instance G.Mutable Vector = MVector diff --git a/Data/Vector/Fusion/Stream/Monadic.hs b/Data/Vector/Fusion/Stream/Monadic.hs index 51fec75..b089b3d 100644 --- a/Data/Vector/Fusion/Stream/Monadic.hs +++ b/Data/Vector/Fusion/Stream/Monadic.hs @@ -101,7 +101,6 @@ import GHC.Exts ( SpecConstrAnnotation(..) ) data SPEC = SPEC | SPEC2 #if __GLASGOW_HASKELL__ >= 700 -{-# ANN type SPEC ForceSpecConstr #-} #endif emptyStream :: String diff --git a/Data/Vector/Generic.hs b/Data/Vector/Generic.hs index 78f7260..f4ea80a 100644 --- a/Data/Vector/Generic.hs +++ b/Data/Vector/Generic.hs @@ -157,7 +157,7 @@ module Data.Vector.Generic ( showsPrec, readPrec, -- ** @Data@ and @Typeable@ - gfoldl, dataCast, mkType + gfoldl, mkType ) where import Data.Vector.Generic.Base @@ -194,7 +194,7 @@ import Prelude hiding ( length, null, showsPrec ) import qualified Text.Read as Read -import Data.Typeable ( Typeable1, gcast1 ) +import Data.Typeable ( gcast1 ) #include "vector.h" @@ -2019,9 +2019,3 @@ gfoldl f z v = z fromList `f` toList v mkType :: String -> DataType {-# INLINE mkType #-} mkType = mkNoRepType - -dataCast :: (Vector v a, Data a, Typeable1 v, Typeable1 t) - => (forall d. Data d => c (t d)) -> Maybe (c (v a)) -{-# INLINE dataCast #-} -dataCast f = gcast1 f - diff --git a/Data/Vector/Primitive.hs b/Data/Vector/Primitive.hs index 5f59bae..06e84c3 100644 --- a/Data/Vector/Primitive.hs +++ b/Data/Vector/Primitive.hs @@ -188,7 +188,6 @@ instance (Data a, Prim a) => Data (Vector a) where toConstr _ = error "toConstr" gunfold _ _ = error "gunfold" dataTypeOf _ = G.mkType "Data.Vector.Primitive.Vector" - dataCast1 = G.dataCast type instance G.Mutable Vector = MVector diff --git a/Data/Vector/Storable.hs b/Data/Vector/Storable.hs index f9928e4..a17e3d6 100644 --- a/Data/Vector/Storable.hs +++ b/Data/Vector/Storable.hs @@ -194,7 +194,6 @@ instance (Data a, Storable a) => Data (Vector a) where toConstr _ = error "toConstr" gunfold _ _ = error "gunfold" dataTypeOf _ = G.mkType "Data.Vector.Storable.Vector" - dataCast1 = G.dataCast type instance G.Mutable Vector = MVector diff --git a/Data/Vector/Unboxed/Base.hs b/Data/Vector/Unboxed/Base.hs index 00350cb..c13ea20 100644 --- a/Data/Vector/Unboxed/Base.hs +++ b/Data/Vector/Unboxed/Base.hs @@ -31,7 +31,7 @@ import Data.Word ( Word, Word8, Word16, Word32, Word64 ) import Data.Int ( Int8, Int16, Int32, Int64 ) import Data.Complex -import Data.Typeable ( Typeable1(..), Typeable2(..), mkTyConApp, +import Data.Typeable ( mkTyConApp, #if MIN_VERSION_base(4,4,0) mkTyCon3 #else @@ -65,19 +65,6 @@ vectorTyCon = mkTyCon3 "vector" vectorTyCon m s = mkTyCon $ m ++ "." ++ s #endif -instance Typeable1 Vector where - typeOf1 _ = mkTyConApp (vectorTyCon "Data.Vector.Unboxed" "Vector") [] - -instance Typeable2 MVector where - typeOf2 _ = mkTyConApp (vectorTyCon "Data.Vector.Unboxed.Mutable" "MVector") [] - -instance (Data a, Unbox a) => Data (Vector a) where - gfoldl = G.gfoldl - toConstr _ = error "toConstr" - gunfold _ _ = error "gunfold" - dataTypeOf _ = G.mkType "Data.Vector.Unboxed.Vector" - dataCast1 = G.dataCast - -- ---- -- Unit -- ---- -- 1.7.10.4