[Haskell-cafe] Image processing using Repa

2012-10-10 Thread Janek S.
I'm playing a bit with Repa library and its DevIL bindings. I tried to modify 
one of the examples 
from tutorial on HaskellWiki. I want to load an image, rotate it and save it to 
disk. I managed 
to write something like this:

import Foreign.Ptr
import System.Environment
import Data.Array.Repa as R hiding ((++))
import qualified Data.Array.Repa.Repr.ForeignPtr as RFP
import Data.Array.Repa.IO.DevIL

main = do
[f] <- getArgs
(RGB v) <- runIL $ readImage f
RFP.computeIntoP (RFP.toForeignPtr v) (rot180 v)
runIL $ writeImage ("flip-"++f) (RGB v)
return ()

rot180 g = backpermute e flop g
where
e@(Z :. x :. y :. _)   = extent g
flop (Z :. i :. j :. k) =
 (Z :. x - i - 1 :. y - j - 1 :. k)

This is obviously wrong, because the foreign pointer used as a data source is 
at the same time 
used as destination, so the data gets overwritten before it is used. Does this 
mean that I have 
to allocate foreign memory buffers on my own? If so, than it feels kind of 
painfull to go through 
the hassle of allocating foreign pointers, converting between many different 
representations and 
so on. Am I doing something wrong and if not is there a more painless way of 
working with images 
and repa in Haskell?

Jan

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


Re: [Haskell-cafe] Image processing using Repa

2012-10-10 Thread Jake McArthur
You do not have to use computeIntoP. You can just use computeP followed by
toForeignPtr (i don't remember the exact name for that and am on my phone
so it would be awkward to look up). So Repa can create the buffer for you.
Coincidentally, I didn't realize computeIntoP even existed, and I want it
for what I'm doing!
On Oct 10, 2012 7:55 AM, "Janek S."  wrote:

> I'm playing a bit with Repa library and its DevIL bindings. I tried to
> modify one of the examples
> from tutorial on HaskellWiki. I want to load an image, rotate it and save
> it to disk. I managed
> to write something like this:
>
> import Foreign.Ptr
> import System.Environment
> import Data.Array.Repa as R hiding ((++))
> import qualified Data.Array.Repa.Repr.ForeignPtr as RFP
> import Data.Array.Repa.IO.DevIL
>
> main = do
> [f] <- getArgs
> (RGB v) <- runIL $ readImage f
> RFP.computeIntoP (RFP.toForeignPtr v) (rot180 v)
> runIL $ writeImage ("flip-"++f) (RGB v)
> return ()
>
> rot180 g = backpermute e flop g
> where
> e@(Z :. x :. y :. _)   = extent g
> flop (Z :. i :. j :. k) =
>  (Z :. x - i - 1 :. y - j - 1 :. k)
>
> This is obviously wrong, because the foreign pointer used as a data source
> is at the same time
> used as destination, so the data gets overwritten before it is used. Does
> this mean that I have
> to allocate foreign memory buffers on my own? If so, than it feels kind of
> painfull to go through
> the hassle of allocating foreign pointers, converting between many
> different representations and
> so on. Am I doing something wrong and if not is there a more painless way
> of working with images
> and repa in Haskell?
>
> Jan
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Image processing using Repa

2012-10-10 Thread Janek S.
> You do not have to use computeIntoP. You can just use computeP followed by
> toForeignPtr (i don't remember the exact name for that and am on my phone
> so it would be awkward to look up). So Repa can create the buffer for you.
> Coincidentally, I didn't realize computeIntoP even existed, and I want it
> for what I'm doing!
I managed to fix my code - thanks! The main function now reads:

main = do
[f] <- getArgs
(RGB v) <- runIL $ readImage f
rotated <- (computeP $ rot180 v) :: IO (Array RFP.F DIM3 Word8)
runIL $ writeImage ("flip-"++f) (RGB rotated)

Jan

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