[Haskell-cafe] fast image processing in haskell?
Chris Kuklewicz
haskell at list.mightyreason.com
Fri Aug 4 19:47:19 EDT 2006
Jeff Briggs wrote:
> Hello,
>
> I am attempting to process images captured from a webcam. My aim is to
> do so, in real time, at the frame rate of the camera. I'm using GHC
> 6.4.2 with -O3.
> A frame consists of ~100k 24bit colour values.
>
> The webcam is interfaced through FFI bindings to some C++ -- these are
> all labelled 'unsafe'. The image is passed to Haskell as a Ptr Word8.
>
> To blit this to the screen (via Gtk2Hs) I do the following:
>
> data Cam = Cam { snap_width :: !Int
> , snap_height :: !Int
> , snap_bytespp :: !Int
> , snap_size :: !Int
> , cam_img :: Ptr Word8
> , cam_obj :: ForeignPtr ()
> }
>
> do (PixbufData _ dst _) <- (pixbufGetPixels pixbuf :: IO (PixbufData Int
> Word8))
> copyBytes dst (cam_img cam)
>
> This achieves the desired throughput (25-29fps.) However, I am at a
> bit of a loss how to do something similar for preprocessing the data
> in Haskell before blitting the data (whilst also retaining some
> semblance of functional programming...)
>
> Currently, I have:
>
> cam_snap cam f x
> = do let loop (r:g:b:rest) n x = f r g b n x >>= loop rest (n+3)
> loop _ _ x = return x
> px <- peekArray (snap_size cam) (cam_img cam)
> loop px 0 x
>
> cam_snap2 cam f x
> = let loop ptr n x
> | n >= snap_size cam
> = return x
> | otherwise
> = do let ptrs = scanl plusPtr ptr [1,1]
> [r,g,b] <- mapM peek ptrs
> f r g b n x >>= loop (ptr `plusPtr` 3) (n+3)
> in loop (cam_img cam) 0 x
>
> do ...
> let sum_px r g b _ (sr,sg,sb) = return (sr+r,sg+g,sb+b)
> sum <- cam_snap (cam ui) sum_px (0.0,0.0,0.0)
> print sum
>
> cam_snap only processes at 5 fps, whereas cam_snap2 operates at 6fps.
>
> Any suggestions?
>
I suggest trying something, using "/usr/bin/ghc -O3 -optc-O3" like this:
> {-# OPTIONS_GHC -funbox-strict-fields #-}
>
> import Foreign
> import Control.Monad
>
> data Cam = Cam { snap_width :: !Int
> , snap_height :: !Int
> , snap_bytespp :: !Int
> , snap_size :: !Int
> , cam_img :: Ptr Word8
> , cam_obj :: ForeignPtr ()
> }
>
>
> type F = Word8 -> Word8 -> Word8 -> Int -> Int -> Int
>
> {-# INLINE cam_snap_3 #-}
> cam_snap_3 :: Cam -> F -> Int -> IO Int
> cam_snap_3 cam f x =
> let end = snap_size cam
> loop ptr n x | ptr `seq` n `seq` x `seq` False = undefined
> | n >= end = return x
> | otherwise = do
> r <- peek ptr
> g <- peek (advancePtr ptr 1)
> b <- peek (advancePtr ptr 2)
> loop (advancePtr ptr 3) (n+3) (f r g b n x)
> in loop (cam_img cam) 0 x
More information about the Haskell-Cafe
mailing list