summaryrefslogtreecommitdiff
path: root/lib/Data/Packed
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Data/Packed')
-rw-r--r--lib/Data/Packed/Internal/Vector.hs59
-rw-r--r--lib/Data/Packed/Matrix.hs28
2 files changed, 15 insertions, 72 deletions
diff --git a/lib/Data/Packed/Internal/Vector.hs b/lib/Data/Packed/Internal/Vector.hs
index d3b80ff..5892e67 100644
--- a/lib/Data/Packed/Internal/Vector.hs
+++ b/lib/Data/Packed/Internal/Vector.hs
@@ -55,48 +55,17 @@ import GHC.Base
55import GHC.IOBase hiding (liftIO) 55import GHC.IOBase hiding (liftIO)
56#endif 56#endif
57 57
58#ifdef VECTOR
59import qualified Data.Vector.Storable as Vector 58import qualified Data.Vector.Storable as Vector
60import Data.Vector.Storable(Vector, 59import Data.Vector.Storable(Vector,
61 unsafeToForeignPtr, 60 unsafeToForeignPtr,
62 unsafeFromForeignPtr, 61 unsafeFromForeignPtr,
63 unsafeWith) 62 unsafeWith)
64#else
65import Foreign.ForeignPtr(withForeignPtr)
66#endif
67 63
68#ifdef VECTOR
69 64
70-- | Number of elements 65-- | Number of elements
71dim :: (Storable t) => Vector t -> Int 66dim :: (Storable t) => Vector t -> Int
72dim = Vector.length 67dim = Vector.length
73 68
74#else
75
76-- | One-dimensional array of objects stored in a contiguous memory block.
77data Vector t =
78 V { ioff :: {-# UNPACK #-} !Int -- ^ offset of first element
79 , idim :: {-# UNPACK #-} !Int -- ^ number of elements
80 , fptr :: {-# UNPACK #-} !(ForeignPtr t) -- ^ foreign pointer to the memory block
81 }
82
83unsafeToForeignPtr :: Storable a => Vector a -> (ForeignPtr a, Int, Int)
84unsafeToForeignPtr v = (fptr v, ioff v, idim v)
85
86-- | Same convention as in Roman Leshchinskiy's vector package.
87unsafeFromForeignPtr :: Storable a => ForeignPtr a -> Int -> Int -> Vector a
88unsafeFromForeignPtr fp i n | n > 0 = V {ioff = i, idim = n, fptr = fp}
89 | otherwise = error "unsafeFromForeignPtr with dim < 1"
90
91unsafeWith (V i _ fp) m = withForeignPtr fp $ \p -> m (p `advancePtr` i)
92{-# INLINE unsafeWith #-}
93
94-- | Number of elements
95dim :: (Storable t) => Vector t -> Int
96dim = idim
97
98#endif
99
100 69
101-- C-Haskell vector adapter 70-- C-Haskell vector adapter
102-- vec :: Adapt (CInt -> Ptr t -> r) (Vector t) r 71-- vec :: Adapt (CInt -> Ptr t -> r) (Vector t) r
@@ -204,36 +173,8 @@ subVector :: Storable t => Int -- ^ index of the starting element
204 -> Int -- ^ number of elements to extract 173 -> Int -- ^ number of elements to extract
205 -> Vector t -- ^ source 174 -> Vector t -- ^ source
206 -> Vector t -- ^ result 175 -> Vector t -- ^ result
207
208#ifdef VECTOR
209
210subVector = Vector.slice 176subVector = Vector.slice
211 177
212{-
213subVector k l v
214 | k<0 || k >= n || k+l > n || l < 0 = error "subVector out of range"
215 | otherwise = unsafeFromForeignPtr fp (i+k) l
216 where
217 (fp, i, n) = unsafeToForeignPtr v
218-}
219
220#else
221
222subVector k l v@V{idim = n, ioff = i}
223 | k<0 || k >= n || k+l > n || l < 0 = error "subVector out of range"
224 | otherwise = v {idim = l, ioff = i+k}
225
226{-
227subVectorCopy k l (v@V {idim=n})
228 | k<0 || k >= n || k+l > n || l < 0 = error "subVector out of range"
229 | otherwise = unsafePerformIO $ do
230 r <- createVector l
231 let f _ s _ d = copyArray d (advancePtr s k) l >> return 0
232 app2 f vec v vec r "subVector"
233 return r
234-}
235
236#endif
237 178
238{- | Reads a vector position: 179{- | Reads a vector position:
239 180
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs
index c1a9b24..fe8c159 100644
--- a/lib/Data/Packed/Matrix.hs
+++ b/lib/Data/Packed/Matrix.hs
@@ -46,6 +46,7 @@ import Data.Array
46 46
47import Data.List(transpose,intersperse) 47import Data.List(transpose,intersperse)
48import Foreign.Storable(Storable) 48import Foreign.Storable(Storable)
49import Control.Monad(liftM)
49 50
50------------------------------------------------------------------- 51-------------------------------------------------------------------
51 52
@@ -351,7 +352,11 @@ toBlocksEvery r c m = toBlocks rs cs m where
351 352
352------------------------------------------------------------------- 353-------------------------------------------------------------------
353 354
354mk c g = \k v -> g (divMod k c) v 355-- Given a column number and a function taking matrix indexes, returns
356-- a function which takes vector indexes (that can be used on the
357-- flattened matrix).
358mk :: Int -> ((Int, Int) -> t) -> (Int -> t)
359mk c g = \k -> g (divMod k c)
355 360
356{- | 361{- |
357 362
@@ -364,9 +369,8 @@ m[1,1] = 5
364m[1,2] = 6@ 369m[1,2] = 6@
365-} 370-}
366mapMatrixWithIndexM_ 371mapMatrixWithIndexM_
367 :: (Element a, Num a, 372 :: (Element a, Num a, Monad m) =>
368 Functor f, Monad f) => 373 ((Int, Int) -> a -> m ()) -> Matrix a -> m ()
369 ((Int, Int) -> a -> f ()) -> Matrix a -> f ()
370mapMatrixWithIndexM_ g m = mapVectorWithIndexM_ (mk c g) . flatten $ m 374mapMatrixWithIndexM_ g m = mapVectorWithIndexM_ (mk c g) . flatten $ m
371 where 375 where
372 c = cols m 376 c = cols m
@@ -380,11 +384,9 @@ Just (3><3)
380 , 20.0, 21.0, 122.0 ]@ 384 , 20.0, 21.0, 122.0 ]@
381-} 385-}
382mapMatrixWithIndexM 386mapMatrixWithIndexM
383 :: (Foreign.Storable.Storable t, 387 :: (Element a, Storable b, Monad m) =>
384 Element a, Num a, 388 ((Int, Int) -> a -> m b) -> Matrix a -> m (Matrix b)
385 Functor f, Monad f) => 389mapMatrixWithIndexM g m = liftM (reshape c) . mapVectorWithIndexM (mk c g) . flatten $ m
386 ((Int, Int) -> a -> f t) -> Matrix a -> f (Matrix t)
387mapMatrixWithIndexM g m = fmap (reshape c) . mapVectorWithIndexM (mk c g) . flatten $ m
388 where 390 where
389 c = cols m 391 c = cols m
390 392
@@ -395,10 +397,10 @@ mapMatrixWithIndexM g m = fmap (reshape c) . mapVectorWithIndexM (mk c g) . flat
395 , 10.0, 111.0, 12.0 397 , 10.0, 111.0, 12.0
396 , 20.0, 21.0, 122.0 ]@ 398 , 20.0, 21.0, 122.0 ]@
397 -} 399 -}
398mapMatrixWithIndex :: (Foreign.Storable.Storable t, 400mapMatrixWithIndex
399 Element a, Num a) => 401 :: (Element a, Storable b) =>
400 ((Int, Int) -> a -> t) -> Matrix a -> Matrix t 402 ((Int, Int) -> a -> b) -> Matrix a -> Matrix b
401mapMatrixWithIndex g m = reshape c $ mapVectorWithIndex (mk c g) $ flatten m 403mapMatrixWithIndex g m = reshape c . mapVectorWithIndex (mk c g) . flatten $ m
402 where 404 where
403 c = cols m 405 c = cols m
404 406