<html>
  <head>
    <meta content="text/html; charset=ISO-8859-1"
      http-equiv="Content-Type">
    <style id="EHTipGlobalStyle">.EHTipToolTip * {background: inherit;font-family: inherit;font-size: inherit;font-size-adjust: none;font-stretch: normal;line-height: inherit;font-variant: normal;border: 0px;text-transform: inherit;color: inherit;font-style: inherit;text-decoration: inherit;margin: 0px 0px 0px 0px;padding: 0px 0px 0px 0px;float: none;display: inline;cursor: default;}
.EHTipReplacer, .EHTipKey, .EHTipAudio {cursor: pointer;}
.EHTipToolTip hr {margin: 0.4em 0;display: block;border: 1px inset;}
.EHTipTranslation {font-style: normal;}
.EHTipTranslation a {color: #000099;font-style: normal;text-decoration: none;}
.EHTipTranslation a:hover {background: inherit;color: #000000;text-decoration: underline;}
</style>
  </head>
  <body style="background-color: rgb(255, 255, 255); color: rgb(0, 0,
    0);" bgcolor="#FFFFFF" text="#000000">
    Hi Joey,<br>
    <br>
    By intermediate lists, do you mean the list comprehension. <br>
    But it is sequence_, so I believe the compiler would spot that
    results are not needed and the list wouldn't be formed anyway.<br>
    Maybe I'm wrong.<br>
    <br>
    I'm not sure if argument list should be fully created for sequence_,
    or is it lazy?<br>
    Full creation of the list might explain the results. The image has
    quite a few pixels.<br>
    <br>
    <br>
    On the other hand, before I noticed that "generateImage" is fast
    enough, I wrote my own function that converted Vector to list, than
    to chunks and back to Vector, and it was fast as "generateImage".<br>
    <br>
    <br>
    vlatko<br>
    <br>
    <blockquote
cite="mid:CAARyMpBLe=azrHSmji+mTEPLH3N2okrZ-wncR5VtT6fnw5RdjQ@mail.gmail.com"
      type="cite"><!--[if !IE]><DIV style="border-left: 2px solid #330033; border-right: 2px solid #330033;  padding: 0px 15px; margin: 2px 0px;"><![endif]--><span
        style="color:#000000;" class="headerSpan">
        <div class="moz-cite-prefix">-------- Original Message --------<br>
          Subject: Re: [Haskell-cafe] JuicyFruit - explanation of speed
          difference of pure and monadic image generation<br>
          From: Joey Adams <a class="moz-txt-link-rfc2396E" href="mailto:joeyadams3.14159@gmail.com"><joeyadams3.14159@gmail.com></a><br>
          To: <a class="moz-txt-link-abbreviated" href="mailto:vlatko.basic@gmail.com">vlatko.basic@gmail.com</a><br>
          Cc: haskell-cafe <a class="moz-txt-link-rfc2396E" href="mailto:haskell-cafe@haskell.org"><haskell-cafe@haskell.org></a><br>
          Date: 20.03.2014 13:35<br>
        </div>
        <br>
        <br>
      </span>
      <div dir="ltr">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) ?<br>
      </div>
      <div class="gmail_extra"><br>
        <br>
        <div class="gmail_quote">On Thu, Mar 20, 2014 at 5:12 AM, Vlatko
          Basic <span dir="ltr"><<a moz-do-not-send="true"
              href="mailto:vlatko.basic@gmail.com" target="_blank">vlatko.basic@gmail.com</a>></span>
          wrote:<br>
          <blockquote class="gmail_quote" style="margin:0 0 0
            .8ex;border-left:1px #ccc solid;padding-left:1ex">Hello
            Cafe,<br>
            <br>
            JuicyFruite library has two functions for creating images.
            One is pure "generateImage", and another monadic
            "withImage".<br>
            I run some speed tests, and got the following results in
            microsecs:<br>
            <br>
            generateImage =              1.0 us<br>
            withImage         =  1501241.1 us<br>
            <br>
            This is the code for both functions, and the full code is at
            [1].<br>
            <br>
            generateImage :: forall a. (Pixel a)<br>
                          => (Int -> Int -> a)  -- ^ Generating
            function, with `x` and `y` params.<br>
                          -> Int        -- ^ Width in pixels<br>
                          -> Int        -- ^ Height in pixels<br>
                          -> Image a<br>
            generateImage f w h = Image { imageWidth = w, imageHeight =
            h, imageData = generated }<br>
              where compCount = componentCount (undefined :: a)<br>
                    generated = runST $ do<br>
                        arr <- M.new (w * h * compCount)<br>
                        let lineGenerator _ y | y >= h = return ()<br>
                            lineGenerator lineIdx y = column lineIdx 0<br>
                              where column idx x | x >= w =
            lineGenerator idx $ y + 1<br>
                                    column idx x = do<br>
                                        unsafeWritePixel arr idx $ f x y<br>
                                        column (idx + compCount) $ x + 1<br>
            <br>
                        lineGenerator 0 0<br>
                        V.unsafeFreeze arr<br>
            <br>
            <br>
            withImage :: forall m pixel. (Pixel pixel, PrimMonad m)<br>
                      => Int                     -- ^ Image width<br>
                      -> Int                     -- ^ Image height<br>
                      -> (Int -> Int -> m pixel) -- ^
            Generating functions<br>
                      -> m (Image pixel)<br>
            withImage width height pixelGenerator = do<br>
              let pixelComponentCount = componentCount (undefined ::
            pixel)<br>
              arr <- M.new (width * height * pixelComponentCount)<br>
              let mutImage = MutableImage<br>
                    { mutableImageWidth = width<br>
                    , mutableImageHeight = height<br>
                    , mutableImageData = arr<br>
                    }<br>
            <br>
              let pixelPositions = [(x, y) | y <- [0 .. height-1], x
            <- [0..width-1]]<br>
              sequence_ [pixelGenerator x y >>= unsafeWritePixel
            arr idx<br>
                                    | ((x,y), idx) <- zip
            pixelPositions [0, pixelComponentCount ..]]<br>
              unsafeFreezeImage mutImage<br>
            <br>
            <br>
            <br>
            The measurement times are for functions alone, without
            loading etc.<br>
            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.<br>
            <br>
            I'm looking at the code, but can't explain to myself why is
            the monadic one so, so much slower.<br>
            One function is recursive and another uses sequence, but
            beside that they look quite similar.<br>
            <br>
            Can someone explain where does such large difference comes
            from?<br>
            <br>
            <br>
            [1] <a moz-do-not-send="true"
href="http://hackage.haskell.org/package/JuicyPixels-3.1.4.1/docs/src/Codec-Picture-Types.html#withImage"
              target="_blank">http://hackage.haskell.org/package/JuicyPixels-3.1.4.1/docs/src/Codec-Picture-Types.html#withImage</a><br>
            <br>
            <br>
            Best regards,<br>
            <br>
            vlatko<br>
            <br>
            <br>
            _______________________________________________<br>
            Haskell-Cafe mailing list<br>
            <a moz-do-not-send="true"
              href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
            <a moz-do-not-send="true"
              href="http://www.haskell.org/mailman/listinfo/haskell-cafe"
              target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
          </blockquote>
        </div>
        <br>
      </div>
      <!--[if !IE]></DIV><![endif]--></blockquote>
    <br>
  </body>
</html>