[Haskell-cafe] Vector: blit'ing a source into a destination

Nicolas Trangez nicolas at incubaid.com
Sun Sep 2 15:24:58 CEST 2012


All,

For some code I need to alter an (unboxed or storable) vector by
blit'ing (copying) data from another (smaller) vector into it,
overwriting the existing data. I couldn't find a function for this in
the vector API, so I hacked something up which cuts the jobs (see
below), but it feels really ugly/dirty.

Any ideas about a better way to tackle this, and wouldn't this be a
useful addition to the standard API?

Thanks,

Nicolas


import Data.Vector.Unboxed (Unbox, Vector)
import qualified Data.Vector.Unboxed as UV
import qualified Data.Vector.Unboxed.Mutable as MUV

blit :: Unbox a => Vector a -> Vector a -> Int -> Vector a
blit src dest offset = UV.modify act dest
  where
    act dest' = do
        let slice = MUV.slice offset len dest'

        src' <- UV.unsafeThaw src
        MUV.copy slice src'

    len = UV.length src

main :: IO ()
main = do
    let v = UV.fromList [0 :: Int .. 10]
        b = UV.fromList [20, 30, 40]

    putStrLn $ "v = " ++ show v
    putStrLn $ "b = " ++ show b
    putStrLn $ "blit b v 2 = " ++ show (blit b v 2)

-- v = fromList [0,1,2,3,4,5,6,7,8,9,10]
-- b = fromList [20,30,40]
-- blit b v 2 = fromList [0,1,20,30,40,5,6,7,8,9,10]




More information about the Haskell-Cafe mailing list