<div dir="ltr"><div dir="ltr"><div dir="ltr"><div dir="ltr"><div>Ah, I somehow forgot all about FreeKiTyVars. It turns out that the `freeKiTyVarsAllVars` function [1] is exactly what drives this behavior:</div><div><br>    freeKiTyVarsAllVars :: FreeKiTyVars -> [Located RdrName]<br>    freeKiTyVarsAllVars (FKTV { fktv_kis = kvs, fktv_tys = tvs }) = kvs ++ tvs<br></div><div><br></div><div>That's about as straightforward as it gets. Thanks!<br></div><div><br></div><div>Ryan S.</div><div>-----</div><div>[1] <a href="https://gitlab.haskell.org/ghc/ghc/blob/5c1f268e2744fab2d36e64c163858995451d7095/compiler/rename/RnTypes.hs#L1604-1605">https://gitlab.haskell.org/ghc/ghc/blob/5c1f268e2744fab2d36e64c163858995451d7095/compiler/rename/RnTypes.hs#L1604-1605</a><br></div></div></div></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Thu, Feb 14, 2019 at 12:46 PM Simon Peyton Jones <<a href="mailto:simonpj@microsoft.com">simonpj@microsoft.com</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">





<div lang="EN-GB">
<div class="gmail-m_-6651887728663558436WordSection1">
<p class="MsoNormal"><span style="font-size:12pt">See Note [Kind and type-variable binders] in RnTypes, and Note [Ordering of implicit variables].<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:12pt">And the data type FreeKiTyVars.<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:12pt"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:12pt">But NB: that in <a href="https://gitlab.haskell.org/ghc/ghc/merge_requests/361" target="_blank">
https://gitlab.haskell.org/ghc/ghc/merge_requests/361</a>, I argue that with this patch we can sweep all this away.<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:12pt"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:12pt">If we did, we’d probably end up with [j,a,k,b].  
<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:12pt"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:12pt">Perhaps that’s an ergonomic reason for retaining the current rather cumbersome code.  (Maybe it could be simplified.)<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:12pt"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-size:12pt">Simon<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-size:12pt"><u></u> <u></u></span></p>
<div style="border-color:currentcolor currentcolor currentcolor blue;border-style:none none none solid;border-width:medium medium medium 1.5pt;padding:0cm 0cm 0cm 4pt">
<div>
<div style="border-color:rgb(225,225,225) currentcolor currentcolor;border-style:solid none none;border-width:1pt medium medium;padding:3pt 0cm 0cm">
<p class="MsoNormal"><b><span lang="EN-US">From:</span></b><span lang="EN-US"> ghc-devs <<a href="mailto:ghc-devs-bounces@haskell.org" target="_blank">ghc-devs-bounces@haskell.org</a>>
<b>On Behalf Of </b>Ryan Scott<br>
<b>Sent:</b> 14 February 2019 15:35<br>
<b>To:</b> <a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a><br>
<b>Subject:</b> scopedSort and kind variable left-biasing<u></u><u></u></span></p>
</div>
</div>
<p class="MsoNormal"><u></u> <u></u></p>
<div>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6pt;margin-left:0cm">
Consider this function:<br>
<br>
    f :: Proxy (a :: j) -> Proxy (b :: k)<br>
<br>
If you just collect the free type variables of `f`'s type in left-to-right order, you'd be left with [a,j,b,k]. But the type of `f` is not `forall (a :: j) j (b :: k) k. Proxy a -> Proxy b`, as that would be ill scoped. `j` must come before `a`, since `j` appears
 in `a`'s kind, and similarly, `k` must come before `b`.<br>
<br>
Fortunately, GHC is quite smart about sorting free variables such that they respect dependency order. If you ask GHCi what the type of `f` is (with -fprint-explicit-foralls enabled), it will tell you this:<br>
<br>
    λ> :type +v f<br>
    f :: forall j k (a :: j) (b :: k). Proxy a -> Proxy b<br>
<br>
As expected, `j` appears before `a`, and `k` appears before `b`.<br>
<br>
In a different context, I've been trying to implement a type variable sorting algorithm similar to the one that GHC is using. My previous understanding was that the entirely of this sorting algorithm was implemented in `Type.scopedSort`. To test my understanding,
 I decided to write a program using the GHC API which directly uses `scopedSort` on the example above:<br>
<br>
    main :: IO ()<br>
    main = do<br>
      let tv :: String -> Int -> Type -> TyVar<br>
          tv n uniq ty = mkTyVar (mkSystemName (mkUniqueGrimily uniq) (mkTyVarOcc n)) ty<br>
          j = tv "j" 0 liftedTypeKind<br>
          a = tv "a" 1 (TyVarTy j)<br>
          k = tv "k" 2 liftedTypeKind<br>
          b = tv "b" 3 (TyVarTy k)<br>
          sorted = scopedSort [a, j, b, k]<br>
      putStrLn $ showSDocUnsafe $ ppr sorted<br>
<br>
To my surprise, however, running this program does /not/ give the answer [j,k,a,b], like what :type reported:<br>
<br>
    λ> main<br>
    [j_0, a_1, k_2, b_3]<br>
<br>
Instead, it gives the answer [j,a,k,b]! Strictly speaking, this answer meets the specification of ScopedSort, since it respects dependency order and preserves the left-to-right ordering of variables that don't depend on each other (i.e., `j` appears to the
 left of `k`, and `a` appears to the left of `b`). But it's noticeably different that what :type reports. The order that :type reports, [j,k,a,b], appears to bias kind variables to the left such that all kind variables (`j` and `k`) appear before any type variables
 (`a` and `b`).<br>
<br>
>From what I can tell, scopedSort isn't the full story here. That is, something else appears to be left-biasing the kind variables. My question is: which part of GHC is doing this left-biasing?<u></u><u></u></p>
</div>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6pt;margin-left:0cm">
<u></u> <u></u></p>
</div>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6pt;margin-left:0cm">
Ryan S.<u></u><u></u></p>
</div>
</div>
</div>
</div>
</div>

</blockquote></div>