<div dir="ltr"><div dir="ltr">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?</div><div dir="ltr"><br></div><div>Ryan S.<br></div></div>