withImage creates intermediate lists, which is probably the main bottleneck.  Also, is it any faster if you specialize withImage instead of making it generic in the monad, e.g. withImage :: (Pixel pixel) => Int -> Int -> (Int -> Int -> IO Pixel) -> IO (Image pixel) ?


On Thu, Mar 20, 2014 at 5:12 AM, Vlatko Basic <vlatko.basic@gmail.com> wrote:
Hello Cafe,

JuicyFruite library has two functions for creating images. One is pure "generateImage", and another monadic "withImage".
I run some speed tests, and got the following results in microsecs:

generateImage =              1.0 us
withImage         =  1501241.1 us

This is the code for both functions, and the full code is at [1].

generateImage :: forall a. (Pixel a)
              => (Int -> Int -> a)  -- ^ Generating function, with `x` and `y` params.
              -> Int        -- ^ Width in pixels
              -> Int        -- ^ Height in pixels
              -> Image a
generateImage f w h = Image { imageWidth = w, imageHeight = h, imageData = generated }
  where compCount = componentCount (undefined :: a)
        generated = runST $ do
            arr <- M.new (w * h * compCount)
            let lineGenerator _ y | y >= h = return ()
                lineGenerator lineIdx y = column lineIdx 0
                  where column idx x | x >= w = lineGenerator idx $ y + 1
                        column idx x = do
                            unsafeWritePixel arr idx $ f x y
                            column (idx + compCount) $ x + 1

            lineGenerator 0 0
            V.unsafeFreeze arr


withImage :: forall m pixel. (Pixel pixel, PrimMonad m)
          => Int                     -- ^ Image width
          -> Int                     -- ^ Image height
          -> (Int -> Int -> m pixel) -- ^ Generating functions
          -> m (Image pixel)
withImage width height pixelGenerator = do
  let pixelComponentCount = componentCount (undefined :: pixel)
  arr <- M.new (width * height * pixelComponentCount)
  let mutImage = MutableImage
        { mutableImageWidth = width
        , mutableImageHeight = height
        , mutableImageData = arr
        }

  let pixelPositions = [(x, y) | y <- [0 .. height-1], x <- [0..width-1]]
  sequence_ [pixelGenerator x y >>= unsafeWritePixel arr idx
                        | ((x,y), idx) <- zip pixelPositions [0, pixelComponentCount ..]]
  unsafeFreezeImage mutImage



The measurement times are for functions alone, without loading etc.
The tests were done with same image(s) and same generating function in the same "main", one after another and in both orders, so laziness shouldn't be an issue.

I'm looking at the code, but can't explain to myself why is the monadic one so, so much slower.
One function is recursive and another uses sequence, but beside that they look quite similar.

Can someone explain where does such large difference comes from?


[1] http://hackage.haskell.org/package/JuicyPixels-3.1.4.1/docs/src/Codec-Picture-Types.html#withImage


Best regards,

vlatko


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