Does tyCoVarsOfTypesList guarantee a particular order?

Ryan Scott ryan.gl.scott at gmail.com
Wed Sep 5 14:07:31 UTC 2018


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
[2] Actually, I would use tyCoVarsOfTypesWellScoped, but dependency order
doesn't come into play in the example I gave above.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20180905/ad00d2b3/attachment.html>


More information about the ghc-devs mailing list