Ah, I somehow forgot all about FreeKiTyVars. It turns out that the `freeKiTyVarsAllVars` function [1] is exactly what drives this behavior:
freeKiTyVarsAllVars :: FreeKiTyVars -> [Located RdrName] freeKiTyVarsAllVars (FKTV { fktv_kis = kvs, fktv_tys = tvs }) = kvs ++ tvs That's about as straightforward as it gets. Thanks! Ryan S. ----- [1] https://gitlab.haskell.org/ghc/ghc/blob/5c1f268e2744fab2d36e64c163858995451d7095/compiler/rename/RnTypes.hs#L1604-1605 On Thu, Feb 14, 2019 at 12:46 PM Simon Peyton Jones <simo...@microsoft.com> wrote: > See Note [Kind and type-variable binders] in RnTypes, and Note [Ordering > of implicit variables]. > > And the data type FreeKiTyVars. > > > > But NB: that in https://gitlab.haskell.org/ghc/ghc/merge_requests/361, I > argue that with this patch we can sweep all this away. > > > > If we did, we’d probably end up with [j,a,k,b]. > > > > Perhaps that’s an ergonomic reason for retaining the current rather > cumbersome code. (Maybe it could be simplified.) > > > > Simon > > > > *From:* ghc-devs <ghc-devs-boun...@haskell.org> *On Behalf Of *Ryan Scott > *Sent:* 14 February 2019 15:35 > *To:* ghc-devs@haskell.org > *Subject:* scopedSort and kind variable left-biasing > > > > Consider this function: > > f :: Proxy (a :: j) -> Proxy (b :: k) > > 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`. > > 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: > > λ> :type +v f > f :: forall j k (a :: j) (b :: k). Proxy a -> Proxy b > > As expected, `j` appears before `a`, and `k` appears before `b`. > > 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: > > main :: IO () > main = do > let tv :: String -> Int -> Type -> TyVar > tv n uniq ty = mkTyVar (mkSystemName (mkUniqueGrimily uniq) > (mkTyVarOcc n)) ty > j = tv "j" 0 liftedTypeKind > a = tv "a" 1 (TyVarTy j) > k = tv "k" 2 liftedTypeKind > b = tv "b" 3 (TyVarTy k) > sorted = scopedSort [a, j, b, k] > putStrLn $ showSDocUnsafe $ ppr sorted > > To my surprise, however, running this program does /not/ give the answer > [j,k,a,b], like what :type reported: > > λ> main > [j_0, a_1, k_2, b_3] > > 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`). > > 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? > > > > Ryan S. >
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs