diff options
Diffstat (limited to 'lib/Data')
-rw-r--r-- | lib/Data/Packed/Internal/Vector.hs | 38 |
1 files changed, 20 insertions, 18 deletions
diff --git a/lib/Data/Packed/Internal/Vector.hs b/lib/Data/Packed/Internal/Vector.hs index 7dd1289..ec2bf3c 100644 --- a/lib/Data/Packed/Internal/Vector.hs +++ b/lib/Data/Packed/Internal/Vector.hs | |||
@@ -365,30 +365,32 @@ foldVectorG f s0 v = foldLoop g s0 (dim v) | |||
365 | mapVectorM :: (Storable a, Storable b, MonadIO m) => (a -> m b) -> Vector a -> m (Vector b) | 365 | mapVectorM :: (Storable a, Storable b, MonadIO m) => (a -> m b) -> Vector a -> m (Vector b) |
366 | mapVectorM f v = do | 366 | mapVectorM f v = do |
367 | w <- liftIO $ createVector (dim v) | 367 | w <- liftIO $ createVector (dim v) |
368 | mapVectorM' f v w (dim v -1) | 368 | mapVectorM' f v w 0 (dim v -1) |
369 | return w | 369 | return w |
370 | where mapVectorM' f' v' w' 0 = do | 370 | where mapVectorM' f' v' w' !k !t |
371 | x <- liftIO $ unsafeWith v' $ \p -> peekElemOff p 0 | 371 | | k == t = do |
372 | y <- f' x | 372 | x <- liftIO $ unsafeWith v' $ \p -> peekElemOff p k |
373 | liftIO $ unsafeWith w' $ \q -> pokeElemOff q 0 y | 373 | y <- f' x |
374 | mapVectorM' f' v' w' !k = do | 374 | liftIO $ unsafeWith w' $ \q -> pokeElemOff q k y |
375 | x <- liftIO $ unsafeWith v' $ \p -> peekElemOff p k | 375 | | otherwise = do |
376 | y <- f' x | 376 | x <- liftIO $ unsafeWith v' $ \p -> peekElemOff p k |
377 | liftIO $ unsafeWith w' $ \q -> pokeElemOff q k y | 377 | y <- f' x |
378 | mapVectorM' f' v' w' (k-1) | 378 | liftIO $ unsafeWith w' $ \q -> pokeElemOff q k y |
379 | mapVectorM' f' v' w' (k+1) t | ||
379 | {-# INLINE mapVectorM #-} | 380 | {-# INLINE mapVectorM #-} |
380 | 381 | ||
381 | -- | monadic map over Vectors | 382 | -- | monadic map over Vectors |
382 | mapVectorM_ :: (Storable a, MonadIO m) => (a -> m ()) -> Vector a -> m () | 383 | mapVectorM_ :: (Storable a, MonadIO m) => (a -> m ()) -> Vector a -> m () |
383 | mapVectorM_ f v = do | 384 | mapVectorM_ f v = do |
384 | mapVectorM' f v (dim v -1) | 385 | mapVectorM' f v 0 (dim v -1) |
385 | where mapVectorM' f' v' 0 = do | 386 | where mapVectorM' f' v' !k !t |
386 | x <- liftIO $ unsafeWith v' $ \p -> peekElemOff p 0 | 387 | | k == t = do |
387 | f' x | 388 | x <- liftIO $ unsafeWith v' $ \p -> peekElemOff p k |
388 | mapVectorM' f' v' !k = do | 389 | f' x |
389 | x <- liftIO $ unsafeWith v' $ \p -> peekElemOff p k | 390 | | otherwise = do |
390 | _ <- f' x | 391 | x <- liftIO $ unsafeWith v' $ \p -> peekElemOff p k |
391 | mapVectorM' f' v' (k-1) | 392 | _ <- f' x |
393 | mapVectorM' f' v' (k+1) t | ||
392 | {-# INLINE mapVectorM_ #-} | 394 | {-# INLINE mapVectorM_ #-} |
393 | 395 | ||
394 | ------------------------------------------------------------------- | 396 | ------------------------------------------------------------------- |