#3039: strange space usage
---------------------------------------+------------------------------------
  Reporter:  igloo                     |          Owner:                  
      Type:  run-time performance bug  |         Status:  new             
  Priority:  normal                    |      Milestone:                  
 Component:  Compiler                  |        Version:  6.10.1          
  Severity:  normal                    |       Keywords:                  
Difficulty:  Unknown                   |       Testcase:                  
        Os:  Unknown/Multiple          |   Architecture:  Unknown/Multiple
---------------------------------------+------------------------------------
 This program:
 {{{
 module Main (main) where

 import System.IO.Unsafe

 main :: IO ()
 main = do writeFile "wibbleflibble" (replicate 100 'z')
           bs <- getCs $ g $ replicate 1000000 "flibble"
           print $ last bs

 getCs :: [FilePath] -> IO String
 getCs [] = return ""
 getCs (c : cs) = do x <- readFile c
                     xs <- unsafeInterleaveIO $ getCs cs
                     return (x ++ xs)

 g :: [FilePath] -> [FilePath]
 g is = map f is

 f :: FilePath -> FilePath
 f fn = "wibble" ++ fn
 }}}
 when run:
 {{{
 $ ghc -fforce-recomp -Wall --make -O2 -prof -auto-all z.hs -o z
 $ ./z +RTS -h -p
 }}}
 shows that around 100k is used by `f` (`h.png`). Running with
 {{{
 $ ./z +RTS -hcf -hy -p
 }}}
 shows that it is all of type `[]` (`hcf_hy.png`). That seems like a large
 amount of space for a 13 character filename, so it smells to me like
 something is wrong somewhere.

 If we inline `g`:
 {{{
 module Main (main) where

 import System.IO.Unsafe

 main :: IO ()
 main = do writeFile "wibbleflibble" (replicate 100 'z')
           bs <- getCs $ map f $ replicate 1000000 "flibble"
           print $ last bs

 getCs :: [FilePath] -> IO String
 getCs [] = return ""
 getCs (c : cs) = do x <- readFile c
                     xs <- unsafeInterleaveIO $ getCs cs
                     return (x ++ xs)

 f :: FilePath -> FilePath
 f fn = "wibble" ++ fn
 }}}
 then it all disappears (`h2.png`).

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3039>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to