[Haskell-cafe] Hsmagick crash

2009-06-08 Thread Ron de Bruijn

Hi,

I am trying to extract the image data from various file formats and it appeared 
that hsmagick would be the right package to use.


However, it doesn't actually work or I use it incorrectly. If you have installed 
hsmagick and change the value of some_png_file to some existing png file, you 
should see that it crashes at some random pixel. For the particular 256*256 
image I had, it crashed on pixel_nr `elem` [54,56,57].


I am open to suggestions for better ways to get a Array (Int,Int) RGB from e.g. 
a png file.


import Graphics.Transform.Magick.Images
import Graphics.Transform.Magick.Types
import Foreign.Storable
import Control.Monad

image_file_name_to_2d_array file =   do
himage - readImage file
let ptr_to_image = image himage
himage_ - peekElemOff ptr_to_image 0
let bounds@(_rows, _cols) = (rows himage_,columns himage_)
number_of_pixels  = fromIntegral _rows * fromIntegral _cols
mapM (\pixel_nr - do
   putStrLn (Pixel:  ++ show pixel_nr)
   pixel_packet - liftM background_color_  $
 peekElemOff
  ptr_to_image
  pixel_nr
   let red_component = red pixel_packet
   putStrLn (Pixel packet:  ++ show red_component)
   return red_component)
  [0.. number_of_pixels - 1]

some_png_file = foo.png

t = do
  initialize_image_library
  image_file_name_to_2d_array some_png_file

initialize_image_library = initializeMagick

Best regards,
 Ron de Bruijn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hsmagick crash

2009-06-08 Thread Mark Wassell
Have you tried 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/pngload ?


Mark


Ron de Bruijn wrote:

Hi,

I am trying to extract the image data from various file formats and it 
appeared that hsmagick would be the right package to use.


However, it doesn't actually work or I use it incorrectly. If you have 
installed hsmagick and change the value of some_png_file to some 
existing png file, you should see that it crashes at some random 
pixel. For the particular 256*256 image I had, it crashed on pixel_nr 
`elem` [54,56,57].


I am open to suggestions for better ways to get a Array (Int,Int) RGB 
from e.g. a png file.


import Graphics.Transform.Magick.Images
import Graphics.Transform.Magick.Types
import Foreign.Storable
import Control.Monad

image_file_name_to_2d_array file =   do
himage - readImage file
let ptr_to_image = image himage
himage_ - peekElemOff ptr_to_image 0
let bounds@(_rows, _cols) = (rows himage_,columns himage_)
number_of_pixels  = fromIntegral _rows * fromIntegral _cols
mapM (\pixel_nr - do
   putStrLn (Pixel:  ++ show pixel_nr)
   pixel_packet - liftM background_color_  $
 peekElemOff
  ptr_to_image
  pixel_nr
   let red_component = red pixel_packet
   putStrLn (Pixel packet:  ++ show red_component)
   return red_component)
  [0.. number_of_pixels - 1]

some_png_file = foo.png

t = do
  initialize_image_library
  image_file_name_to_2d_array some_png_file

initialize_image_library = initializeMagick

Best regards,
 Ron de Bruijn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hsmagick crash

2009-06-08 Thread Ron de Bruijn

Mark Wassell schreef:
 Have you tried
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/pngload ?
Hi Mark,

I just did:

import Codec.Image.PNG

png_file_to_2d_array file = do
  either_error_string_or_png - loadPNGFile file
  either
(\s - error $ (png_file_to_2d_array)  ++ s)
(\png -
  putStrLn (show (dimensions png))
  )
either_error_string_or_png

and then calling it gives:

*** Exception: (png_file_to_2d_array) failed to parse chunk IHDR, (line 1, 
column 1):

unexpected 0x0
expecting valid colorType: supported Ct2,Ct6

Best regards, Ron
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hsmagick crash

2009-06-08 Thread Thomas ten Cate
On Mon, Jun 8, 2009 at 13:11, Ron de Bruijnr...@gamr7.com wrote:
 Mark Wassell schreef:
 Have you tried
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/pngload ?
 Hi Mark,

 I just did:

 import Codec.Image.PNG

 png_file_to_2d_array file = do
  either_error_string_or_png - loadPNGFile file
  either
    (\s - error $ (png_file_to_2d_array)  ++ s)
    (\png -
      putStrLn (show (dimensions png))
      )
    either_error_string_or_png

 and then calling it gives:

 *** Exception: (png_file_to_2d_array) failed to parse chunk IHDR, (line 1,
 column 1):
 unexpected 0x0
 expecting valid colorType: supported Ct2,Ct6

Testing this code with the PNG file from [1] gives me

(png_file_to_2d_array) PNG_transparency_demonstration_2.png (line 1,
column 1):
unexpected 0x2d

I guess that proves that it's not just you, but not much else.

Thomas

[1] 
http://upload.wikimedia.org/wikipedia/commons/9/9a/PNG_transparency_demonstration_2.png
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe