I am seeing this panic while compiling GHC stage2,
ghc-stage1: panic! (the 'impossible' happened) (GHC version 8.1.20170124 for x86_64-unknown-linux): runtimeRepPrimRep typePrimRep (a :: TYPE k0) k0 Call stack: ?callStack, called at compiler/utils/Util.hs:1352:50 in ghc:Util prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1166:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1170:37 in ghc:Outputable pprPanic, called at compiler/simplStg/RepType.hs:360:5 in ghc:RepTypePlease report this as a GHC bug: http://www.haskell.org/ghc/reportabug<<ghc: 1038844096 bytes, 158 GCs, 21564561/73278928 avg/max bytes residency (8 samples), 148M in use, 0.000 INIT (0.000 elapsed), 1.113 MUT (1.125 elapsed), 0.935 GC (0.940 elapsed) :ghc>>compiler/ghc.mk:582: recipe for target 'compiler/stage2/build/StgCmmMonad.p_o' failed
This appears to be due to my enabling of profiling. build.mk contains,
ghc-stage1: panic! (the 'impossible' happened) (GHC version 8.1.20170124 for x86_64-unknown-linux): runtimeRepPrimRep typePrimRep (a :: TYPE k0) k0 Call stack: ?callStack, called at compiler/utils/Util.hs:1352:50 in ghc:Util prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1166:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1170:37 in ghc:Outputable pprPanic, called at compiler/simplStg/RepType.hs:358:5 in ghc:RepType runtimeRepPrimRep, called at compiler/simplStg/RepType.hs:340:5 in ghc:RepType kindPrimRep, called at compiler/simplStg/RepType.hs:303:18 in ghc:RepType typePrimRep, called at compiler/simplStg/RepType.hs:67:11 in ghc:RepType typePrimRepArgs, called at compiler/simplStg/RepType.hs:108:13 in ghc:RepType countFunRepArgs, called at compiler/basicTypes/Id.hs:570:19 in ghc:Id idFunRepArity, called at compiler/codeGen/StgCmmClosure.hs:334:13 in ghc:StgCmmClosure
So it seems that we somehow have an unsaturated application of (#,#) making it to CoreToStg. Usually saturated applications of a DataConWorkId will result in a StgConApp. However, since this isn't saturated we end up with an StgApp. More updates to come.
At this point I'm fairly convinced that this was introduced by the levity polymorphism work. While I'm still working out precisely what is going on, it seems that our conception of arity may be a bit inconsistent, meaning that we don't eta expand enough in CorePrep.
One thing that surprised me is the type of the worker for (#,#),
That is, it seems to me like the worker is missing RuntimeRep arguments. This seems especially suspicious in light of the fact that I see the RuntimeRep arguments instantiated at the application site (e.g. ticket:13233#comment:131533). Goldfire, am I missing something here?
Ahhh, I see what is happening here. CoreArity.mkEtaWW is refusing to eta expand the value-level arguments of (#,#) as they are levity polymorphic,
|otherwise-- We have an expression of arity > 0,-- but its type isn't a function, or a binder-- is levity-polymorphic=WARN(True,(pprorig_n<+>pprorig_ty)$$pprorig_expr)(getTCvInScopesubst,reverseeis)
Had I been compiling with DEBUG this would have been plainly obvious but I was lazily merely building with BuildFlavour=prof. Serves me right, I suppose.
Anyways, this is a little hairy. Indeed eta expanding here would be quite suspicious. Really, it seems like we never should have produced the lambda being scrutinised in ticket:13233#comment:131533 at all given that it is levity polymorphic. I'll have to look into where this is coming from.
At first glance there is nothing particularly alarming about this. However, note the tick around (#,#): this is quite bad since it cuts the (#,#) off from its RuntimeRep applications, making the whole expression appear much more polymorphic than it really is in CorePrep.cpeApp.
Specifically, we first collect_args on the whole expression yielding,
cpe_app then looks at the tick<getInfoDown> (#,#) to decide what to do next. Specifically, it wants to see a plain Var, but that's not what we have. Consequently we end up recursing via cpeArg, which will be deprived of knowledge of the RuntimeRep type applications.
It's difficult to say what the right solution here is. I have yet to look into how we end up with the tick scoping over only the constructor; it's possible that the tick was pushed in too far. More coming.
I do wonder whether collect_args is being too conservative here: it will only look through ticks where tickishPlace tickish == PlaceNonLam && tickish tickishScopesLike SoftScope. Even in the most restrictive tick placement type (PlaceRuntime) we allow ticks to be floated through type lambdas. Perhaps collect_args should continue to look through ticks, so long as there are no value-applications inside?
In general all of this tick business is terribly fragile since there is no strong invariant (as far as I know) dictating where they might appear. I wonder if it would be reasonable a put inplace a Core invariant (checked by CoreLint) stating that "a tick must not sit directly inside of a type abstraction, type application, or cast. That is, we would normalize all things of the form,
(tick<t> e) @ty --> tick<t> (e @ty)(tick<t> e) `cast` co --> tick<t> (e `cast` co)/\ty -> (tick<t> e) --> tick<t> (/\ty -> e)
It already seems like we try to do something along these lines, but it's not strongly checked.
Hmm, interesting... CoreUtils.mkTick actually does the exact opposite of what I suggest: it pushes ticks **into** type applications. This certainly explains my observations. Unfortunately there's no explanation given for why we want to do this.
Goldfire, it would be interesting to hear your opinion about the above two comments.
I have no opinion. This area of the compiler is a mystery to me. That levity-polymorphism check you discovered earlier was put there only by Simon guiding my hand.
It still sounds like you're on a brilliant chase, though... :)
I strongly agree that we should write down the invariants for ticks, and check them in Lint. Sadly I do not know what they are. The only people who do are Simon Marlow and Peter Wortmann.
I feel uneasy about the whole tick business being so ill-documented.
I strongly agree that we should write down the invariants for ticks
So just to write down what we discussed the other day:
I believe there are (or were) no invariants on where ticks can appear in Core. However, there's an invariant that (#,#) must be directly applied to its type arguments, with no intervening ticks. (maybe it's more general than this?). Core Lint should really check this invariant.
FWIW, here is a much easier way to trigger this panic that doesn't require profiling:
{-# LANGUAGE ScopedTypeVariables #-}{-# LANGUAGE TypeInType #-}{-# LANGUAGE UnboxedTuples #-}moduleBugwhereimportGHC.Exts(TYPE)classFoo(a::TYPErep)wherebar::forall(b::TYPErep2).(a->a->b)->a->a->bbaz::forall(a::TYPErep).Fooa=>a->a->(#a,a#)baz=bar(#,#)
$ ~/Software/ghc/inplace/bin/ghc-stage2 Bug.hs[1 of 1] Compiling Bug ( Bug.hs, Bug.o )ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.3.20170322 for x86_64-unknown-linux): runtimeRepPrimRep typePrimRep (a_12 :: TYPE k0_10) k0_10 Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1191:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1195:37 in ghc:Outputable pprPanic, called at compiler/simplStg/RepType.hs:360:5 in ghc:RepType
Interesting. This is certainly the same panic, but the cause here is much different. Previously we were falling victim to ticks getting put between an unboxed tuple type constructor and its applied RuntimeReps. In contrast, here we are seeing a call to runtimeRepPrimRep while generating code for,
tl;dr: Implementing this efficiently is non-obvious. But I think I found a way in the process of writing this comment.
So I finally sat down this morning to fix this. But I can't think of a way to do so reasonably efficiently.
The challenge is:
Figure out when an Id which hasNoBinding is used with levity polymorphic arguments.
The problem is that, in both the zonker and the desugarer (really, the only places to detect levity polymorphism problems), by the time we're looking at an Id, it's too late. We've lost all the context, including any type arguments (that is, HsWrappers) that will instantiate the Id's levity polymorphic polytype. We could do the usual thing and accumulate arguments as we descend, but that seems fragile within the complexity of HsSyn, needing to deal with HsWrap, sections, and other horrors. We could check the desugared expression, but when? And how to do so without unwrapping all the Apps that have accumulated? To solve that last question, we could add an extra return value to dsExpr stating when we're desugaring an applied hasNoBinding Id... but it's still unclear when to run the check.
My most promising idea was to check whenever desugaring an HsWrap, figuring that a use of a polymorphic hasNoBinding Id would always be directly within an HsWrap. If we cleverly use composition to avoid HsWrap foo (HsWrap bar ...), we can quickly detect when an HsWrap surrounds a hasNoBinding Id -- but only if the typechecker always puts such an Id in an HsWrap. Alas, since we have the lazy instantiation of TypeApplications, that's no longer true. If a polymorphic hasNoBinding Id is used as the argument to a higher-rank function, it's possible there will be no HsWrap. And insisting on instantiating hasNoBinding Ids right away means that these will no longer be usable with TypeApplications, which would be a shame.
Perhaps a small tweak on the above idea will work: dsExpr gets an additional parameter saying whether or not the expr being desugared is immediately wrapped in an HsWrap. If we find a HsVar with a levity-polymorphic hasNoBinding Id inside and we're not in an HsWrap, issue an error. Additionally, every time we desugar an HsWrap, check if it's immediately wrapping a hasNoBinding id; if so, so the levity polymorphism check, using the type of the desugared expression to do the check. This might just work. It's heavier than I'd like, but not unreasonably so.
I like it enough to implement. Thanks for listening. :)
RyanGlScott, did ticket:13233#comment:133965 come from user code? If not then we might just have to punt this on to 8.4.
It's only user code in the sense that I stumbled upon it independently while idly trying out levity polymorphism. I wouldn't be heartbroken if it didn't make it into 8.2.
I think this is a reasonable candidate for 8.2. Simon and I agree that the patch as submitted is a little smelly, but it works (modulo validation glitches). We have a plan for a better approach, but the better approach will have to wait until I free up.
The patch Ben just committed fixes this bug, but in a stopgap manner. We can do better.
Please merge this patch, but then reopen the ticket after merging.
(Below are mostly notes to self.)
There are two separate problems:
How to ascertain whether or not a primop is saturated during desugaring (or, possibly, earlier). Simon and I once thought that we could do this in the desugarer by decomposing nested HsApps, using a little stack data type to denote all the different ways a function could be applied (HsApp, HsWrap with the right wrapper, sections, tuple-sections, HsTypeApp, maybe more) uncovering what the function was underneath, and then checking how many parameters are supplied. But now, I think it's much better to do this in the type-checker, especially because the type-checker already decomposes nested HsApps. (See TcExpr.tcApp.) When it discovers what the function is, it can check whether the function is a hasNoBinding primop. If so, it can eta-expand as necessary (but only if necessary) and use a new piece of HsSyn to denote a saturated primop. (It will be a new invariant that no unsaturated primop passes the type-checker.) This seems better than redoing the stack type in the desugarer. The original problem in #13233 (closed) was around levity polymorphism. If we make this change in the type checker, then the existing levity polymorphism checks should just work. We'll have to be careful to make the HsSyn structure printable in the way a user expects, so that the levity-polymorphism error message doesn't talk about an argument the user didn't write.
How to make sure that saturated primops stay that way in Core. This would be a new check in Lint as well as new checks on any code that does eta-contraction. It has been suggested that levity-polymorphic primops desugar to a family of levity-monomorphic primops. This surely would work, but there doesn't seem to be benefit over a plan simply to keep primops eta-expanded always. Then, there's no worry about eta-contracting levity-polymorphic arguments.