[Haskell-cafe] fast image processing in haskell?
Jeff Briggs
ephemeral.elusive at gmail.com
Sat Aug 5 11:38:50 EDT 2006
On 05/08/06, Chris Kuklewicz <haskell at list.mightyreason.com> wrote:
> 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
>
Ah, so excessive laziness and IO were killing it! Thanks! This works
most excellently :)
More information about the Haskell-Cafe
mailing list