[Haskell-cafe] some newbie FFI questions

2004-07-01 Thread John Kozak
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


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some newbie FFI questions

2004-07-01 Thread Ketil Malde
John Kozak [EMAIL PROTECTED] writes:

 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.

Are you using UArrays?  If you're going to read the whole image
anyway, they will probably be faster than the normal arrays.

Also, I read somewhere that operations are often specialized for
Double but not Float - since you talk about image loading rather than
processing, it may be worth it to use Floats to save space, even if
Doubles could be faster.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some newbie FFI questions

2004-07-01 Thread MR K P SCHUPKE
If you are using GHC the fastest way I know to do this
is to build the array using a mutable-unboxed array in the
state-monad. Then freeze the array and return an
unboxed immutable array. This is a lot faster than
building the array by copying (every time you set a
value in an immutable array the whole array much be
copied - for a sizeable image this is quite a lot of
work!)

Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some newbie FFI questions

2004-07-01 Thread MR K P SCHUPKE
Oh... also when using unboxed arrays you may well have
to have a separate array for each colour plane (r,g,b,a)
as I think unboxed arrays can only contain primitive types - although
I am not certain about this - it may be enough to have the
contents strict.

Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some newbie FFI questions

2004-07-01 Thread Duncan Coutts
On Thu, 2004-07-01 at 12:34, MR K P SCHUPKE wrote:
 Oh... also when using unboxed arrays you may well have
 to have a separate array for each colour plane (r,g,b,a)
 as I think unboxed arrays can only contain primitive types - although
 I am not certain about this - it may be enough to have the
 contents strict.

Sadly arrays of unboxed records are not currently possible. The only
instances for MArray / IArray with unboxed arrays are simple primitive
types.

See the instances for mutable arrays:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Array.MArray.html#1
and for imutable arrays
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Array.IArray.html#1

I don't think it is easy for non-ghc hackers to add extra instances.

Intuitively it seems obvious that user defined types that are just
products of unboxable types are also unboxable. Being able to say
'deriving Unboxable' would be nice...

Duncan

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some newbie FFI questions

2004-07-01 Thread MR K P SCHUPKE
Yes, deriving unboxable would be nice... I think for images though
it is not too much of a problem to work with a record of arrays
rather that an array of records. 

Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] some newbie FFI questions

2004-07-01 Thread Simon Marlow
On 01 July 2004 11:53, John Kozak wrote:

 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.

It depends how you want to use the image data, but this is almost
certainly not the best representation.

The fastest choice would be simply 'Ptr CFloat' (i.e. do no conversion
or marshalling at all).  This is essentially what your C program is
doing.  In Haskell you can allocate the memory using allocaBytes or
mallocForeignPtr (no free required).

Your other choices are:

 - IOUArray Int Float
   Fast access, but you need to convert the entire array into one
   of these, and back again if you need to pass it back to C.
  
 - (IOUArray Int Float, IOUArray Int Float, IOUArray Int Float)
   i.e. split the planes.  Might be useful, depending on how
   you access the array.  Conversion required again.

 - StorableArray Int CFloat
   You can convert the 'Ptr CFloat' you get back from C directly
   into a StorableArray, which gives you easy access using the
   mutable array primitives in Haskell, and an easy way to pass the
   array back to C using withStorableArray.

   Unfortunately accessing StorableArrays isn't as fast as it could be.
   And there ought to be a way to convert between StorableArray and
   IOUArray.  This is one area that could do with some attention.

 - Array Pixel, and data Pixel = Pixel {-# UNPACK #-}!Float ...
   Not too great, because you have a few extra layers of indirection
   compared to IOUArrays, even with the UNPACKs.

 - Array (Float,Float,Float)
   Terrible :-)

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

Using realToFrac, I guess.

 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). 

I suggest fixing a more efficient representation first.  This will
reduce the amount of manipulation of the data, and either make the bug
go away or make it easier to find.

Cheers,
Simon

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie questions

