Repository : ssh://darcs.haskell.org//srv/darcs/packages/vector

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/04516581815ef7dd796d0937b3953e51366c7303

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

commit 04516581815ef7dd796d0937b3953e51366c7303
Author: Roman Leshchinskiy <[email protected]>
Date:   Sun Aug 28 10:45:27 2011 +0000

    Follow changes in primitive

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

 Data/Vector.hs                   |    2 +-
 Data/Vector/Mutable.hs           |    2 +-
 Data/Vector/Primitive.hs         |    2 +-
 Data/Vector/Primitive/Mutable.hs |    4 ++--
 4 files changed, 5 insertions(+), 5 deletions(-)

diff --git a/Data/Vector.hs b/Data/Vector.hs
index 439e88b..a628871 100644
--- a/Data/Vector.hs
+++ b/Data/Vector.hs
@@ -227,7 +227,7 @@ instance G.Vector Vector a where
 
   {-# INLINE basicUnsafeCopy #-}
   basicUnsafeCopy (MVector i n dst) (Vector j _ src)
-    = copyArray src j dst i n
+    = copyArray dst i src j n
 
 -- See http://trac.haskell.org/vector/ticket/12
 instance Eq a => Eq (Vector a) where
diff --git a/Data/Vector/Mutable.hs b/Data/Vector/Mutable.hs
index e3514fa..cc35edb 100644
--- a/Data/Vector/Mutable.hs
+++ b/Data/Vector/Mutable.hs
@@ -104,7 +104,7 @@ instance G.MVector MVector a where
 
   {-# INLINE basicUnsafeCopy #-}
   basicUnsafeCopy (MVector i n dst) (MVector j _ src)
-    = copyMutableArray src j dst i n
+    = copyMutableArray dst i src j n
   
   basicUnsafeMove dst@(MVector iDst n arrDst) src@(MVector iSrc _ arrSrc)
     = case n of
diff --git a/Data/Vector/Primitive.hs b/Data/Vector/Primitive.hs
index d76479d..1fe3677 100644
--- a/Data/Vector/Primitive.hs
+++ b/Data/Vector/Primitive.hs
@@ -209,7 +209,7 @@ instance Prim a => G.Vector Vector a where
 
   {-# INLINE basicUnsafeCopy #-}
   basicUnsafeCopy (MVector i n dst) (Vector j _ src)
-    = copyByteArray src (j*sz) dst (i*sz) (n*sz)
+    = copyByteArray dst (i*sz) src (j*sz) (n*sz)
     where
       sz = sizeOf (undefined :: a)
 
diff --git a/Data/Vector/Primitive/Mutable.hs b/Data/Vector/Primitive/Mutable.hs
index 2e769e0..447e315 100644
--- a/Data/Vector/Primitive/Mutable.hs
+++ b/Data/Vector/Primitive/Mutable.hs
@@ -95,13 +95,13 @@ instance Prim a => G.MVector MVector a where
 
   {-# INLINE basicUnsafeCopy #-}
   basicUnsafeCopy (MVector i n dst) (MVector j _ src)
-    = copyMutableByteArray src (j*sz) dst (i*sz) (n*sz)
+    = copyMutableByteArray dst (i*sz) src (j*sz) (n*sz)
     where
       sz = sizeOf (undefined :: a)
   
   {-# INLINE basicUnsafeMove #-}
   basicUnsafeMove (MVector i n dst) (MVector j _ src)
-    = moveByteArray src (j*sz) dst (i*sz) (n * sz)
+    = moveByteArray dst (i*sz) src (j*sz) (n * sz)
     where
       sz = sizeOf (undefined :: a)
 



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to