[Haskell-cafe] Haskell Data.Vector, huge memory leak

Florian Gillard florian.gillard at gmail.com
Sun Apr 26 19:44:06 UTC 2015


Hi,

I am trying to make a basic 2D engine with haskell and the SDL1.2 bindings
(for fun, I am just learning). Ideally the world is to be procedurally
generated, chunk by chunk, allowing free exploration.

Right now my chunk is composed of 200*200 tiles which I represent using a
type:

Mat [Tile] = Vec.Vector (Vec.Vector [Tile])

and these functions:

fromMat :: [[a]] ->  Mat a
fromMat xs = Vec.fromList [Vec.fromList xs' | xs' <- xs]
(§) :: Mat a -> (Int, Int) -> a
v § (r, c) = (v Vec.! r) Vec.! c

I am using cyclic list of tiles in order to allow for sprite animation, and
later for dynamic behaviour.

Each frame of the game loop, the program reads the part of the vector
relevant to the current camera position, display the corresponding tiles
and return a new vector in which every of these cyclic lists has been
replaced by it's tail.

Here is the code responsible for this:

applyTileMat :: Chunk -> SDL.Surface -> SDL.Surface -> IO Chunk
applyTileMat ch src dest =
  let m = chLand $! ch
      (x,y) = chPos ch
      wid = Vec.length (m Vec.! 0) - 1
      hei = (Vec.length m) - 1
      (canW,canH) = canvasSize ch in

  do sequence $ [ applyTile (head (m § (i,j))) (32*(j-x), 32*(i-y))
src dest | i <- [y..(y+canH)], j <- [x..(x+canW)]]
     m' <-sequence $ [sequence [(return $! tail (m § (i,j))) | j <-
[0..wid]] | i <- [0..hei]] --weird :P
     return ch { chLand = fromMat m' }

the first sequence does the display part, the second one returns the new
vector m'.

At first I was using the following comprehension to get m'

let !m' = [id $! [(tail $! (m § (i,j))) | j <- [0..wid]] | i <- [0..hei]]

but doing so results in ever increasing memory usage. I think it has to do
with lazy evaluation preventing the data to be properly garbage collected,
but I don't really understand why.

In this particular case, it doesn't really mater since I have to look at
the whole vector. But I don't know how I should do if I wanted to only
"update" part of my chunk each frame, thus making a new chunk with only
part of the data from the previous one.

I am probably not using Data.Vector the way it's intended, but it's the
simplest data structure I found with O(n) random access.

The whole code is there:
https://github.com/eniac314/wizzard/blob/master/tiler.hs
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150426/f89b558f/attachment.html>


More information about the Haskell-Cafe mailing list