
#14884: Type holes cause assertion failure in ghc-stage2 compiler during type checking -------------------------------------+------------------------------------- Reporter: sighingnow | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- ghc-stage2 panic! due to assertion failure when compiling the following code with `ghc-stage2 Bug.hs` {{{#!hs module Bug where x :: IO () x = _ print "abc" }}} Callstack: {{{ λ inplace\bin\ghc-stage2 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.5.20180225 for x86_64-unknown-mingw32): ASSERT failed! t_a4ec[tau:2] 2 1 Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler\utils\Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler\utils\Outputable.hs:1206:5 in ghc:Outputable assertPprPanic, called at compiler\\typecheck\\TcType.hs:1187:83 in ghc:TcType CallStack (from -prof): TcInteract.solve_loop (compiler\typecheck\TcInteract.hs:(247,9)-(254,44)) TcInteract.solveSimples (compiler\typecheck\TcInteract.hs:(241,5)-(243,21)) TcRnDriver.simplifyTop (compiler\typecheck\TcRnDriver.hs:408:25-39) TcRnDriver.tcRnSrcDecls (compiler\typecheck\TcRnDriver.hs:254:25-65) }}} The failed assertion is `checkTcLevelInvariant ctxt_tclvl tv_tclvl` in `isTouchableMetaTyVar`: {{{#!hs isTouchableMetaTyVar :: TcLevel -> TcTyVar -> Bool isTouchableMetaTyVar ctxt_tclvl tv | isTyVar tv -- See Note [Coercion variables in free variable lists] = ASSERT2( tcIsTcTyVar tv, ppr tv ) case tcTyVarDetails tv of MetaTv { mtv_tclvl = tv_tclvl } -> ASSERT2( checkTcLevelInvariant ctxt_tclvl tv_tclvl, ppr tv $$ ppr tv_tclvl $$ ppr ctxt_tclvl ) tv_tclvl `sameDepthAs` ctxt_tclvl _ -> False | otherwise = False }}} Notice that the ghc-stage1 compiler doesn't panic and report the type hole correctly. This seems a regression and I have checked that ghc-8.2.2 also works well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14884 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler