[commit: vector] simd: Added NFData instances for all vectors (993b4b2)

Geoffrey Mainland gmainlan at ghc.haskell.org
Fri Jul 19 14:23:33 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : simd

http://hackage.haskell.org/trac/ghc/changeset/993b4b28e6737b3f616fe380fa62aa74c0e369d7

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

commit 993b4b28e6737b3f616fe380fa62aa74c0e369d7
Author: Bas van Dijk <v.dijk.bas at gmail.com>
Date:   Sat Jan 7 16:09:49 2012 +0000

    Added NFData instances for all vectors

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

 Data/Vector.hs                   |   14 +++++++++++++-
 Data/Vector/Mutable.hs           |    9 +++++++++
 Data/Vector/Primitive.hs         |    4 ++++
 Data/Vector/Primitive/Mutable.hs |    4 ++++
 Data/Vector/Storable.hs          |    4 ++++
 Data/Vector/Storable/Mutable.hs  |    4 ++++
 Data/Vector/Unboxed/Base.hs      |    5 +++++
 vector.cabal                     |    2 +-
 8 files changed, 44 insertions(+), 2 deletions(-)

diff --git a/Data/Vector.hs b/Data/Vector.hs
index 3b38d69..138b2db 100644
--- a/Data/Vector.hs
+++ b/Data/Vector.hs
@@ -1,4 +1,9 @@
-{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeFamilies, Rank2Types #-}
+{-# LANGUAGE FlexibleInstances
+           , MultiParamTypeClasses
+           , TypeFamilies
+           , Rank2Types
+           , BangPatterns
+  #-}
 
 -- |
 -- Module      : Data.Vector
@@ -156,6 +161,7 @@ import           Data.Vector.Mutable  ( MVector(..) )
 import           Data.Primitive.Array
 import qualified Data.Vector.Fusion.Stream as Stream
 
+import Control.DeepSeq ( NFData, rnf )
 import Control.Monad ( MonadPlus(..), liftM, ap )
 import Control.Monad.ST ( ST )
 import Control.Monad.Primitive
@@ -191,6 +197,12 @@ data Vector a = Vector {-# UNPACK #-} !Int
                        {-# UNPACK #-} !(Array a)
         deriving ( Typeable )
 
+instance NFData a => NFData (Vector a) where
+    rnf (Vector i n arr) = force i
+        where
+          force !ix | ix < n    = rnf (indexArray arr ix) `seq` force (ix+1)
+                    | otherwise = ()
+
 instance Show a => Show (Vector a) where
   showsPrec = G.showsPrec
 
diff --git a/Data/Vector/Mutable.hs b/Data/Vector/Mutable.hs
index cc35edb..6168bea 100644
--- a/Data/Vector/Mutable.hs
+++ b/Data/Vector/Mutable.hs
@@ -54,6 +54,8 @@ import qualified Data.Vector.Generic.Mutable as G
 import           Data.Primitive.Array
 import           Control.Monad.Primitive
 
+import Control.DeepSeq ( NFData, rnf )
+
 import Prelude hiding ( length, null, replicate, reverse, map, read,
                         take, drop, splitAt, init, tail )
 
@@ -70,6 +72,13 @@ data MVector s a = MVector {-# UNPACK #-} !Int
 type IOVector = MVector RealWorld
 type STVector s = MVector s
 
+instance NFData a => NFData (MVector s a) where
+    rnf (MVector i n arr) = unsafeInlineST $ force i
+        where
+          force !ix | ix < n    = do x <- readArray arr ix
+                                     rnf x `seq` force (ix+1)
+                    | otherwise = return ()
+
 instance G.MVector MVector a where
   {-# INLINE basicLength #-}
   basicLength (MVector _ n _) = n
diff --git a/Data/Vector/Primitive.hs b/Data/Vector/Primitive.hs
index f6eb42b..5f59bae 100644
--- a/Data/Vector/Primitive.hs
+++ b/Data/Vector/Primitive.hs
@@ -140,6 +140,8 @@ import qualified Data.Vector.Fusion.Stream as Stream
 import           Data.Primitive.ByteArray
 import           Data.Primitive ( Prim, sizeOf )
 
+import Control.DeepSeq ( NFData )
+
 import Control.Monad ( liftM )
 import Control.Monad.ST ( ST )
 import Control.Monad.Primitive
@@ -172,6 +174,8 @@ data Vector a = Vector {-# UNPACK #-} !Int
                        {-# UNPACK #-} !ByteArray
   deriving ( Typeable )
 
+instance NFData (Vector a)
+
 instance (Show a, Prim a) => Show (Vector a) where
   showsPrec = G.showsPrec
 
diff --git a/Data/Vector/Primitive/Mutable.hs b/Data/Vector/Primitive/Mutable.hs
index d496e7e..2028ea5 100644
--- a/Data/Vector/Primitive/Mutable.hs
+++ b/Data/Vector/Primitive/Mutable.hs
@@ -55,6 +55,8 @@ import           Data.Primitive ( Prim, sizeOf )
 import           Control.Monad.Primitive
 import           Control.Monad ( liftM )
 
+import Control.DeepSeq ( NFData )
+
 import Prelude hiding ( length, null, replicate, reverse, map, read,
                         take, drop, splitAt, init, tail )
 
@@ -71,6 +73,8 @@ data MVector s a = MVector {-# UNPACK #-} !Int
 type IOVector = MVector RealWorld
 type STVector s = MVector s
 
+instance NFData (MVector s a)
+
 instance Prim a => G.MVector MVector a where
   basicLength (MVector _ n _) = n
   basicUnsafeSlice j m (MVector i n arr)
diff --git a/Data/Vector/Storable.hs b/Data/Vector/Storable.hs
index 5f88580..f9928e4 100644
--- a/Data/Vector/Storable.hs
+++ b/Data/Vector/Storable.hs
@@ -146,6 +146,8 @@ import Foreign.ForeignPtr
 import Foreign.Ptr
 import Foreign.Marshal.Array ( advancePtr, copyArray )
 
+import Control.DeepSeq ( NFData )
+
 import Control.Monad.ST ( ST )
 import Control.Monad.Primitive
 
@@ -178,6 +180,8 @@ data Vector a = Vector {-# UNPACK #-} !Int
                        {-# UNPACK #-} !(ForeignPtr a)
         deriving ( Typeable )
 
+instance NFData (Vector a)
+
 instance (Show a, Storable a) => Show (Vector a) where
   showsPrec = G.showsPrec
 
diff --git a/Data/Vector/Storable/Mutable.hs b/Data/Vector/Storable/Mutable.hs
index 2334b92..b61bc57 100644
--- a/Data/Vector/Storable/Mutable.hs
+++ b/Data/Vector/Storable/Mutable.hs
@@ -57,6 +57,8 @@ module Data.Vector.Storable.Mutable(
   unsafeWith
 ) where
 
+import Control.DeepSeq ( NFData )
+
 import qualified Data.Vector.Generic.Mutable as G
 import Data.Vector.Storable.Internal
 
@@ -93,6 +95,8 @@ data MVector s a = MVector {-# UNPACK #-} !Int
 type IOVector = MVector RealWorld
 type STVector s = MVector s
 
+instance NFData (MVector s a)
+
 instance Storable a => G.MVector MVector a where
   {-# INLINE basicLength #-}
   basicLength (MVector n _) = n
diff --git a/Data/Vector/Unboxed/Base.hs b/Data/Vector/Unboxed/Base.hs
index 2d9822e..00350cb 100644
--- a/Data/Vector/Unboxed/Base.hs
+++ b/Data/Vector/Unboxed/Base.hs
@@ -22,6 +22,8 @@ import qualified Data.Vector.Generic.Mutable as M
 
 import qualified Data.Vector.Primitive as P
 
+import Control.DeepSeq ( NFData )
+
 import Control.Monad.Primitive
 import Control.Monad ( liftM )
 
@@ -50,6 +52,9 @@ type instance G.Mutable Vector = MVector
 
 class (G.Vector Vector a, M.MVector MVector a) => Unbox a
 
+instance NFData (Vector a)
+instance NFData (MVector s a)
+
 -- -----------------
 -- Data and Typeable
 -- -----------------
diff --git a/vector.cabal b/vector.cabal
index 629682f..939e4a4 100644
--- a/vector.cabal
+++ b/vector.cabal
@@ -171,7 +171,7 @@ Library
   Install-Includes:
         vector.h
 
-  Build-Depends: base >= 4 && < 5, primitive >= 0.4.9 && < 0.6, ghc-prim
+  Build-Depends: base >= 4 && < 5, primitive >= 0.4.0.1 && < 0.5, ghc-prim
 
   if impl(ghc<6.13)
     Ghc-Options: -finline-if-enough-args -fno-method-sharing






More information about the ghc-commits mailing list