expandTypeSynonyms panics after kind equality patch
Simon Peyton Jones
simonpj at microsoft.com
Thu Jan 7 11:31:56 UTC 2016
Richard
I'm confused too.
The 'go' function in 'expandTypeSynonyms' didn't use to take a substitution, but now it does. I think you intend that
go subst ty = expand (substTy subst ty)
where 'go' is the new 'go' and 'expand' is 'expandTypeSynonyms'. Correct? So you are avoiding repeated traversal by carrying a substitution in with you.
It would be good to write down this invariant.
OK so suppose we have
new_go subst (T ty1 ty2)
where type T a = rhs. (Notice T has arity 1 but is applied to two args.)
Then we this should be equivalent to
expand (T (subst(ty1)) (subst(ty2))
which is
expand (rhs[a -> subst ty1] subst(ty2))
So instead of
go subst (TyConApp tc tys)
| Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys
= let subst' = unionTCvSubst subst (mkTopTCvSubst tenv) in
go subst' (mkAppTys rhs tys')
I'd expect to see
go subst (TyConApp tc tys)
| Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc
(map (go subst) tys)
= mkAppTys (go (mkTopTCvSubst tenv) rhs) tys'
Notice that I'm applying 'go subst' to 'tys' before giving the args to 'expandSynTyCon_maybe'.
Does that look right? What you have looks entirely inexplicable.
Simon
| -----Original Message-----
| From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Ömer
| Sinan Agacan
| Sent: 06 January 2016 16:34
| To: ghc-devs <ghc-devs at haskell.org>
| Subject: expandTypeSynonyms panics after kind equality patch
|
| My branch panicking during stage 2 build and when I tried to debug I
| realized the panicking function is `unionTCvSubst`, when called by
| `expandTypeSynonyms`.
| In my branch I'm doing some type-based transformations and I'm using
| `expandTypeSynonyms` on type of identifiers for that.
|
| According to git blame logs, the function `unionTCvSubst` was added
| with kind equality patch. The patch made this change in
| `expandTypeSynonyms`:
|
| - = go (mkAppTys (substTy (mkTopTvSubst tenv) rhs) tys')
| + = let subst' = unionTCvSubst subst (mkTopTCvSubst tenv) in
| + go subst' (mkAppTys rhs tys')
|
| Which is what's causing the panic. The exact place it's panicking
| during the
| stage2 build is when I call `expandTypeSynonyms` on type `TvSubstEnv`
| (i.e. in my transformation I get type of an id and it turns out to be
| TvSubstEnv, when I call `expandTypeSynonyms` on this type it panics)
|
| I figured this much but I don't understand type system details, so,
| does anyone here have any ideas what's going wrong here? Richard?
|
| Note that this panic happens even though I don't do any changes in
| types - I'm just looking at the types for some transformations but no
| changes on the types are done.
| _______________________________________________
| ghc-devs mailing list
| ghc-devs at haskell.org
| https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h
| askell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
| devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c2d9763ba60bc4a7
| 845d608d316b74402%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=hRlHPbg
| girbpZXO1Ei6jN%2bRV7UUl98pFg%2bMHGVzxtmU%3d
More information about the ghc-devs
mailing list