[Haskell-cafe] Hsmagick crash
Mark Wassell
mwassell at bigpond.net.au
Mon Jun 8 06:53:58 EDT 2009
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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list