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

Simon Marlow marlowsd at gmail.com
Wed Jul 2 08:20:00 UTC 2014


I'm not sure of the correct way to fix this either - Simon, what do you 
think?  This is a regression in 7.8 relative to 7.6 which unfortunately 
wasn't caught by the test suite.  The commit that broke this fixed 
something else, so it's not a simple matter of reverting it.

Vitaly, one concrete thing you can do right now is add a test case and 
mark it broken by #9046.

Cheers,
Simon

On 22/06/2014 15:47, Vitaly Bragilevsky wrote:
> 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
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://www.haskell.org/mailman/listinfo/ghc-devs
>


More information about the ghc-devs mailing list