Making compilation results deterministic (#4012)

Bartosz Nitka niteria at gmail.com
Mon Sep 14 17:04:29 UTC 2015


Hello,

For the past couple of weeks I've been working on making compilation
results deterministic.
What I'm focusing on right now is the interface file determinism, I don't
care about binaries being deterministic.

I'd like to give a status update and ask for some advice, since I'm running
into issues that I don't have a good way of solving.

The first question anyone might ask is how did nondeterminism creep into
the compiler. If we're compiling with a single thread there's no reason for
the computation to proceed in non deterministic way. I'm fairly certain
that the issue originates from lazy loading of interface files. Relevant
function:
https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/typecheck/TcRnMonad.hs;12098c2e70b2a432f4ed675ed72b53a396cb2842$1414-1421.
What happens is that if you already have an interface file for a target
you're trying to build the computation will proceed differently.

Why does lazy loading matter? As you load the interface file it needs to
get type-checked and that means it needs to pull some Uniques from a global
UniqSupply. It does that in different order resulting in different Unique
assignment. As far as I can tell, lazy loading is required for performance,
so I abandoned the idea of fixing it. I haven't looked at parallel
compilation yet, but I'd expect it to result in different Unique assignment
as well.

I believe up to this point we're ok. Uniques are non-deterministic, but it
shouldn't be a big deal. Uniques should be opaque enough to not affect the
order of computation, for example the order of binds considered. But they
aren't.

Uniques are used in different ways throughout the compiler and they end up
reordering things:

1) They have an `Ord` instance:
https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/basicTypes/Unique.hs;12098c2e70b2a432f4ed675ed72b53a396cb2842$190-195
.

So far the places it impacts the most are places that use
`stronglyConnCompFromEdgedVertices`, because Unique is used as a Node key
and the result depends on the order of Nodes being considered. Some
examples:
https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/simplCore/OccurAnal.hs;12b0bb6f15caa5b4b01d0330a7a8d23e3c10842c$183,646,681,846
https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/rename/RnSource.hs;12b0bb6f15caa5b4b01d0330a7a8d23e3c10842c$1365
(because Ord for Name uses Unique
https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/basicTypes/Name.hs;12b0bb6f15caa5b4b01d0330a7a8d23e3c10842c$410-411
)

I've tried to see what removing it would entail and the changes would be
far reaching: https://phabricator.haskell.org/P62.

2) VarEnv, NameEnv are implemented in terms of UniqFM, which is just
Data.IntMap with keys being the Unique integer values.

The way this bites us is that when UniqFM's get converted to a list they
end up being sorted on Unique value. This problem is more widespread than
the `stronglyConnCompFromEdgedVertices` issue, there's even a place where
it's implicitly depended on:
https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/nativeGen/RegAlloc/Liveness.hs;12b0bb6f15caa5b4b01d0330a7a8d23e3c10842c$837-842
.

