[Haskell-cafe] some newbie FFI questions

John Kozak jk at xylema.org
Thu Jul 1 06:53:13 EDT 2004


I'm trying to experiment with image processing in haskell (with which
I haven't much experience).  I've written some FFI code to talk to
the ImageMagick library which provokes a few questions (environment is
ghc 6.2.1 on debian):

1. Speed: I'm reading in a 2000x1500 pixel image, and have defined a
   Pixel type like this:

data Pixel a = Pixel !a !a !a deriving Show

  I use ImageMagick to load the image, then build an Array of Pixel
  Floats.  Building the array takes 45 seconds on a 2.5Ghz P4 with
  code compiled -O2, which seems slow to me - are my expectations
  unrealistic?  I've tried various UNPACK things which didn't make
  much difference.

2. How do I convert a CFloat into a Float?

3. I get the wrong answer ;-)  I expect the C and haskell code below
   to produce the same pixel data, but they don't (the C code is right).

C code:

#include <stdio.h>
#include <wand/magick_wand.h>

int main(int argc,char *argv[])
{
    MagickWand *wand = NewMagickWand();
    int         width,height;
    float      *pixels;
    int         i,j;
    if (argc!=2)
    {
	fprintf(stderr,"bad args\n");
	exit(100);
    }
    if (!MagickReadImage(wand,argv[1]))
    {
	fprintf(stderr,"can't read file\n");
	exit(1);
    }
    
    height = MagickGetImageHeight(wand);
    width  = MagickGetImageWidth(wand);
    printf("dimension: %dx%d\n",width,height);
    pixels = (float*) malloc(3*width*height*sizeof(float));
    
    if (!MagickGetImagePixels(wand,0,0,width,height,"RGB",FloatPixel,(unsigned char*) pixels))
    {
	fprintf(stderr,"can't get pixels\n");
	exit(1);
    }

    printf("%f %f %f\n",pixels[0],pixels[1],pixels[2]);
    printf("%f %f %f\n",pixels[4],pixels[5],pixels[6]);
    printf("%f %f %f\n",pixels[7],pixels[8],pixels[9]);
}

haskell code:

-- requires flags:   -fffi -fglasgow-exts

import Foreign
import Foreign.C
import MarshalArray

import Char
import List
import Array
import Bits

data Pixel a = Pixel !a !a !a deriving Show

data MagickWand 			-- opaque

foreign import ccall "wand/magick_wand.h NewMagickWand" newMagickWand :: IO (Ptr MagickWand)
foreign import ccall "wand/magick_wand.h DestroyMagickWand" destroyMagickWand :: (Ptr MagickWand) -> IO ()
foreign import ccall "wand/magick_wand.h MagickSetFilename" setFilename :: Ptr MagickWand -> CString -> IO ()
foreign import ccall "wand/magick_wand.h MagickReadImage" readImage :: Ptr MagickWand -> CString -> IO CInt
foreign import ccall "wand/magick_wand.h MagickGetImageWidth" getWidth :: Ptr MagickWand -> CULong
foreign import ccall "wand/magick_wand.h MagickGetImageHeight" getHeight :: Ptr MagickWand -> CULong
foreign import ccall "wand/magick_wand.h MagickGetImagePixels" getPixels :: Ptr MagickWand -> CULong -> CULong -> CULong -> CULong -> CString -> CInt -> (Ptr a) -> IO CInt	

-- StorageType: enum Char=1,Short,Integer,Long,Float=5,Double

type Frame a = Array (Int,Int) (Pixel a)

getPixel :: ([a],Int) -> Pixel a
getPixel (floats,i) = Pixel (floats!!(i*3)) (floats!!(i*3+1)) (floats!!(i*3+2))

getFrame :: (Storable a) => (Ptr a) -> Int -> Int -> IO (Frame a)
getFrame arr h w = do
		     putStr ("getFrame: "++(show (w,h))++"\n")
		     floats <- peekArray (3*h*w) arr
		     return (array ((1,1),(h,w)) [((i,j),getPixel (floats,((w*i)+j))) | i<-[1..h],j<-[1..w]])

loadFrameFloat :: FilePath -> IO (Frame CFloat)
loadFrameFloat filename = do
			   wand <- newMagickWand  
			   f <- (newCString filename)
		           ok <- readImage wand f
		           let w = (fromInteger.toInteger) (getWidth wand)
			       h = (fromInteger.toInteger) (getHeight wand) in
			    do
		             arr <- mallocArray (w*h*3) :: (IO (Ptr CFloat))
		             rgb <- (newCString "RGB")
		             ok1 <- getPixels wand 0 0 (getHeight wand) (getWidth wand) rgb 5 arr -- PixelFloat==5
			     frame <- getFrame arr h w
                             free arr
			     destroyMagickWand wand
			     return frame
thanks,

John




More information about the Haskell-Cafe mailing list