The left to right ordering is guaranteed by RnTypes.extract<blah> functions.
See Note [Ordering of implicit variables]

I don’t think tyCoVarsOfTypesList makes any guarantees.

But it probably *could*.   If you look at FV.hs, you’ll see that it works 
right-to-left, putting ‘x’ on the front of the accumulating list the first time 
it encounters it.

So in tyCoVarsOfTypes [a,b]
we push b onto the list, then a.  Result a:b:[]

In in tyCoVarsOfTypes [a,b,a]
we push a on the list (the rightmost occurrence), then b, then we ignore the 
next occurrence of a.  Result: b:a:[].

You could add new guarantees I suppose.  But they aren’t there right now.

Simon

From: ghc-devs <ghc-devs-boun...@haskell.org> On Behalf Of Ryan Scott
Sent: 05 September 2018 15:08
To: ghc-devs@haskell.org
Subject: Does tyCoVarsOfTypesList guarantee a particular order?

tyCoVarsOfTypesList guarantees that it returns its answer in a deterministic 
order. For the longest time, I must have assumed that this order was left to 
right. However, it appears that my assumption was wrong! This can be 
demonstrated with this program:
    module Main where

    import Name
    import TyCoRep
    import TysPrim
    import Var

    main :: IO ()
    main = do
      putStrLn "(1)"
      print $ map (getOccString . tyVarName)
            $ tyCoVarsOfTypesList
              [TyVarTy alphaTyVar, TyVarTy betaTyVar]

      putStrLn "(2)"
      print $ map (getOccString . tyVarName)
            $ tyCoVarsOfTypesList
              [TyVarTy alphaTyVar, TyVarTy betaTyVar, TyVarTy alphaTyVar]

This gives the following output:

    (1)
    ["a","b"]
    (2)
    ["b","a"]

The first one makes total sense to me. The second, one however, does not. If 
the free variables of that list were returned in left-to-right order (or even 
right-to-left order!), then (2) should give the same answer as (1). Instead, it 
lists "b" _before_ "a", which I find incredibly baffling.

To explain why I care so much about this, we're currently trying to improve 
Haddock's logic for choosing when to put explicit `forall`s in front of types 
[1]. Our litmus test is this: if the order in which a user wrote the `forall`d 
variables differs from the order in which the free variables of the body would 
normally occur, then have Haddock display an explicit forall. I would have 
assumed that tyCoVarsOfTypesList [2] would be enough to determine the "normal" 
order of the free variables, but as the example above proves, this sometimes 
gives unexpected orderings when there are multiple occurrences of the same 
variable.

We are currently having to work around this issue [1] by implementing our own 
custom versions of tyCoFVsOfType and friends that accumulate variables in 
reverse order (and then reversing the list at the end!) to get the order we 
expect. This feels incredibly wasteful to me, so I'd like to know if there's a 
better way. In particular:

1. Is this behavior of tyCoVarsOfTypesList expected?
2. If not, should we change it?

Ryan S.
-----
[1] See 
https://github.com/haskell/haddock/pull/931<https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fhaskell%2Fhaddock%2Fpull%2F931&data=02%7C01%7Csimonpj%40microsoft.com%7C79995d7103ee4a30066308d6133901b7%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636717532892126908&sdata=Q%2F2vdira5ae1Y%2FEgXAADmN7D1HZYo1w1d00wlH%2FdDPg%3D&reserved=0>
[2] Actually, I would use tyCoVarsOfTypesWellScoped, but dependency order 
doesn't come into play in the example I gave above.
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Reply via email to