[commit: vector] simd: Comment out the NFData instance for mutable boxed vectors for now (3247dd1)
Geoffrey Mainland
gmainlan at ghc.haskell.org
Fri Jul 19 14:24:05 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch : simd
http://hackage.haskell.org/trac/ghc/changeset/3247dd115fea8bd380762c9d0030f325f2a3e260
>---------------------------------------------------------------
commit 3247dd115fea8bd380762c9d0030f325f2a3e260
Author: Roman Leshchinskiy <rl at cse.unsw.edu.au>
Date: Sun Jan 29 12:14:29 2012 +0000
Comment out the NFData instance for mutable boxed vectors for now
>---------------------------------------------------------------
Data/Vector/Mutable.hs | 3 +++
1 file changed, 3 insertions(+)
diff --git a/Data/Vector/Mutable.hs b/Data/Vector/Mutable.hs
index 6168bea..e896f3a 100644
--- a/Data/Vector/Mutable.hs
+++ b/Data/Vector/Mutable.hs
@@ -72,12 +72,15 @@ data MVector s a = MVector {-# UNPACK #-} !Int
type IOVector = MVector RealWorld
type STVector s = MVector s
+-- NOTE: This seems unsafe, see http://trac.haskell.org/vector/ticket/54
+{-
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 #-}
More information about the ghc-commits
mailing list