2004-07-01 Thread Crypt Master
Hi
I consider myself a pretty good imperative programmer, been at it for 
decades, and am tryibng my hand at Haskell now. Unfrituantly I am not 
getting it all that quickly despite having the multimedia haskell book.

To start ghetting some hands on, I thought iI owuld do something which i 
have done many times before in imperatives, a basic Genetic Algorithm 
Library. Unfortunatly I am comming unstuck straight away and was hoping some 
of you kind folk could point in the direction of dry land :-)

iIf your not familiar with GAs its not too important, simply a GA searches 
over the whole solution space randomly. Well not quiet, its a guided search, 
its guided by evolution ie by the fitness of each indicidual of a random 
initial population. Evolution is simulated by 3 basic operators, selection, 
cross over and mutation. selection is which indiviuals get to breed, cross 
over is how they breed, and mutation is just things intetresting.

So after reading the multimedia book, Iimmediately thought of a defining the 
solution space as a infinite list. I was hoping then I could do things like 
take 5 gaSolutionSpace to get 5 iterations or generations. My first attempt 
tied to use lis syntax [], but it wouldnt compile and after seeing 
numsFrom ina  tutorial I redefined it as such. Here is what I have so far:

-- gaSolutionSpace :: [a] - [a]
-- gaSolutionSpace [] = gaSolutionSpace createRandomPopulation -- recursive 
base case
gaSolutionSpace x = x : gaSolutionSpace (evolvepopulation x)

evolvepopulation :: a - a
evolvepopulation p = mutate cross select p
-- createRandomPopulation :: [Num a]
createRandomPopulation = [1,23,4,5,6]
cross p  = p
mutate p = p
select p = p

The take operator doesnt work on this. from hugs:
HAGA take 5 gaSolutionSpace [1,2,3,4,5]
ERROR - Type error in application
*** Expression : take 5 gaSolutionSpace [1,2,3,4,5]
*** Term   : take
*** Type   : Int - [e] - [e]
*** Does not match : a - b - c - d
I am not sure I follow this. I assume its cause I didnt use the list 
notation in definaing gaSolutionSpace. Any ideas on how to do that. ? What 
about using map. It occurs to me that you can define gaSolutionspace as a 
map of the evolvolepopuloation function acrossan infinite solution space, 
but I dont know how to makethis  infinte list to map over ...?

There ar 2 papaers on GAs in haskell, but they use monads. I realise for 
performance I will probably have to use them too, but for now I would liek 
to do it without mondas even if performance isnt optimal.

Sorry again for the newbie questions, but any help is appreciated.
Stephen
_
Help STOP SPAM with the new MSN 8 and get 2 months FREE*  
http://join.msn.com/?page=features/junkmail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie questions

2004-07-01 Thread Crypt Master
Hi
I consider myself a pretty good imperative programmer, been at it for 
decades, and am tryibng my hand at Haskell now. Unfrituantly I am not 
getting it all that quickly despite having the multimedia haskell book.

To start ghetting some hands on, I thought iI owuld do something which i 
have done many times before in imperatives, a basic Genetic Algorithm 
Library. Unfortunatly I am comming unstuck straight away and was hoping some 
of you kind folk could point in the direction of dry land :-)

iIf your not familiar with GAs its not too important, simply a GA searches 
over the whole solution space randomly. Well not quiet, its a guided search, 
its guided by evolution ie by the fitness of each indicidual of a random 
initial population. Evolution is simulated by 3 basic operators, selection, 
cross over and mutation. selection is which indiviuals get to breed, cross 
over is how they breed, and mutation is just things intetresting.

So after reading the multimedia book, Iimmediately thought of a defining the 
solution space as a infinite list. I was hoping then I could do things like 
take 5 gaSolutionSpace to get 5 iterations or generations. My first attempt 
tied to use lis syntax [], but it wouldnt compile and after seeing 
numsFrom ina  tutorial I redefined it as such. Here is what I have so far:

