[GHC] #14163: Stack Overflow with ApplicativeDo

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: | Operating System: MacOS X Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I tried to compile one of our server applications with 8.2.1 (which compiles fine with 8.0.2). The compilation runs smooth, but when it reaches a specific file, the RAM usage goes up to > 20GB pretty fast on my 16GB machine and the GHC process gets terminated with a stack overflow error. I tried to find a minimal example that causes this behavior: {{{ #!/usr/bin/env stack -- stack --resolver nightly-2017-08-25 script {-# LANGUAGE ApplicativeDo #-} x = do (a, _) <- undefined (b, _) <- undefined (c, _) <- undefined undefined main = undefined }}} It only happens with at least 3 of these pattern matches. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by lippling: Old description:
I tried to compile one of our server applications with 8.2.1 (which compiles fine with 8.0.2).
The compilation runs smooth, but when it reaches a specific file, the RAM usage goes up to > 20GB pretty fast on my 16GB machine and the GHC process gets terminated with a stack overflow error.
I tried to find a minimal example that causes this behavior:
{{{ #!/usr/bin/env stack -- stack --resolver nightly-2017-08-25 script
{-# LANGUAGE ApplicativeDo #-}
x = do (a, _) <- undefined (b, _) <- undefined (c, _) <- undefined undefined
main = undefined }}}
It only happens with at least 3 of these pattern matches.
New description: I tried to compile one of our server applications with 8.2.1 (which compiles fine with 8.0.2). The compilation runs smoothly, but when it reaches a specific file, the RAM usage goes up to > 20GB pretty fast on my 16GB machine and the GHC process gets terminated with a stack overflow error. I tried to find a minimal example that causes this behavior: {{{ #!/usr/bin/env stack -- stack --resolver nightly-2017-08-25 script {-# LANGUAGE ApplicativeDo #-} x = do (a, _) <- undefined (b, _) <- undefined (c, _) <- undefined undefined main = undefined }}} It only happens with at least 3 of these pattern matches. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => ApplicativeDo * owner: (none) => simonmar Comment: OK Simon M is the expert here. But I did find that if I add the following `traceRn` in `rearrangeForApplicativeDo`: {{{ rearrangeForApplicativeDo ctxt stmts0 = do optimal_ado <- goptM Opt_OptimalApplicativeDo let stmt_tree | optimal_ado = mkStmtTreeOptimal stmts | otherwise = mkStmtTreeHeuristic stmts traceRn "rearrangeForADo" (ppr stmt_tree) <------------------- NEW return_name <- lookupSyntaxName' returnMName pure_name <- lookupSyntaxName' pureAName }}} then I get this output {{{ rearrangeForADo (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind (StmtTreeBind }}} That is, it seems that `mkStmtTreeHeuristic`goes into a loop. If you use `-foptimal-applicative-do` it works fine! Over to you, Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by lippling): So the workarounds are: - Disable ApplicativeDo -OR- - Enable the `-foptimal-applicative-do` flag and have longer compile times (O(n^2) vs. O(n^3)) -OR- - Rearrange the code so that ApplicativeDo doesn't "trigger" Am I right? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high * milestone: => 8.2.2 Old description:
I tried to compile one of our server applications with 8.2.1 (which compiles fine with 8.0.2).
The compilation runs smoothly, but when it reaches a specific file, the RAM usage goes up to > 20GB pretty fast on my 16GB machine and the GHC process gets terminated with a stack overflow error.
I tried to find a minimal example that causes this behavior:
{{{ #!/usr/bin/env stack -- stack --resolver nightly-2017-08-25 script
{-# LANGUAGE ApplicativeDo #-}
x = do (a, _) <- undefined (b, _) <- undefined (c, _) <- undefined undefined
main = undefined }}}
It only happens with at least 3 of these pattern matches.
New description: I tried to compile one of our server applications with 8.2.1 (which compiles fine with 8.0.2). The compilation runs smoothly, but when it reaches a specific file, the RAM usage goes up to > 20GB pretty fast on my 16GB machine and the GHC process gets terminated with a stack overflow error. I tried to find a minimal example that causes this behavior: {{{#!hs #!/usr/bin/env stack -- stack --resolver nightly-2017-08-25 script {-# LANGUAGE ApplicativeDo #-} x = do (a, _) <- undefined (b, _) <- undefined (c, _) <- undefined undefined main = undefined }}} It only happens with at least 3 of these pattern matches. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I think your summary of the workarounds is right. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I have a pretty decent guess about the problem. We have {{{#!hs mkStmtTreeHeuristic :: [(ExprLStmt GhcRn, FreeVars)] -> ExprStmtTree mkStmtTreeHeuristic [one] = StmtTreeOne one mkStmtTreeHeuristic stmts = case segments stmts of [one] -> split one segs -> StmtTreeApplicative (map split segs) where split [one] = StmtTreeOne one split stmts = StmtTreeBind (mkStmtTreeHeuristic before) (mkStmtTreeHeuristic after) where (before, after) = splitSegment stmts }}} The `do` block in question can't actually be split at all (all the pattern matches are strict). So I ''think'' the trick is probably to make sure `before` is non-empty before producing `StmtTreeBind`. I'll give this a whirl. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3900 Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * differential: => Phab:D3900 Comment: I have a workaround: if the splitter doesn't actually split, just pull off the first statement and the rest and form a `StmtTreeBind`. But I don't yet understand enough to see why we have this problem with strict patterns and not with other dependencies. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo
-------------------------------------+-------------------------------------
Reporter: lippling | Owner: simonmar
Type: bug | Status: new
Priority: high | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1
Resolution: | Keywords: ApplicativeDo
Operating System: MacOS X | Architecture: x86_64
Type of failure: Compile-time | (amd64)
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3900
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3900 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): @lippling: there's one other workaround, which is to add a ~ to your patterns, like so: {{{ x = do ~(a, _) <- undefined ~(b, _) <- undefined ~(c, _) <- undefined undefined }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3900 Wiki Page: | -------------------------------------+------------------------------------- Comment (by lippling): @simonmar: Thanks! Good to know. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3900 Wiki Page: | -------------------------------------+------------------------------------- Comment (by George): Is this a duplicate of #14034 ? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3900 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Yes, thanks! I've closed #14034 as a dup. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo
-------------------------------------+-------------------------------------
Reporter: lippling | Owner: simonmar
Type: bug | Status: new
Priority: high | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1
Resolution: | Keywords: ApplicativeDo
Operating System: MacOS X | Architecture: x86_64
Type of failure: Compile-time | (amd64)
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3900
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by David Feuer

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: merge Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3900 Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14163: Stack Overflow with ApplicativeDo -------------------------------------+------------------------------------- Reporter: lippling | Owner: simonmar Type: bug | Status: closed Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3900 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: comment:14 merged to `ghc-8.2` as 55b27a3231d6c25bc257006d59b329dd43ac4118. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14163#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC