Fixing Trac #9046 (Panic in GHCi when using :print).

Vitaly Bragilevsky bravit111 at gmail.com
Sun Jun 22 14:47:19 UTC 2014


Hello,

I am trying to fix the bug #9046 (Panic in GHCi when using :print).
I've discovered that It was introduced by this SPJ's commit (25 Nov 2013):
https://ghc.haskell.org/trac/ghc/changeset/a8ac471d435214dbdc1fa70f938c63128993a1db/ghc
and especially by this change:

-type QuantifiedType = ([TyVar], Type)   -- Make the free type
variables explicit
+type QuantifiedType = ([TyVar], Type)
+   -- Make the free type variables explicit
+   -- The returned Type should have no top-level foralls (I believe)

 quantifyType :: Type -> QuantifiedType
--- Generalize the type: find all free tyvars and wrap in the appropiate ForAll.
-quantifyType ty = (varSetElems (tyVarsOfType ty), ty)
+-- Generalize the type: find all free and forall'd tyvars
+-- and return them, together with the type inside, which
+-- should not be a forall type.
+--
+-- Thus (quantifyType (forall a. a->[b]))
+-- returns ([a,b], a -> [b])
+
+quantifyType ty = (varSetElems (tyVarsOfType rho), rho)
+  where
+    (_tvs, rho) = tcSplitForAllTys ty

While this change looks reasonable to me it breaks exploiting thunks
created by `:print` ghci's command
from polymorphic values. Before this change we could have:

$ ghci -fprint-explicit-foralls
GHCi, version 7.6.3.20130421: http://www.haskell.org/ghc/  :? for help
> :print length
length = (_t1::forall a. [a] -> Int)
> _t1 [1,2,3]
3

And now we have:
$ ghci -fprint-explicit-foralls
GHCi, version 7.8.2: http://www.haskell.org/ghc/  :? for help
> :print length
length = (_t1::[a] -> Int)
> _t1 [1,2,3]
ghc: panic! (the 'impossible' happened)
  (GHC version 7.8.2 for x86_64-unknown-linux):
        tcTyVarDetails a{tv arw} [tv]


This particular panic is caused by unification
(compiler/typecheck/TcUnify.lhs line 1042).
In case of `read` instead of `length` we get panic even earlier in
simplification (compiler/typecheck/TcSimplify line 85).

The concrete reason for the panic is wrong constructor used for tyvar
(TyVar instead of TcTyVar).

I see several ways to fix this:
1) rollback to forall-types in `:print` (requires change in
cvObtainTerm, RtClosureInspect.hs);
2) skolemise free tyvar to RuntimeUnk (it becomes TcTyVar then):
   a) in cvObtainTerm;
   b) somewhere before typechecking.

I can't decide the correct way to fix this bug or maybe there are
other alternatives.
Anyway I am ready to work on this though I need some advice.

With best regards,
Vitaly Bragilevsky


More information about the ghc-devs mailing list