[GHC] #11276: GHC hangs/takes an exponential amount of time with simple program

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This was discovered when trying to compile xml-conduit. Here is the standalone test case with a few comments indicating how to make it compile. The program compiles with ghc-7.10.2 but fails with HEAD. {{{#!hs {-# LANGUAGE RankNTypes #-} module Hang where import Control.Monad import Data.Char data Event = EventBeginDocument | EventEndDocument | EventBeginDoctype | EventEndDoctype | EventInstruction | EventBeginElement | EventEndElement | EventContent Content | EventComment | EventCDATA data Content = ContentText String | ContentEntity String peek :: Monad m => Consumer a m (Maybe a) peek = undefined type Consumer i m r = forall o. ConduitM i o m r tag :: forall m a b c o . Monad m => ConduitM Event o m (Maybe c) tag = do _ <- dropWS return undefined where -- Add this and it works -- dropWS :: Monad m => ConduitM Event o m (Maybe Event) dropWS = do -- Swap these two lines and it works -- let x = undefined x <- peek let isWS = case x of -- Remove some of these and it works Just EventBeginDocument -> True Just EventEndDocument -> True Just EventBeginDoctype{} -> True Just EventEndDoctype -> True Just EventInstruction{} -> True Just EventBeginElement{} -> False Just EventEndElement{} -> False Just (EventContent (ContentText t)) | all isSpace t -> True | otherwise -> False Just (EventContent ContentEntity{}) -> False Just EventComment{} -> True Just EventCDATA{} -> False Nothing -> False if isWS then dropWS else return x -- Inlined Instances instance Functor (ConduitM i o m) where fmap f (ConduitM c) = ConduitM $ \rest -> c (rest . f) instance Applicative (ConduitM i o m) where pure x = ConduitM ($ x) {-# INLINE pure #-} (<*>) = ap {-# INLINE (<*>) #-} instance Monad (ConduitM i o m) where return = pure ConduitM f >>= g = ConduitM $ \h -> f $ \a -> unConduitM (g a) h instance Monad m => Functor (Pipe l i o u m) where fmap = liftM {-# INLINE fmap #-} instance Monad m => Applicative (Pipe l i o u m) where pure = Done {-# INLINE pure #-} (<*>) = ap {-# INLINE (<*>) #-} instance Monad m => Monad (Pipe l i o u m) where return = pure {-# INLINE return #-} HaveOutput p c o >>= fp = HaveOutput (p >>= fp) c o NeedInput p c >>= fp = NeedInput (p >=> fp) (c >=> fp) Done x >>= fp = fp x PipeM mp >>= fp = PipeM ((>>= fp) `liftM` mp) Leftover p i >>= fp = Leftover (p >>= fp) i newtype ConduitM i o m r = ConduitM { unConduitM :: forall b. (r -> Pipe i i o () m b) -> Pipe i i o () m b } data Pipe l i o u m r = HaveOutput (Pipe l i o u m r) (m ()) o | NeedInput (i -> Pipe l i o u m r) (u -> Pipe l i o u m r) | Done r | PipeM (m (Pipe l i o u m r)) | Leftover (Pipe l i o u m r) l }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 7.10.3 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: | -------------------------------------+------------------------------------- Changes (by mpickering): * priority: high => highest -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 7.10.3 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: | -------------------------------------+------------------------------------- Changes (by snoyberg): * cc: snoyberg (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 7.10.3 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: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => gkaracha Comment: Eek. This is another example of the new pattern-match checker falling into exponential behaviour. Workaround: `-fno-warn-overlapping-patterns -fno-warn-incomplete-patterns` George: here is another for your list Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 7.10.3 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 gkaracha): Replying to [ticket:11276 mpickering]:
This was discovered when trying to compile xml-conduit. Here is the standalone test case with a few comments indicating how to make it compile.
The program compiles with ghc-7.10.2 but fails with HEAD.
{{{#!hs -- Add this and it works -- dropWS :: Monad m => ConduitM Event o m (Maybe Event) }}}
Thanks for the comments! If you just add the signature it really does compile? This is a bit strange, since the check runs post-typechecking so I would expect to have the same signature inferred at this point so I would not expect it to make a difference. I'll have to take a closer look, thanks :) George -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 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: | -------------------------------------+------------------------------------- Changes (by mpickering): * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 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 mpickering): George, do you have any idea what is going on here? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 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 gkaracha): Replying to [comment:6 mpickering]:
George, do you have any idea what is going on here?
I have been busy these days with #11195, #11303 and #11245 so I did not have enough time to look into it. Fortunately they are all done now so #11276 is my main priority now, I hope to have some feedback to give tomorrow. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 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 gkaracha): Ha, finally! It took more than I expected but I found the source: I do not understand why but GHC wraps all patterns in `CoPat`s: {{{#!hs Just (EventBeginDocument |> <Event>_R) Just (EventEndDocument |> <Event>_R) ... }}} Hence, the following match of `translatePat` (in `deSugar/Check.hs`) is triggered: {{{#!hs CoPat wrapper p ty -> do ps <- translatePat p (xp,xe) <- mkPmId2FormsSM ty let g = mkGuard ps (HsWrap wrapper (unLoc xe)) return [xp,g] }}} This means that, e.g. for the first clause, instead of the *expected*: {{{ Just EventBeginDocument }}} The following is generated: {{{ Just (d2JK (EventBeginDocument <- d2JK)) }}} And like this, we end up with a bunch of guards which make the checker explode. The reason I had it translated like this is that `CoPat`s are used for data families, where we have the original and a representation type constructor. Dropping the `wrapper` would give a type error (while it shouldn't) because the two constructors are different so the guaird translation allowed me to match against `d2JK` using the source type (original tyCon) and then match the guard `(EventBeginDocument <- d2JK)` using the internal type (representation tyCon) and avoid the mix-up. It will need some tinkering but I think I can find a workaround. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: gkaracha
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.10.3
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 Ben Gamari

#11276: GHC hangs/takes an exponential amount of time with simple program
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: gkaracha
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.10.3
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 hvr):
Replying to [comment:10 Ben Gamari
In [changeset:"0acdcf2482d24903b504e6b34fa745ef855ff00d/ghc" 0acdcf24/ghc]
Merged to ghc-8.0 via c1acc2a92947f512b1a6a20019524af09266a2aa -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 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 simonpj): George: short term, can we just degrade gracefully for now, and do something that doesn't blow up, at the expense of maybe reporting fewer warnings? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 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 gkaracha): Hmmm, the problem appears only with data families right now I think. Dropping the wrapper in the general case does not help because we end up with non-satisfiable constraints. We could deactivate pm checking for matches that contain `CoPat`s but this goes beyond data families (as the original test case without the signature has shown). I am still trying some ideas but I do not know exactly how much time will I need or if they are going to work after all. What is the time frame? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: pattern | checker Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => pattern checker -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: pattern | checker, PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: pattern checker => pattern checker, PatternMatchWarnings -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: pattern | checker, PatternMatchWarnings 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 simonpj): Does Phab:D1795 fix this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: pattern | checker, PatternMatchWarnings 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 gkaracha): Replying to [comment:16 simonpj]:
Does Phab:D1795 fix this?
Yes, it does. The current limits are: {{{ test('T11276', compile_timeout_multiplier(0.01), compile, ['-fwarn- incomplete-patterns -fwarn-overlapping-patterns +RTS -M1G -RTS']) }}} and it passes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: patch Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: pattern | checker, PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1795 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D1795 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11276: GHC hangs/takes an exponential amount of time with simple program
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: gkaracha
Type: bug | Status: patch
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.10.3
Resolution: | Keywords: pattern
| checker, PatternMatchWarnings
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1795
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11276: GHC hangs/takes an exponential amount of time with simple program -------------------------------------+------------------------------------- Reporter: mpickering | Owner: gkaracha Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: pattern | checker, PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1795 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 6e23b68047a2c995562eba173fe9485cae18bff2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11276#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC