[GHC] #15630: panic! Simplifier ticks exhausted

#15630: panic! Simplifier ticks exhausted --------------------------------------+--------------------------------- Reporter: micahshahn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Windows Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- Compiling the following with -O2 causes a panic. {{{#!hs module GHCPanic where data IValue = IDefault | IInt Int | IBlob String (?) :: Applicative m => (IValue -> m a) -> IValue -> m (Maybe a) (?) _ IDefault = pure Nothing (?) p x = Just <$> p x getInt :: IValue -> Either () Int getInt (IInt i) = Right i getInt v = Left () getString :: IValue -> Either () String getString (IBlob b) = Right $ b getString v = Left () (<+>) :: Applicative m => (m (a -> b), [IValue]) -> (IValue -> m a) -> (m b, [IValue]) (<+>) (f, (v:vs)) p = (f <*> (p v), vs) data TestStructure = TestStructure { _param1 :: Int , _param2 :: Maybe String , _param3 :: Maybe Int , _param4 :: Maybe String , _param5 :: Maybe Int , _param6 :: Maybe Int , _param7 :: Maybe String , _param8 :: Maybe String , _param9 :: Maybe Int , _param10 :: Maybe Int , _param11 :: Maybe String , _param12 :: Maybe String , _param13 :: Maybe Int , _param14 :: Maybe Int , _param15 :: Maybe String } getMenuItem :: [IValue] -> Either () TestStructure getMenuItem vs = fst $ (pure TestStructure, vs) <+> getInt <+> (getString ?) <+> (getInt ?) <+> (getString ?) <+> (getInt ?) <+> (getInt ?) <+> (getString ?) <+> (getString ?) <+> (getInt ?) <+> (getInt ?) <+> (getString ?) <+> (getString ?) <+> (getInt ?) <+> (getInt ?) <+> (getString ?) }}} {{{ ghc.exe: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-mingw32): Simplifier ticks exhausted When trying UnfoldingDone $j_s1y9 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: 71323 Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler\utils\Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler\utils\Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler\simplCore\SimplMonad.hs:199:31 in ghc:SimplMonad }}} This seems similar to #8319 which was marked as being fixed. It compiles (albeit very very slowly!) if I remove the last parameter and the last application of (<+>). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15630 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15630: panic! Simplifier ticks exhausted ---------------------------------+-------------------------------------- Reporter: micahshahn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by osa1): * version: 8.2.2 => 8.5 * milestone: 8.6.1 => Comment: Confirmed on GHC HEAD and 8.6 beta. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15630#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15630: panic! Simplifier ticks exhausted ---------------------------------+-------------------------------------- Reporter: micahshahn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by simonpj): I strongly suspect that this is another example of #13253. Look at the example in `bad.hs` on that ticket. We know exactly what is going wrong -- see the comment stream. I've had a fix pending in my tree for months, but I keep getting pre- empted. Your new ticket will help incentivise me. Is it mission critical for you? Putting NOINLINE on `<+>` might well fix it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15630#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15630: panic! Simplifier ticks exhausted ---------------------------------+-------------------------------------- Reporter: micahshahn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by micahshahn): It's not mission critical for me at all - I have a lot of these kind of DAL structures to write so I think I'll end up writing a custom generic typeclass derivation for them with a more straightforward implementation. I figured it was worth a write up in case we weren't aware of this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15630#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15630: panic! Simplifier ticks exhausted ---------------------------------+-------------------------------------- Reporter: micahshahn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by simonpj): Indeed v helpful to have a concrete, small, example. Thanks -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15630#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15630: panic! Simplifier ticks exhausted ---------------------------------+-------------------------------------- Reporter: micahshahn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by tdammers): Did some quick testing; `{-# NOINLINE (<+>) #-}` does "fix" the problem (bringing compilation time for the example here down from 8 minutes to less than one second); however, the patch from https://ghc.haskell.org/trac/ghc/ticket/13253#comment:24 doesn't seem to make a difference. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15630#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC