summaryrefslogtreecommitdiff
path: root/lib
diff options
context:
space:
mode:
authorVivian McPhail <haskell.vivian.mcphail@gmail.com>2010-08-27 04:38:35 +0000
committerVivian McPhail <haskell.vivian.mcphail@gmail.com>2010-08-27 04:38:35 +0000
commit5e60b08d76e666643c795131bcbb18d196a39520 (patch)
treec1f699d05e196db4efba6b87ce793c8a326321eb /lib
parent6058e1b17c005be1ea95ebb7d98d9fd15bb538d2 (diff)
fix zipVector name to zipVectorWith
Diffstat (limited to 'lib')
-rw-r--r--lib/Data/Packed/Internal/Vector.hs8
-rw-r--r--lib/Data/Packed/Vector.hs6
-rw-r--r--lib/Numeric/LinearAlgebra/Linear.hs8
3 files changed, 13 insertions, 9 deletions
diff --git a/lib/Data/Packed/Internal/Vector.hs b/lib/Data/Packed/Internal/Vector.hs
index c8cc2c2..be2fcbb 100644
--- a/lib/Data/Packed/Internal/Vector.hs
+++ b/lib/Data/Packed/Internal/Vector.hs
@@ -17,7 +17,7 @@ module Data.Packed.Internal.Vector (
17 Vector, dim, 17 Vector, dim,
18 fromList, toList, (|>), 18 fromList, toList, (|>),
19 join, (@>), safe, at, at', subVector, takesV, 19 join, (@>), safe, at, at', subVector, takesV,
20 mapVector, zipVector, unzipVectorWith, 20 mapVector, zipVectorWith, unzipVectorWith,
21 mapVectorM, mapVectorM_, 21 mapVectorM, mapVectorM_,
22 foldVector, foldVectorG, foldLoop, 22 foldVector, foldVectorG, foldLoop,
23 createVector, vec, 23 createVector, vec,
@@ -319,8 +319,8 @@ mapVector f v = unsafePerformIO $ do
319{-# INLINE mapVector #-} 319{-# INLINE mapVector #-}
320 320
321-- | zipWith for Vectors 321-- | zipWith for Vectors
322zipVector :: (Storable a, Storable b, Storable c) => (a-> b -> c) -> Vector a -> Vector b -> Vector c 322zipVectorWith :: (Storable a, Storable b, Storable c) => (a-> b -> c) -> Vector a -> Vector b -> Vector c
323zipVector f u v = unsafePerformIO $ do 323zipVectorWith f u v = unsafePerformIO $ do
324 let n = min (dim u) (dim v) 324 let n = min (dim u) (dim v)
325 w <- createVector n 325 w <- createVector n
326 unsafeWith u $ \pu -> 326 unsafeWith u $ \pu ->
@@ -333,7 +333,7 @@ zipVector f u v = unsafePerformIO $ do
333 go (k-1) 333 go (k-1)
334 go (n -1) 334 go (n -1)
335 return w 335 return w
336{-# INLINE zipVector #-} 336{-# INLINE zipVectorWith #-}
337 337
338-- | unzipWith for Vectors 338-- | unzipWith for Vectors
339unzipVectorWith :: (Storable (a,b), Storable c, Storable d) 339unzipVectorWith :: (Storable (a,b), Storable c, Storable d)
diff --git a/lib/Data/Packed/Vector.hs b/lib/Data/Packed/Vector.hs
index 81dfa37..a526caa 100644
--- a/lib/Data/Packed/Vector.hs
+++ b/lib/Data/Packed/Vector.hs
@@ -26,7 +26,7 @@ module Data.Packed.Vector (
26-- vectorFMax, vectorFMin, vectorFMaxIndex, vectorFMinIndex, 26-- vectorFMax, vectorFMin, vectorFMaxIndex, vectorFMinIndex,
27-- vectorMax, vectorMin, 27-- vectorMax, vectorMin,
28 vectorMaxIndex, vectorMinIndex, 28 vectorMaxIndex, vectorMinIndex,
29 mapVector, zipVector, unzipVector, unzipVectorWith, 29 mapVector, zipVector, zipVectorWith, unzipVector, unzipVectorWith,
30 mapVectorM, mapVectorM_, 30 mapVectorM, mapVectorM_,
31 fscanfVector, fprintfVector, freadVector, fwriteVector, 31 fscanfVector, fprintfVector, freadVector, fwriteVector,
32 foldLoop, foldVector, foldVectorG 32 foldLoop, foldVector, foldVectorG
@@ -114,6 +114,10 @@ buildVector len f =
114 fromList $ map f [0 .. (len - 1)] 114 fromList $ map f [0 .. (len - 1)]
115 115
116 116
117-- | zip for Vectors
118zipVector :: (Storable a, Storable b, Storable (a,b)) => Vector a -> Vector b -> Vector (a,b)
119zipVector = zipVectorWith (,)
120
117-- | unzip for Vectors 121-- | unzip for Vectors
118unzipVector :: (Storable a, Storable b, Storable (a,b)) => Vector (a,b) -> (Vector a,Vector b) 122unzipVector :: (Storable a, Storable b, Storable (a,b)) => Vector (a,b) -> (Vector a,Vector b)
119unzipVector = unzipVectorWith id 123unzipVector = unzipVectorWith id
diff --git a/lib/Numeric/LinearAlgebra/Linear.hs b/lib/Numeric/LinearAlgebra/Linear.hs
index ae48245..71869cb 100644
--- a/lib/Numeric/LinearAlgebra/Linear.hs
+++ b/lib/Numeric/LinearAlgebra/Linear.hs
@@ -73,8 +73,8 @@ instance Vectors Vector (Complex Float) where
73 absSum = (:+ 0) . toScalarQ AbsSum 73 absSum = (:+ 0) . toScalarQ AbsSum
74 vectorMin = ap (@>) minIdx 74 vectorMin = ap (@>) minIdx
75 vectorMax = ap (@>) maxIdx 75 vectorMax = ap (@>) maxIdx
76 minIdx = minIdx . fst . fromComplex . (zipVector (*) `ap` mapVector conjugate) 76 minIdx = minIdx . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate)
77 maxIdx = maxIdx . fst . fromComplex . (zipVector (*) `ap` mapVector conjugate) 77 maxIdx = maxIdx . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate)
78 dot = dotQ 78 dot = dotQ
79 79
80instance Vectors Vector (Complex Double) where 80instance Vectors Vector (Complex Double) where
@@ -83,8 +83,8 @@ instance Vectors Vector (Complex Double) where
83 absSum = (:+ 0) . toScalarC AbsSum 83 absSum = (:+ 0) . toScalarC AbsSum
84 vectorMin = ap (@>) minIdx 84 vectorMin = ap (@>) minIdx
85 vectorMax = ap (@>) maxIdx 85 vectorMax = ap (@>) maxIdx
86 minIdx = minIdx . fst . fromComplex . (zipVector (*) `ap` mapVector conjugate) 86 minIdx = minIdx . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate)
87 maxIdx = maxIdx . fst . fromComplex . (zipVector (*) `ap` mapVector conjugate) 87 maxIdx = maxIdx . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate)
88 dot = dotC 88 dot = dotC
89 89
90---------------------------------------------------- 90----------------------------------------------------