-- gaSolutionSpace :: [a] - [a]
-- gaSolutionSpace [] = gaSolutionSpace createRandomPopulation -- recursive 
base case
gaSolutionSpace x = x : gaSolutionSpace (evolvepopulation x)

evolvepopulation :: a - a
evolvepopulation p = mutate cross select p
-- createRandomPopulation :: [Num a]
createRandomPopulation = [1,23,4,5,6]
cross p  = p
mutate p = p
select p = p

The take operator doesnt work on this. from hugs:
HAGA take 5 gaSolutionSpace [1,2,3,4,5]
ERROR - Type error in application
*** Expression : take 5 gaSolutionSpace [1,2,3,4,5]
*** Term   : take
*** Type   : Int - [e] - [e]
*** Does not match : a - b - c - d
I am not sure I follow this. I assume its cause I didnt use the list 
notation in definaing gaSolutionSpace. Any ideas on how to do that. ? What 
about using map. It occurs to me that you can define gaSolutionspace as a 
map of the evolvolepopuloation function acrossan infinite solution space, 
but I dont know how to makethis  infinte list to map over ...?

There ar 2 papaers on GAs in haskell, but they use monads. I realise for 
performance I will probably have to use them too, but for now I would liek 
to do it without mondas even if performance isnt optimal.

Sorry again for the newbie questions, but any help is appreciated.
Stephen
_
Add photos to your e-mail with MSN 8. Get 2 months FREE*. 
http://join.msn.com/?page=features/featuredemail

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie questions

2004-07-01 Thread Duncan Coutts
On Thu, 2004-07-01 at 17:01, Crypt Master wrote:
 I consider myself a pretty good imperative programmer, been at it for 
 decades, and am tryibng my hand at Haskell now. Unfrituantly I am not 
 getting it all that quickly despite having the multimedia haskell book.

[snip]

 The take operator doesnt work on this. from hugs:
 
 HAGA take 5 gaSolutionSpace [1,2,3,4,5]
 ERROR - Type error in application
 *** Expression : take 5 gaSolutionSpace [1,2,3,4,5]
 *** Term   : take
 *** Type   : Int - [e] - [e]
 *** Does not match : a - b - c - d

What this error message is telling you is this:
  * The 'take' function wants two parameters, an Int and a list of
some type '[e]'. It will give you back a list of the same type
  * You have given it three parameters, or to put it another way you
are using 'take' as if it had type 'a - b - c - d' (for some
a,b,c  d)

The solution then is to just pass two arguments. How do you do that?
In what you've written can you see that you're passing 3 arguments?
take 5 gaSolutionSpace [1,2,3,4,5]

People say function application in Haskell is written without brackets
but this can be misleading, here you do need brackets to indicate that
'gaSolutionSpace [1,2,3,4,5]' is one argument and not two. So you should
write:
take 5 (gaSolutionSpace [1,2,3,4,5])

Now there are just two parameters, where the second parameter is another
expression rather than a simple variable or constant.

If your gaSolutionSpace takes a list type and returns a list type then
this will be well typed, and hugs will not complain.

Duncan

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Newbie questions

2004-07-01 Thread Ferenc Wagner
Crypt Master [EMAIL PROTECTED] writes:

 -- gaSolutionSpace :: [a] - [a]
 gaSolutionSpace x = x : gaSolutionSpace (evolvepopulation x)

Stop deceiving yourself until it's too late. :)
Why did you comment out the type annotation?
-- 
Feri.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] My old chess player

2004-07-01 Thread paolo veronelli
Ok Crypt Master give the hint to pronounce something ,because I feel a 
complete stupid in front of Functional Programming' though I'm a trained 
imperative one.

I've read the nice paper www.cs.chalmers.se/~rjmh/Papers/whyfp.html  and 
remember may years ago the hard job done to make my chess engine work ,but 
that was imperative C that's why it was hard ,isn't it?

