
#13527: ghc has a stack space leak when prints warnings -------------------------------------+------------------------------------- Reporter: slyfox | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by slyfox): I've built ghc-prof and found out GHC is most stressed in 'ErrUtils.getCaretDiagnostic' where source file is read from disk and then chunked by newlines. lexemeToString generates a lot of heap traffic as it decodes whole file into String. This example is enough to take more that 100M of stack: {{{#!hs {-# LANGUAGE PackageImports #-} module Main (main) where import qualified StringBuffer as SB main = do b <- SB.hGetStringBuffer "a.c" let s = SB.lexemeToString b (SB.len b) print (length $ lines s) }}} {{{ $ ghc --make a.hs -o a -package=ghc -debug -rtsopts $ ./a +RTS -K100M a: Stack space overflow: current size 33624 bytes. a: Use `+RTS -Ksize -RTS' to increase it. }}} Looks like there is 2 bugs here: - '''lexemeToString''' takes a lot of stack to decode StringBuffer into String - '''getCaretDiagnostic ''' could use more efficient mechanism to split file into lines before converting everything to String. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13527#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler