[GHC] #8184: Compiler panic in the presence of cyclic imports

#8184: Compiler panic in the presence of cyclic imports -----------------------------------+--------------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time crash Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: 910 Blocked By: | Related Tickets: | -----------------------------------+--------------------------------------- A.hs {{{ #!haskell module A where import {-# SOURCE #-} B data X = X Y }}} B.hs-boot {{{ #!haskell module B where data Y }}} B.hs {{{ #!haskell module B where import A data Y = Y Int Int thing :: X -> a thing (X (Y a b)) = thing (X (Y a b)) }}} C.hs {{{ #!haskell module C where import A import B panic :: Int -> a panic x = thing (X (Y x x)) }}} Now try to compile module C: {{{ $ ghc-stage2 -O C [1 of 4] Compiling B[boot] ( B.hs-boot, B.o-boot ) [2 of 4] Compiling A ( A.hs, A.o ) [3 of 4] Compiling B ( B.hs, B.o ) [4 of 4] Compiling C ( C.hs, C.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.7.20130826 for x86_64-unknown-linux): applyTypeToArgs main:B.$wthing{v rsQ} [gid] @ a{tv ivX} [tv] ww_iwm{v} [lid] ww_iwn{v} [lid] a{tv ivX} [tv] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} I encountered this bug when attempting to compile GHC with GHC -O2 --make. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8184: Compiler panic in the presence of cyclic imports ---------------------------------------+----------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: 910 | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by parcs): Note that the panic doesn't occur when compiling each module separately in one-shot mode. The only difference seems to be that when compiled in one-shot mode, the worker for `thing` has the type {{{ #!haskell $wthing :: Int -> Int -> a }}} whereas when compiled in --make mode, it's {{{ #!haskell $wthing :: Y -> a }}} And judging by the panic message the compiler seems to attempt to apply `$wthing` to 2 Ints as if it had the former type. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8184: Compiler panic in the presence of cyclic imports ---------------------------------------+----------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: 910 | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by parcs): Digging deeper, the problem seems to be that in `WwLib.mkWWstr_one`, `deepSplitProductType_maybe y_type' returns `Nothing` when compiling `B`. But when compiling `C` (after re-typechecking the loop) it returns `Just y_datacon`. The immediate problem seem to lie in `WwLib.deepSplitProductType_maybe`: {{{ #!haskell deepSplitProductType_maybe :: Type -> Maybe (DataCon, [Type], [Type], Coercion) deepSplitProductType_maybe ty | let (ty1, co) = topNormaliseNewType ty `orElse` (ty, mkReflCo Representational ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 , Just con <- isDataProductTyCon_maybe tc -- ^ This pattern fails for Y when compiling A.hs (because Y looks empty then) -- and succeeds when compiling C (because the import loop has been -- re-typechecked by then). This discrepancy causes `WwLib.mkWWstr_one` to -- return a different worker type depending on whether one is compiling -- a module inside the loop or outside the loop. = Just (con, tc_args, dataConInstArgTys con tc_args, co) deepSplitProductType_maybe _ = Nothing }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8184: Compiler panic in the presence of cyclic imports ---------------------------------------+----------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: 910 | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by simonpj): Thanks. I too had a look at this yesterday and I know exactly what's going on: * When compiling B, the `TyCon` for X (which was built when compiling A) has a `DataCon` for X's constructor `X`. The type of that data con is `Y -> X`, but the `Y` is "abstract"; it has no data constructors yet, because it too necessarily was built when compiling A. * When building the wrapper for `thing` in B, we use the types to drive the w/w split. We unpack X and get a field of type Y, but it's the "old" Y. So `thing` gets only one level of unpacking, despite the rather obvious form of its RHS. * With `--make`, before compiling C we re-tyepcheck the `TyCons` in the module loop (see `GhcMake.reTypecheckLoop`), so now we have the "right" X. Then when we construct the wrapper for `thing` we can see the two-level unpacking. Net result: B and C differ on what the wrapper for `thing` looks like; disaster. If wrappers were exposed as INLINE things just like any other INLINE thing, there would be just one source of truth, namely the interface file for B. Currently we try to abbreviate the interface file, by making `thing` say "I have a wrapper and its worker is `$wthing`", and the importing module constructs the wrapper from that information plus its strictness info. It would actually be simpler not to attempt this abbreviation. Interface files would get a bit bigger, but there would be other savings. I might try that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8184: Compiler panic in the presence of cyclic imports ---------------------------------------+----------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: 910 | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by parcs): I noticed a different but perhaps related discrepancy when compiling each module separately in one-shot mode: {{{ $ rm *.hi *.hi-boot $ ghc-stage2 -O -c B.hs-boot $ ghc-stage2 -O -c A.hs $ ghc-stage2 -O -c B.hs $ ghc-stage2 --show-iface B.hi ... $wthing :: forall a. GHC.Types.Int -> GHC.Types.Int -> a {- Arity: 2, HasNoCafRefs, Strictness: b -} ... thing :: forall a. A.X -> a {- Arity: 1, HasNoCafRefs, Strictness: b, Inline: INLINE[0], Unfolding: Worker(ext): B.$wthing (arity 1) -} ... }}} The arity of `$wthing` is 1 according to the declaration of `thing`, but `$wthing`'s actual arity is 2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8184: Compiler panic in the presence of cyclic imports ---------------------------------------+----------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: 910 | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by parcs): Thanks for the detailed explanation by the way. Your explanation gave me an idea: What if, instead of retypechecking the module loop ''after'' compiling the last module in the loop, we purged the (potentially stale) interfaces of the modules within the loop ''before'' compiling the last module in the loop? Then as we simultaneously compile the last module in the loop, the necessary interfaces will have to be (re-)sucked in and (re-)typechecked. Does this make sense? I think this solution would eradicate this bug and other bugs like it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8184: Compiler panic in the presence of cyclic imports ---------------------------------------+----------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: 910 | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by parcs): Okay, so that is not as straightforward as it originally sounded since I forgot that home module interfaces are handled specially.. Still, this issue highlights a significant flaw in how module loops are compiled in --make mode. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8184: Compiler panic in the presence of cyclic imports ---------------------------------------+----------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: 910 | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by simonpj): Yes, indeed. It is a significant flaw. The thing is, a `TyCon` in GHC literally points to its `DataCons` and they literally point to their `Types` and they literally point to the `TyCons` mentioned in the type. So there is a big cyclic data structure here. It's very convenient to ''use'', but a pain to ''build''. If I knew an easy solution I'd have adopted it, but I don't (yet). However for this particular problem I think we can adopt the solution I outlined. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8184: Compiler panic in the presence of cyclic imports ---------------------------------------+----------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: 910 | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by simonpj): Interestingly, Nick Frisby's recent patch (in #7782) does exactly what I propose in comment 3 above. If you pull HEAD I think you'll find the bug is indeed fixed. Want to check. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8184: Compiler panic in the presence of cyclic imports ---------------------------------------+----------------------------------- Reporter: parcs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: 910 | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by parcs): Yep, the test case in the description now compiles and it's now again possible to build GHC with GHC --make -O2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8184: Compiler panic in the presence of cyclic imports
---------------------------------------+-----------------------------------
Reporter: parcs | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time crash | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: 910 | Blocked By:
| Related Tickets:
---------------------------------------+-----------------------------------
Comment (by Patrick Palka

#8184: Compiler panic in the presence of cyclic imports ---------------------------------------+----------------------------------- Reporter: parcs | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: T8184 | Difficulty: Unknown Blocking: 910 | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Changes (by parcs): * status: new => closed * testcase: => T8184 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8184#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC