Collapsing HsForAllTy, again

Alan & Kim Zimmerman alan.zimm at gmail.com
Fri Apr 10 12:31:01 UTC 2015


Ok, I am making progress, when it is done I will put up a patch.

I figured I was probably posting too much, sorry all.

Alan

On Fri, Apr 10, 2015 at 2:08 PM, Simon Peyton Jones <simonpj at microsoft.com>
wrote:

>  You are describing code I cannot see.  Can you perhaps just work out
> what is happening and fix it?  Nothing very deep is here, I think.  If you
> get really stuck and cannot make progress then put it in a Phab patch and I
> will try to look.  But I’m struggling with time at the moment.
>
>
>
> Simon
>
>
>
> *From:* Alan & Kim Zimmerman [mailto:alan.zimm at gmail.com]
> *Sent:* 10 April 2015 13:05
>
> *To:* Simon Peyton Jones
> *Cc:* ghc-devs at haskell.org
> *Subject:* Re: Collapsing HsForAllTy, again
>
>
>
> And once the splitLHsForAllTy is sorted, this
>
> tc_inst_head :: HsType Name -> TcM TcType
> tc_inst_head (HsForAllTy _ _ hs_tvs hs_ctxt hs_ty)
>   = tcHsTyVarBndrs hs_tvs $ \ tvs ->
>     do { ctxt <- tcHsContext hs_ctxt
>        ; ty   <- tc_lhs_type hs_ty ekConstraint    -- Body for forall has
> kind Constraint
>        ; return (mkSigmaTy tvs ctxt ty) }
>
> results in
>
> libraries/base/Data/Monoid.hs:217:23:
>     Illegal constraint: Alternative f => Monoid (Alt f a)
>     In the instance declaration for ‘Alternative f => Monoid (Alt f a)’
>
> Alan
>
>
>
> On Fri, Apr 10, 2015 at 1:11 PM, Alan & Kim Zimmerman <alan.zimm at gmail.com>
> wrote:
>
>   It looks like
>
> splitLHsForAllTy
>     :: LHsType name
>     -> (LHsTyVarBndrs name, HsContext name, LHsType name)
> splitLHsForAllTy poly_ty
>   = case unLoc poly_ty of
>         HsParTy ty                -> splitLHsForAllTy ty
>         HsForAllTy _ _ tvs cxt ty -> (tvs, unLoc cxt, ty)
>         _                         -> (emptyHsQTvs, [], poly_ty)
>         -- The type vars should have been computed by now, even if they
> were implicit
>
> needs a recursive call for the HsForAllTy case, it now generates
>
> libraries/base/Data/Monoid.hs:217:10:
>     Malformed instance: forall f a. Alternative f => Monoid (Alt f a)
>
>   Alan
>
>
>
> On Fri, Apr 10, 2015 at 10:13 AM, Simon Peyton Jones <
> simonpj at microsoft.com> wrote:
>
>  Look at how instance declarations are parsed. If you look at Parser.y
> you’ll see that for
>
>
>
> instance (Eq a, Eq b) => Eq (a,b)
>
>
>
> we get (in effect)
>
>
>
> mkImplicitHsForAllTy (mkQualifiedHsForAllTy (Eq a, Eq b) (Eq (a,b))
>
>
>
> The outer mkImplicit.. is to ensure that there is always, in the end, a
> HsForAllTy around the whole thing, even around
>
> instance Eq a
>
> say.
>
>
>
> But we don’t actually want two nested HsForAllTys.  mk_forall_ty collapsed
> the two.
>
>
>
> But you don’t want that either.  So I think you should make
> mkImplictHsForAllTy do the test instead.  Its goal is to wrap a HsForallTy
> if there isn’t one already. So
>
>
>
> mkImplicitHsForAllTy (HsForAllTy exp tvs cxt ty)
>
>   = HsForAllTy exp’ tvs cxt ty
>
>   where
>
>     exp’ = case exp of
>
>              Qualified -> Implicit
>
>              _         -> exp
>
> mkImplicitHsForAllTy ty = mkHsForAllTy Implicit  []  (L loc _) ty
>
>
>
> should do the job.
>
>
>
> Incidentally, mkImplicitHsForAllTy should not take a ctxt argument.  If
> you have a non-empty context, use mkQualifiedHsForAllTy.  That means that
> in Convert you’ll need to use
>
>    mkHsForAllTy Implicit ctxt ty’
>
> instead of mkImplicitHsForAllTy
>
>
>
> Simon
>
>
>
> *From:* Alan & Kim Zimmerman [mailto:alan.zimm at gmail.com]
> *Sent:* 10 April 2015 08:02
> *To:* Simon Peyton Jones
> *Cc:* ghc-devs at haskell.org
> *Subject:* Re: Collapsing HsForAllTy, again
>
>
>
> If I replace it with
>
>
> mkHsForAllTy :: HsExplicitFlag -> [LHsTyVarBndr RdrName] -> LHsContext
> RdrName -> LHsType RdrName -> HsType RdrName
> -- Smart constructor for HsForAllTy
> -- mkHsForAllTy exp tvs (L _ []) ty = mk_forall_ty exp tvs ty
> mkHsForAllTy exp tvs (L _ []) ty = HsForAllTy exp Nothing (mkHsQTvs tvs)
> (L noSrcSpan []) ty
> mkHsForAllTy exp tvs ctxt     ty = HsForAllTy exp extra   (mkHsQTvs tvs)
> cleanCtxt        ty
>   where -- Separate the extra-constraints wildcard when present
>         (cleanCtxt, extra)
>           | (L l HsWildcardTy) <- ignoreParens (last (unLoc ctxt)) = (init
> `fmap` ctxt, Just l)
>           | otherwise = (ctxt, Nothing)
>         ignoreParens (L _ (HsParTy ty)) = ty -- TODO:AZ We lose the
> annotation here
>         ignoreParens ty                 = ty
>
>
> I get the following errors in the stage 2 compile (only first 3 shown here)
>
>
> libraries/ghc-prim/GHC/Classes.hs:52:19:
>     Malformed instance: (Eq a, Eq b) => Eq (a, b)
>
> libraries/ghc-prim/GHC/Classes.hs:53:19:
>     Malformed instance: (Eq a, Eq b, Eq c) => Eq (a, b, c)
>
> libraries/ghc-prim/GHC/Classes.hs:54:19:
>     Malformed instance: (Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d)
>
>  Alan
>
>
>
> On Fri, Apr 10, 2015 at 12:14 AM, Simon Peyton Jones <
> simonpj at microsoft.com> wrote:
>
>  Hmm.  I’m not sure what the motivation is either.  Try dropping it out
> and see if anything goes wrong.
>
>
> Simon
>
>
>
> *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of *Alan
> & Kim Zimmerman
> *Sent:* 09 April 2015 22:15
> *To:* ghc-devs at haskell.org
> *Subject:* Collapsing HsForAllTy, again
>
>
>
> With the help of Jan Stolarek I tracked down the HsForAllTy flattening to
>  `HsTypes.mk_forall_ty`.
>
> This function takes any nested HsForAllTy's where the top one does not
> have a context defined, and collapses them into a single one.
>
> I do not know what the motivation for this is, and if it perhaps speeds up
> or simplifies further compilation.
>
> But now that API Annotations have arrived, making sure we do not lose the
> annotations for the sub-HsForAllTy  causes significant gymnastics in the
> parser [1].
>
> So my question is, is there a good reason to continue doing this, given
> the trade-off in parser complexity.
>
> Regards
>
>   Alan
>
> [1]  https://phabricator.haskell.org/D833
>
>
>
>
>
>
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20150410/76a25fe7/attachment.html>


More information about the ghc-devs mailing list