
#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