[Haskell-cafe] How can I get the mutable array out of an IOUArray
for FFI use?
Thomas Schilling
nominolo at googlemail.com
Sat Aug 2 04:12:21 EDT 2008
Maybe you can rewrite your code using the functions from this module:
http://haskell.org/ghc/docs/latest/html/libraries/array/Data-Array-
Storable.html
On 29 Jul 2008, at 09:22, Ryan Ingram wrote:
> I wrote some fast bit-twiddling functions in C because my Haskell
> performance wasn't good enough. Now I'm trying to recompile with
> GHC6.8.3 and failing. This code worked on GHC6.6.1.
>
> I get the following error:
>
>> ghc --make main.hs
>
> Bitmap.hs:11:7:
> Could not find module `Data.Array.IO.Internals':
> it is hidden (in package array-0.1.0.0)
>
> I suppose I can declare a copy of the internal type and use
> unsafeCoerce#, but that seems like a terrible idea if there is a
> better way. What's the right way to make this work? Can I force that
> module to be unhidden? Should I file a GHC bug?
>
> -- ryan
>
> {-# OPTIONS_GHC -fffi -fglasgow-exts #-}
> {-# INCLUDE "bitmap_operations.h" #-}
>
> module Bitmap (
> clearBitmap,
> ) where
> 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
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
/ Thomas
--
Monkey killing monkey killing monkey over pieces of the ground.
Silly monkeys give them thumbs they forge a blade
And where there's one they're bound to divide it
Right in two
-------------- next part --------------
A non-text attachment was scrubbed...
Name: PGP.sig
Type: application/pgp-signature
Size: 194 bytes
Desc: This is a digitally signed message part
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20080802/ba79f4ea/PGP.bin
More information about the Haskell-Cafe
mailing list