[Haskell-cafe] Re: Blitting one IOUArray into another

Ryan Ingram ryani.spam at gmail.com
Thu Jan 8 21:37:32 EST 2009


You can't safely convert an IOUArray into a Ptr; Ptr is a raw value
which isn't noticed by the garbage collector, so if the data is
relocated or GC'd while you have a pointer to it, further access will
corrupt memory.  Rather, the data inside of an IOUArray is held in a
MutableByteArray#.

In Data.Array.IO.Internals you can get at the newtype for IOUArray.  I
have some code that looks like this:

> import Foreign.Ptr
> import Data.Array.Base
> import Data.Array.IO.Internals
> import GHC.Exts
> import Data.Word

> foreign import ccall unsafe clear_bitmap ::
>     MutableByteArray# RealWorld -> Word32 -> Word32 -> IO ()

> {-# INLINE unsafeGetMutableArray# #-}
> unsafeGetMutableArray# :: IOUArray Int Word32 -> MutableByteArray# RealWorld
> unsafeGetMutableArray# (IOUArray (STUArray _ _ array#)) = array#
>
> clearBitmap :: IOUArray Int Word32 -> Word32 -> Word32 -> IO ()
> clearBitmap a1 color size
>     = clear_bitmap (unsafeGetMutableArray# a1) color size

Then the I have a small amount of C code implementing "clear_bitmap":

void clear_bitmap(HsWord32* img, HsWord32 color, HsWord32 size)
{
	for(; size; --size, ++img)
	{
		*img = color;
	}
}

This is OK to do because the "unsafe" ccall guarantees that no GC can
happen during the outcall to clear_bitmap, so we can manipulate the
pointer directly.

If you want to stay entirely in Haskell, there are a bunch of
operations on MutableByteArray# in GHC.Exts; see
http://www.haskell.org/ghc/docs/6.10-latest/html/libraries/ghc-prim/GHC-Prim.html#12

You probably need {-# LANGUAGE MagicHash #-} in order to get these to
work; it makes # be a legal symbol in identifiers.  It also helps to
know the newtype for IO, if you want to write actually usable
functions on top of these internal bits.

> newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))

Of course all of this is GHC-specific, and internal to base and
subject to change.  But I found it useful.

  -- ryan

On Thu, Jan 8, 2009 at 6:51 AM, Bueno, Denis <denbuen at sandia.gov> wrote:
> On 01/07/2009 14:36 , "Neal Alexander" <wqeqweuqy at hotmail.com> wrote:
>
>> Bueno, Denis wrote:
>>> Oh, do you mean by actually calling memcpy via ffi?
>>
>> http://www.haskell.org/ghc/docs/latest/html/libraries/base/Foreign-Marshal-Uti
>> ls.html
>
> Ah, thanks.  Is there a way to simply "cast" an IOUArray Int Int64 into
> something like a Ptr Int64, or will I need to change my code to allocate the
> arrays differently (using something in Foreign.*)?
>
> I hoogle'd functions "IOUArray a b -> Ptr b", but couldn't find anything.
>                              Denis
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list