John Huges say the way for trees is
data Albero position=Foglia position |Ramo position [Albero position]
This is like Quantum-Mechanics for my head but it works ,I've tried.
figliatore creatore (Foglia position) =
Ramo position (map (figliatore creatore) (creatore (Foglia Position))
This I don't know how to try it but I'm faithfully blind
Now I would like to make a change to fit my player,but the wall is too 
high.
My function 'creatore' in fact would take a list of moves and a starting 
position as argument, not a nice ready position.
My imperative engine stored leaves with a pointer to their mothers so that 
it was easy to track the list of moves.
Now maybe I have to change Albero definition in

data Albero move mother=Foglia move mother |Ramo move mother [Albero move 
mother]

Is this the way?
the road tracker is going to be
pather (Foglia move mother)=
if mother==() = ()
else = (pather madre ):madre
This doesn't compile!!
And I don't write the new 'figliatore' not to insult anyone
Thanks For Comments Paolino
Using M2, Opera's revolutionary e-mail client: http://www.opera.com/m2/
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some newbie FFI questions

2004-07-01 Thread Alastair Reid

 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

 [with a==Float being a typical instantiation]

For images of this size, I'd recommend using a different datatype because:

1) Each Pixel Float will take at least 56 bytes to store instead of 
   the 12 you expect in C.
   An array of pixels will require 4 bytes to point to each pixel bringing
   the total cost to 60 bytes or 180M instead of 36M per image.

   (I'm adding 2 words of GC-related header which I think is accurate
   for GHC.)

2) Access will be inefficient: 2 levels of indirection to access each field.
   GHC may also check that a pixel and a field are evaluated on each
   dereference so expect 4 memory reads and 2 branches per field access.

3) Memory locality is a major factor when processing images of this 
   size.  A conventional C-style array gives good locality for
   either columns or rows while a Haskell array of Pixel will give
   terrible locality because the garbage collector will keep 
   moving things around without any thoughts about locality.

4) Most image processing operations can be coded up using 1 and 2-dimensional
   array variants of the familiar list operations: map, fold{l,r}, scan{l,r}.

   This lets you hide details of the representation from most
   code manipulating images and to match the pattern of access
   to the memory layout of the image to improve cache locality.

Overall, I'd probably use an unboxed Haskell array.  This would let you get a 
memory layout (and memory consumption) close to the normal C layout.  I'd use 
access functions to hide the boxing/unboxing and I'd write some 
map/fold/scan-like functions to operate on the arrays.

In some cases, I'd leave the object in the C world and access it using FFI 
functions and using various convolution operators written in C.  This works 
great if you already have a good image processing library, you're not 
interested in writing too many new image mangling functions of your own, and 
costs of copying the image from C to Haskell (and back again, no doubt), are 
excessive.  (I did this some years ago in a real time visual tracking system 
that had to deal with 640x512 images coming in at the rate of 30 frames per 
second.)

Hope this helps,

--
Alastair Reid
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some newbie FFI questions

2004-07-01 Thread John Kozak
Alastair Reid writes:
  [...]
  Overall, I'd probably use an unboxed Haskell array.  This would let you get a 
  memory layout (and memory consumption) close to the normal C layout.  I'd use 
  access functions to hide the boxing/unboxing and I'd write some 
  map/fold/scan-like functions to operate on the arrays.
  

Thanks (and thanks to the other respondents, too).  Using unboxed
arrays has got my load time down to 15s (from 45), which is OK.  

  In some cases, I'd leave the object in the C world and access it using FFI 
  functions and using various convolution operators written in C.  This works 
  great if you already have a good image processing library, you're not 
  interested in writing too many new image mangling functions of your own, and 
  costs of copying the image from C to Haskell (and back again, no doubt), are 
  excessive.  (I did this some years ago in a real time visual tracking system 
  that had to deal with 640x512 images coming in at the rate of 30 frames per 
  second.)

I found your FVision paper a couple of days ago - nice!

John

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe