[Git][ghc/ghc][wip/sjakobi/nondetfolds] 2 commits: More comments

Simon Jakobi gitlab at gitlab.haskell.org
Thu Apr 2 11:58:20 UTC 2020



Simon Jakobi pushed to branch wip/sjakobi/nondetfolds at Glasgow Haskell Compiler / GHC


Commits:
5a8fc542 by Simon Jakobi at 2020-04-02T13:50:35+02:00
More comments

- - - - -
3e0f1411 by Simon Jakobi at 2020-04-02T13:57:17+02:00
Add references to Note [Deterministic UniqFM]

- - - - -


7 changed files:

- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/Types/Unique/DSet.hs
- compiler/GHC/Types/Var/Env.hs
- compiler/GHC/Types/Var/Set.hs
- compiler/typecheck/TcEvidence.hs
- compiler/typecheck/TcSimplify.hs
- compiler/utils/GraphOps.hs


Changes:

=====================================
compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
=====================================
@@ -555,7 +555,8 @@ delAssoc a m
         | Just aSet     <- lookupUFM  m a
         , m1            <- delFromUFM m a
         = nonDetStrictFoldUniqSet (\x m -> delAssoc1 x a m) m1 aSet
-          -- It's OK to use nonDetStrictFoldUFM here because deletion is commutative
+          -- It's OK to use a non-deterministic fold here because deletion is
+          -- commutative
 
         | otherwise     = m
 


=====================================
compiler/GHC/Types/Unique/DSet.hs
=====================================
@@ -98,6 +98,9 @@ uniqDSetIntersectUniqSet :: UniqDSet a -> UniqSet b -> UniqDSet a
 uniqDSetIntersectUniqSet xs ys
   = UniqDSet (udfmIntersectUFM (getUniqDSet xs) (getUniqSet ys))
 
+-- See Note [Deterministic UniqFM] to learn about nondeterminism.
+-- If you use this please provide a justification why it doesn't introduce
+-- nondeterminism.
 nonDetStrictFoldUniqDSet :: (a -> b -> b) -> b -> UniqDSet a -> b
 nonDetStrictFoldUniqDSet f acc (UniqDSet s) = nonDetStrictFoldUDFM f acc s
 


=====================================
compiler/GHC/Types/Var/Env.hs
=====================================
@@ -583,6 +583,9 @@ lookupDVarEnv = lookupUDFM
 foldDVarEnv :: (a -> b -> b) -> b -> DVarEnv a -> b
 foldDVarEnv = foldUDFM
 
+-- See Note [Deterministic UniqFM] to learn about nondeterminism.
+-- If you use this please provide a justification why it doesn't introduce
+-- nondeterminism.
 nonDetStrictFoldDVarEnv :: (a -> b -> b) -> b -> DVarEnv a -> b
 nonDetStrictFoldDVarEnv = nonDetStrictFoldUDFM
 


=====================================
compiler/GHC/Types/Var/Set.hs
=====================================
@@ -154,6 +154,9 @@ allVarSet = uniqSetAll
 mapVarSet :: Uniquable b => (a -> b) -> UniqSet a -> UniqSet b
 mapVarSet = mapUniqSet
 
+-- See Note [Deterministic UniqFM] to learn about nondeterminism.
+-- If you use this please provide a justification why it doesn't introduce
+-- nondeterminism.
 nonDetStrictFoldVarSet :: (Var -> a -> a) -> a -> VarSet -> a
 nonDetStrictFoldVarSet = nonDetStrictFoldUniqSet
 
@@ -292,6 +295,9 @@ minusDVarSet = minusUniqDSet
 dVarSetMinusVarSet :: DVarSet -> VarSet -> DVarSet
 dVarSetMinusVarSet = uniqDSetMinusUniqSet
 
+-- See Note [Deterministic UniqFM] to learn about nondeterminism.
+-- If you use this please provide a justification why it doesn't introduce
+-- nondeterminism.
 nonDetStrictFoldDVarSet :: (Var -> a -> a) -> a -> DVarSet -> a
 nonDetStrictFoldDVarSet = nonDetStrictFoldUniqDSet
 


=====================================
compiler/typecheck/TcEvidence.hs
=====================================
@@ -501,6 +501,9 @@ evBindMapBinds = foldEvBindMap consBag emptyBag
 foldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a
 foldEvBindMap k z bs = foldDVarEnv k z (ev_bind_varenv bs)
 
+-- See Note [Deterministic UniqFM] to learn about nondeterminism.
+-- If you use this please provide a justification why it doesn't introduce
+-- nondeterminism.
 nonDetStrictFoldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a
 nonDetStrictFoldEvBindMap k z bs = nonDetStrictFoldDVarEnv k z (ev_bind_varenv bs)
 
@@ -863,7 +866,7 @@ findNeededEvVars ev_binds seeds
   where
    also_needs :: VarSet -> VarSet
    also_needs needs = nonDetStrictFoldUniqSet add emptyVarSet needs
-     -- It's OK to use nonDetStrictFoldUFM here because we immediately
+     -- It's OK to use a non-deterministic fold here because we immediately
      -- forget about the ordering by creating a set
 
    add :: Var -> VarSet -> VarSet


=====================================
compiler/typecheck/TcSimplify.hs
=====================================
@@ -1863,6 +1863,8 @@ neededEvVars implic@(Implic { ic_given = givens
 
       ; let seeds1        = foldr add_implic_seeds old_needs implics
             seeds2        = nonDetStrictFoldEvBindMap add_wanted seeds1 ev_binds
+                            -- It's OK to use a non-deterministic fold here
+                            -- because add_wanted is commutative
             seeds3        = seeds2 `unionVarSet` tcvs
             need_inner    = findNeededEvVars ev_binds seeds3
             live_ev_binds = filterEvBindMap (needed_ev_bind need_inner) ev_binds


=====================================
compiler/utils/GraphOps.hs
=====================================
@@ -64,7 +64,7 @@ addNode k node graph
         -- add back conflict edges from other nodes to this one
         map_conflict =
           nonDetStrictFoldUniqSet
-            -- It's OK to use nonDetStrictFoldUFM here because the
+            -- It's OK to use a non-deterministic fold here because the
             -- operation is commutative
             (adjustUFM_C (\n -> n { nodeConflicts =
                                       addOneToUniqSet (nodeConflicts n) k}))
@@ -74,7 +74,7 @@ addNode k node graph
         -- add back coalesce edges from other nodes to this one
         map_coalesce =
           nonDetStrictFoldUniqSet
-            -- It's OK to use nonDetStrictFoldUFM here because the
+            -- It's OK to use a non-deterministic fold here because the
             -- operation is commutative
             (adjustUFM_C (\n -> n { nodeCoalesce =
                                       addOneToUniqSet (nodeCoalesce n) k}))
@@ -477,8 +477,8 @@ freezeNode k
                                 -- If the edge isn't actually in the coelesce set then just ignore it.
 
         fm2     = nonDetStrictFoldUniqSet (adjustUFM_C (freezeEdge k)) fm1
-                    -- It's OK to use nonDetStrictFoldUFM here because the operation
-                    -- is commutative
+                    -- It's OK to use a non-deterministic fold here because the
+                    -- operation is commutative
                         $ nodeCoalesce node
 
     in  fm2



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ebbd82602573a3313119b079e56ede716d93bab3...3e0f14115156921c5bb21e239542e0ad6646e701

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ebbd82602573a3313119b079e56ede716d93bab3...3e0f14115156921c5bb21e239542e0ad6646e701
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200402/c7fb7074/attachment-0001.html>


More information about the ghc-commits mailing list