[Haskell-cafe] How to translate Repa 2 program to efficient Repa 3 code?

2012-05-26 Thread Michael Serra
Hi Haskellers,
I've posted this question (and my code) to stack overflow as well (
http://stackoverflow.com/questions/10747079/what-are-the-key-differences-between-the-repa-2-and-3-apis),
so if anyone here has the answer, I'll post it to that site for the world's
reference.  Using the Repa 2 API, I have written some simple image
convolution tests which run more than fast enough.  The trick to getting
good performance was to call 'force' after every array transformation.  I
can't quite figure out the analogous thing to do with Repa 3 - at
stackoverflow you can see my Repa 3 code, which runs correctly but very
slowly.  It is not clear to me how exactly the monadic computeP functions
in Repa 3 are intended to be used - I have several calls to 'force' in my
Repa 2 code, but only 1 call to computeP in the Repa 3 version.  I've read
the excellent Numeric Haskell Repa tutorial by Don S, but it doesn't
cover Repa 3.  My thanks in advance!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to translate Repa 2 program to efficient Repa 3 code?

2012-05-26 Thread Michael Serra
Hi Haskellers,
I've posted this question (and my code) to stack overflow as well (
http://stackoverflow.com/questions/10747079/what-are-the-key-differences-between-the-repa-2-and-3-apis),
so if anyone here has the answer, I'll post it to that site for the world's
reference.  Using the Repa 2 API, I have written some simple image
convolution tests which run more than fast enough.  The trick to getting
good performance was to call 'force' after every array transformation.  I
can't quite figure out the analogous thing to do with Repa 3 - at
stackoverflow you can see my Repa 3 code, which runs correctly but very
slowly.  It is not clear to me how exactly the monadic computeP functions
in Repa 3 are intended to be used - I have several calls to 'force' in my
Repa 2 code, but only 1 call to computeP in the Repa 3 version.  I've read
the excellent Numeric Haskell Repa tutorial by Don S, but it doesn't
cover Repa 3.  My apologies if this message appears twice; it didn't seem
to be sent the first time.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Mitigating state-threading through an application loop

2011-12-20 Thread Michael Serra
Hello Haskellers,
  I'm implementing a simple tree-manipulating (for sports tournaments)
application prototype, with SDL for graphics and simple user interaction.
For reference, I've posted the code on hpaste. http://hpaste.org/55506
My question is about code organization: everything was simple and elegant
until I started writing the program's display/event loop.  Every function
in this section has to be passed the same parameters - the application
window to draw on, the font to display text with, the tree representing the
current application state, etc.  The font is an especially egregious
example of the problem, because it's only used by one function but to get
there it must be threaded through all of them (looking at the hpaste, you
will see I don't want to call openFont on every invocation of drawTexts;
what's needed is to call it once in main and have the resulting value
available to drawTxt.  So my question: how can I mitigate the ugliness of
this state-threading?  I understand this is one purpose for monads; am I
supposed to implement a monad transformer for this?

I think it would be great if I could define a type AppState as a tuple of
the various things I need to thread, and specify some kind of automatic
as-pattern, so that every function taking this AppState parameter would
implicitly have its components bound to certain preset names.  I've never
seen anyone do this however.  What is the right solution?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Inconsistent window updates with SDL library

2011-05-16 Thread Michael Serra
Greetings Haskellers,
  I'm relatively new to the language and I'm writing a basic game of life
simulation to try out the SDL bindings.  The program updates the window with
the next generation of cells each time you press 'n', and the problem I'm
finding is that every so often the window stops updating.  The program
continues; refreshing the window (by moving it, say) updates it to the
correct current state.  I thought there must be a big problem with my code,
but found the same behavior with lesson
20https://github.com/snkkid/LazyFooHaskellof the SDL lazyfoo
tutorials (the animation test).  Can anyone explain what
is causing this?  I hope to hear I've made some obvious mistake, rather than
discover any limitation with the useful SDL bindings..
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Inconsistent window updates with SDL library

2011-05-16 Thread Michael Serra
Oh, in case the code would be helpful.. ;)

import Data.Set (toList, fromList, intersection, size)
import Data.List ((\\))
import System.Random (randomRIO)
import Data.Word (Word32)
import Graphics.UI.SDL as SDL

main = do
  SDL.init [InitVideo, InitTimer, InitEventthread]
  w - setVideoMode 1440 900 32 []
  setCaption LIFE life
  eventLoop w cells
  quit

eventLoop w cs = do
  drawCells w cs
  e - waitEventBlocking
  checkEvent e
where
  checkEvent (KeyUp (Keysym SDLK_ESCAPE _ _)) = return ()
  checkEvent (KeyUp (Keysym SDLK_n _ _))  = eventLoop w $ nextgen cs
  checkEvent _= eventLoop w cs

drawCells w cs = do
  clearScreen
  s - createRGBSurface [SWSurface] size size 32 0 0 0 0
  sequence $ map (draw s) $ scale cs
  SDL.flip w
where
  clearScreen  = fillRect w (Just $ Rect 0 0 1440 900) $ Pixel 0x0
  rect x y = Just $ Rect x y size size
  scale= map (\(x,y) - (x * size, y * size))
  size = 16
  draw s (x,y) =
do
  r - randomRIO (0::Int, 0xFF)
  fillRect s (rect 0 0) $ Pixel (fromIntegral r :: Word32)
  blitSurface s (rect 0 0) w $ rect x y


cells  = [(25,14),(26,14),(25,15),(24,15),(25,16)]

nextgen cs = (filter (live cs) cs) ++ births cs

live cs c  = size neighbors  1size neighbors  4
   where neighbors = adj c `intersection` fromList cs

births cs  = (filter neighbors3 allAdjacent) \\ cs
   where allAdjacent  = nub $ concatMap (toList . adj) cs
 neighbors3 c = size (neighbors c) == 3
 neighbors c  = adj c `intersection` fromList cs
 nub  = toList . fromList

adj (x,y)  = fromList $ tail [(a,b) | a - [x,x+1,x-1], b - [y,y+1,y-1]]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe