[GHC] #9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm

#9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Keywords: | Operating System: Architecture: x86_64 (amd64) | Unknown/Multiple Difficulty: Unknown | Type of failure: Compile- Blocked By: | time crash Related Tickets: | Test Case: T3500b | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- {{{ $ make fulltest TEST="T3500b" WAY=optasm =====> T3500b(optasm) 3767 of 4101 [0, 0, 0] cd ./typecheck/should_run && '/home/slyfox/dev/git/ghc- validate/inplace/bin/ghc-stage2' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts -fno-ghci-history -o T3500b T3500b.hs -O -fasm >T3500b.comp.stderr 2>&1 Compile failed (status 256) errors were: [1 of 1] Compiling Main ( T3500b.hs, T3500b.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.9.20140907 for x86_64-unknown-linux): Simplifier ticks exhausted When trying RuleFired foldr/augment To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 12441 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Attempt to increase '''-fsimpl-tick-factor''' does not help copiling sample. Looks like infinite inlining pass. The test source itself: {{{#!hs {-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances #-} module Main where newtype Mu f = Mu (f (Mu f)) type family Id m type instance Id m = m instance Show (Id (f (Mu f))) => Show (Mu f) where show (Mu f) = show f showMu :: Mu (Either ()) -> String showMu = show item :: Mu (Either ()) item = Mu (Right (Mu (Left ()))) main = print (showMu item) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9565 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: | Architecture: x86_64 (amd64) Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: T3500b | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by carter): could this be an instance of the known issue about recursive types interacting with the inliner? https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/bugs.html see the second item there if i change the program to {{{ {-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances #-} module Main where newtype Mu f = Mu (f (Mu f)) type family Id m type instance Id m = m instance Show (Id (f (Mu f))) => Show (Mu f) where show (Mu f) = show f {-# NOINLINE show #-} showMu :: Mu (Either ()) -> String showMu = show item :: Mu (Either ()) item = Mu (Right (Mu (Left ()))) main = print (showMu item) }}} that is, I mark the show instance NOINLINE, the problem goes away. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9565#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: | Architecture: x86_64 (amd64) Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: T3500b | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by slyfox): Oh, I see. I propose to mark it as expect_broken for opt targets if noone objects. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9565#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: | Architecture: x86_64 (amd64) Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: T3500b | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by carter): I'm not sure, its in the test suite which means it was working before right? Or is this part of the suite that's only run on a slow validate? I'll try to dig in once I'm off my phone. I also may have run the test case incorrectly on my local machine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9565#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Resolution: | Keywords:
Operating System: | Architecture: x86_64 (amd64)
Unknown/Multiple | Difficulty: Unknown
Type of failure: Compile- | Blocked By:
time crash | Related Tickets:
Test Case: T3500b |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#9565: T3500b exhaust simplifier ticks (loops?) on WAY=optasm -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: fixed | Keywords: Operating System: | Architecture: x86_64 (amd64) Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: | simplCore/should_compile/T9565 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: T3500b => simplCore/should_compile/T9565 * resolution: => fixed Comment: I'm happy to say that this is fixed by the same patch as #9583. I've added a separate test case (compile only) since the purpose is different to the (identical) test for #3500. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9565#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC