[Haskell-cafe] space leak?
Massimiliano Gubinelli
mgubi at mac.com
Fri Nov 2 06:02:40 EDT 2007
> ( these two lines are just to fool the gmane post algorithm which
> complains for top-posting....)
Hi,
i'm learning Haskell and trying to use the HPDF 1.2 library I've come
across some large memory consumption for which I do not understand
the origin. I've tried heap profiling but without much success.
This is my code
> module Main where
> import Control.Monad.State
> import Graphics.PDF
> data Opcodes = Rect | Ship deriving (Show)
> doPage (Rect:ops) = do
> stroke $! Rectangle 10.0 10.0 10.0 10.0
> doPage ops
> doPage l = return l
> doOps [] = return ()
> doOps (Ship:ops) = {-# SCC "OPSHIP" #-} do
> p <- addPage Nothing
> ops' <- drawWithPage p $! do
> strokeColor red
> applyMatrix $ (translate 72.0 72.0)
> doPage ops
> doOps ops'
> doOps (op:_) = error ("unexpected " ++ show op)
> testpdf = do
> let ops = concat $ replicate 100 (Ship : (replicate 1000 Rect ))
> pageRect = PDFRect 0 0
> (floor $ 21.0/2.54*72.0) (floor $ 29.7/2.54*72.0)
> runPdf "test1.pdf" (standardDocInfo { author=toPDFString "mgubi",
> compressed = False})
> pageRect $ doOps ops
> testpdf' = do
> let pageRect = PDFRect 0 0
> (floor $ 21.0/2.54*72.0) (floor $ 29.7/2.54*72.0)
> runPdf "full.pdf" (standardDocInfo { author=toPDFString "mgubi",
> compressed = False})
> pageRect $ sequence_ $ foldM f [] $ replicate 100 $
> (\p -> sequence_ $ replicate 1000 $
> drawWithPage p $ stroke $
> Rectangle 0.0 0.0 10.0 10.0)
> where f ps acts = do
> p <- addPage Nothing
> acts p
> return $ p:ps
> main = testpdf
now, if I run testpdf' then memory profile is very low and everything
is as expected while if I run testpdf then the profile grows up to
80MB and more. This is the stripped down version of the original
program (which is a DVI interpreter) so there I will have also some
StateT and more complicated opcodes. I would like to know what is
wrong with the above code. Could someone help me?
thanks,
Massimiliano Gubinelli
More information about the Haskell-Cafe
mailing list