I've tried to fix it by making `toList` return the elements in the order of
insertion (https://phabricator.haskell.org/P63), but that turned out to
have significant cost. My unscientific benchmark on aeson and text showed
10% compilation time increase. It's possible it can be done in less
expensive way, I've tried a couple of approaches, but all of them resulted
in 10% time increase. I've also considered to split UniqFM to two different
types, one that keeps the ordering, and one that can't `toList`, but I
suspect that the cut will not be clean, so I haven't tried that.

In some cases we got away with ordering things by OccName where needed: (
https://phabricator.haskell.org/D1073, https://phabricator.haskell.org/D1192),
but OccName's don't have to be unique in every case and if we try to make
them unique that would make them longer and probably result in even greater
slowdown.

The instance I've recently looked at doesn't look like it can be solved by
sorting by OccName.
The code that triggers the problem (simplified from haskell-src-exts):

  data Decl l = Boring l
    deriving (Eq)

  data Binds l
    = BDecls  l [Decl l]     -- ^ An ordinary binding group
    | IPBinds l [IPBind l]   -- ^ A binding group for implicit parameters
  deriving (Eq)

  data IPBind l = Boring2 l
  deriving (Eq)

The end result is:

4449fe3f8368a2c47b2499a1fb033b6a
  $fEqBinds_$c==$Binds :: Eq l => Binds l -> Binds l -> Bool
  {- Arity: 1, HasNoCafRefs, Strictness: <L,U(C(C1(U)),A)>,
     Unfolding: (\ @ l $dEq :: Eq l ->
                 let {
                   $dEq1 :: Eq (Decl l) = $fEqDecl @ l $dEq
                 } in
                 let {
                   $dEq2 :: Eq (IPBind l) = $fEqIPBind @ l $dEq
                 } in
                 \ ds :: Binds l ds1 :: Binds l ->
                 case ds of wild {
                   BDecls a1 a2
                   -> case ds1 of wild1 {
                        BDecls b1 b2
                        -> case == @ l $dEq a1 b1 of wild2 {
                             False -> False True -> $fEq[]_$c== @ (Decl l)
$dEq1 a2 b2 }
                        IPBinds ipv ipv1 -> False }
                   IPBinds a1 a2
                   -> case ds1 of wild1 {
                        BDecls ipv ipv1 -> False
                        IPBinds b1 b2
                        -> case == @ l $dEq a1 b1 of wild2 {
                             False -> False
                             True -> $fEq[]_$c== @ (IPBind l) $dEq2 a2 b2 }
} }) -}

vs

bb525bf8c0145a5379b3c29e8adb4b18
  $fEqBinds_$c==$Binds :: Eq l => Binds l -> Binds l -> Bool
  {- Arity: 1, HasNoCafRefs, Strictness: <L,U(C(C1(U)),A)>,
     Unfolding: (\ @ l $dEq :: Eq l ->
                 let {
                   $dEq1 :: Eq (IPBind l) = $fEqIPBind @ l $dEq
                 } in
                 let {
                   $dEq2 :: Eq (Decl l) = $fEqDecl @ l $dEq
                 } in
                 \ ds :: Binds l ds1 :: Binds l ->
                 case ds of wild {
                   BDecls a1 a2
                   -> case ds1 of wild1 {
                        BDecls b1 b2
                        -> case == @ l $dEq a1 b1 of wild2 {
                             False -> False True -> $fEq[]_$c== @ (Decl l)
$dEq2 a2 b2 }
                        IPBinds ipv ipv1 -> False }
                   IPBinds a1 a2
                   -> case ds1 of wild1 {
                        BDecls ipv ipv1 -> False
                        IPBinds b1 b2
                        -> case == @ l $dEq a1 b1 of wild2 {
                             False -> False
                             True -> $fEq[]_$c== @ (IPBind l) $dEq1 a2 b2 }
} }) -}


This happens because when desugaring dictionaries we do an SCC on Uniques
that ends up reordering lets (
https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/deSugar/DsBinds.hs;12b0bb6f15caa5b4b01d0330a7a8d23e3c10842c$835
)

Now all of the dictionaries have OccName of Eq. I could probably reach
deeper into the term to extract enough information (in this instance, the
constructor name) to get deterministic ordering, but this feels very ad-hoc
and I don't expect it to scale to the whole codebase.


Another problem with fixing things in this ad-hoc manner is keeping them
fixed. There's nothing preventing people from introducing nondeterminism.
One idea that makes it more testable is to test it with different
UniqSupply allocation patterns. I've found it useful to compare against
UniqSupply that starts at a big number and allocates in decreasing order.
Gray codes could be used to generate non-sequential order.


The reason I'm posting this is to get some ideas, because at this point I
feel stuck, I don't see a good way of achieving the end goal. I hope
someone with more intimate GHC knowledge can point out a wrong assumption
I've made or suggest an approach I haven't thought of.

Cheers,
Bartosz
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20150914/df7673f8/attachment-0001.html>


More information about the ghc-devs mailing list