[Git][ghc/ghc][wip/sjakobi/nondetfolds] 3 commits: Delete foldUniqDSet and foldDVarSet

Simon Jakobi gitlab at gitlab.haskell.org
Thu Apr 2 11:37:17 UTC 2020



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


Commits:
30721598 by Simon Jakobi at 2020-04-02T13:18:57+02:00
Delete foldUniqDSet and foldDVarSet

- - - - -
e4d38d7c by Simon Jakobi at 2020-04-02T13:26:24+02:00
Delete nonDetFoldUDFM, nonDetFoldUFM, nonDetFoldUniqSet,

... nonDetFoldUniqSet_Directly, nonDetFoldVarSet

- - - - -
ebbd8260 by Simon Jakobi at 2020-04-02T13:37:03+02:00
Comments

- - - - -


9 changed files:

- compiler/GHC/Core/Op/SetLevels.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Rename/Source.hs
- compiler/GHC/Stg/Lift/Analysis.hs
- compiler/GHC/Types/Unique/DFM.hs
- compiler/GHC/Types/Unique/DSet.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Unique/Set.hs
- compiler/GHC/Types/Var/Set.hs


Changes:

=====================================
compiler/GHC/Core/Op/SetLevels.hs
=====================================
@@ -1582,11 +1582,13 @@ placeJoinCeiling le@(LE { le_ctxt_lvl = lvl })
 maxFvLevel :: (Var -> Bool) -> LevelEnv -> DVarSet -> Level
 maxFvLevel max_me env var_set
   = nonDetStrictFoldDVarSet (maxIn max_me env) tOP_LEVEL var_set
+    -- It's OK to use a non-deterministic fold here because maxIn commutes.
 
 maxFvLevel' :: (Var -> Bool) -> LevelEnv -> TyCoVarSet -> Level
 -- Same but for TyCoVarSet
 maxFvLevel' max_me env var_set
   = nonDetStrictFoldUniqSet (maxIn max_me env) tOP_LEVEL var_set
+    -- It's OK to use a non-deterministic fold here because maxIn commutes.
 
 maxIn :: (Var -> Bool) -> LevelEnv -> InVar -> Level -> Level
 maxIn max_me (LE { le_lvl_env = lvl_env, le_env = id_env }) in_var lvl


=====================================
compiler/GHC/Core/Unify.hs
=====================================
@@ -659,8 +659,8 @@ niSubstTvSet :: TvSubstEnv -> TyCoVarSet -> TyCoVarSet
 -- This is used in the occurs check, before extending the substitution
 niSubstTvSet tsubst tvs
   = nonDetStrictFoldUniqSet (unionVarSet . get) emptyVarSet tvs
-  -- It's OK to nonDetStrictFoldUFM here because we immediately forget the
-  -- ordering by creating a set.
+  -- It's OK to use a non-deterministic fold here because we immediately forget
+  -- the ordering by creating a set.
   where
     get tv
       | Just ty <- lookupVarEnv tsubst tv


=====================================
compiler/GHC/Rename/Source.hs
=====================================
@@ -1423,7 +1423,7 @@ depAnalTyClDecls rdr_env kisig_fv_env ds_w_fvs
 toParents :: GlobalRdrEnv -> NameSet -> NameSet
 toParents rdr_env ns
   = nonDetStrictFoldUniqSet add emptyNameSet ns
-  -- It's OK to use nonDetStrictFoldUFM because we immediately forget the
+  -- It's OK to use a non-deterministic fold because we immediately forget the
   -- ordering by creating a set
   where
     add n s = extendNameSet s (getParent rdr_env n)


=====================================
compiler/GHC/Stg/Lift/Analysis.hs
=====================================
@@ -546,6 +546,7 @@ closureGrowth expander sizer group abs_ids = go
         newbies = abs_ids `minusDVarSet` clo_fvs'
         -- Lifting @f@ removes @f@ from the closure but adds all @newbies@
         cost = nonDetStrictFoldDVarSet (\id size -> sizer id + size) 0 newbies - n_occs
+        -- Using a non-deterministic fold is OK here because addition is commutative.
     go (RhsSk body_dmd body)
       -- The conservative assumption would be that
       --   1. Every RHS with positive growth would be called multiple times,


=====================================
compiler/GHC/Types/Unique/DFM.hs
=====================================
@@ -57,7 +57,6 @@ module GHC.Types.Unique.DFM (
 
         udfmToList,
         udfmToUfm,
-        nonDetFoldUDFM,
         nonDetStrictFoldUDFM,
         alwaysUnsafeUfmToUdfm,
     ) where
@@ -273,13 +272,10 @@ elemUDFM k (UDFM m _i) = M.member (getKey $ getUnique k) m
 foldUDFM :: (elt -> a -> a) -> a -> UniqDFM elt -> a
 foldUDFM k z m = foldr k z (eltsUDFM m)
 
--- | Performs a nondeterministic fold over the UniqDFM.
+-- | Performs a nondeterministic strict fold over the UniqDFM.
 -- It's O(n), same as the corresponding function on `UniqFM`.
 -- If you use this please provide a justification why it doesn't introduce
 -- nondeterminism.
-nonDetFoldUDFM :: (elt -> a -> a) -> a -> UniqDFM elt -> a
-nonDetFoldUDFM k z (UDFM m _i) = foldr k z $ map taggedFst $ M.elems m
-
 nonDetStrictFoldUDFM :: (elt -> a -> a) -> a -> UniqDFM elt -> a
 nonDetStrictFoldUDFM k z (UDFM m _i) = foldl' k' z m
   where


=====================================
compiler/GHC/Types/Unique/DSet.hs
=====================================
@@ -26,7 +26,7 @@ module GHC.Types.Unique.DSet (
         unionUniqDSets, unionManyUniqDSets,
         minusUniqDSet, uniqDSetMinusUniqSet,
         intersectUniqDSets, uniqDSetIntersectUniqSet,
-        foldUniqDSet, nonDetStrictFoldUniqDSet,
+        nonDetStrictFoldUniqDSet,
         elementOfUniqDSet,
         filterUniqDSet,
         sizeUniqDSet,
@@ -98,9 +98,6 @@ uniqDSetIntersectUniqSet :: UniqDSet a -> UniqSet b -> UniqDSet a
 uniqDSetIntersectUniqSet xs ys
   = UniqDSet (udfmIntersectUFM (getUniqDSet xs) (getUniqSet ys))
 
-foldUniqDSet :: (a -> b -> b) -> b -> UniqDSet a -> b
-foldUniqDSet c n (UniqDSet s) = foldUDFM c n s
-
 nonDetStrictFoldUniqDSet :: (a -> b -> b) -> b -> UniqDSet a -> b
 nonDetStrictFoldUniqDSet f acc (UniqDSet s) = nonDetStrictFoldUDFM f acc s
 


=====================================
compiler/GHC/Types/Unique/FM.hs
=====================================
@@ -56,7 +56,7 @@ module GHC.Types.Unique.FM (
         intersectUFM_C,
         disjointUFM,
         equalKeysUFM,
-        nonDetFoldUFM, nonDetStrictFoldUFM, foldUFM, nonDetFoldUFM_Directly,
+        nonDetStrictFoldUFM, foldUFM, nonDetFoldUFM_Directly,
         anyUFM, allUFM, seqEltsUFM,
         mapUFM, mapUFM_Directly,
         elemUFM, elemUFM_Directly,
@@ -318,9 +318,6 @@ nonDetKeysUFM (UFM m) = map getUnique $ M.keys m
 -- See Note [Deterministic UniqFM] to learn about nondeterminism.
 -- If you use this please provide a justification why it doesn't introduce
 -- nondeterminism.
-nonDetFoldUFM :: (elt -> a -> a) -> a -> UniqFM elt -> a
-nonDetFoldUFM k z (UFM m) = M.foldr k z m
-
 nonDetStrictFoldUFM :: (elt -> a -> a) -> a -> UniqFM elt -> a
 nonDetStrictFoldUFM k z (UFM m) = M.foldl' (flip k) z m
 


=====================================
compiler/GHC/Types/Unique/Set.hs
=====================================
@@ -42,9 +42,7 @@ module GHC.Types.Unique.Set (
         unsafeUFMToUniqSet,
         nonDetEltsUniqSet,
         nonDetKeysUniqSet,
-        nonDetFoldUniqSet,
         nonDetStrictFoldUniqSet,
-        nonDetFoldUniqSet_Directly
     ) where
 
 import GhcPrelude
@@ -164,18 +162,9 @@ nonDetKeysUniqSet = nonDetKeysUFM . getUniqSet'
 -- See Note [Deterministic UniqFM] to learn about nondeterminism.
 -- If you use this please provide a justification why it doesn't introduce
 -- nondeterminism.
-nonDetFoldUniqSet :: (elt -> a -> a) -> a -> UniqSet elt -> a
-nonDetFoldUniqSet c n (UniqSet s) = nonDetFoldUFM c n s
-
 nonDetStrictFoldUniqSet :: (elt -> a -> a) -> a -> UniqSet elt -> a
 nonDetStrictFoldUniqSet c n (UniqSet s) = nonDetStrictFoldUFM c n s
 
--- See Note [Deterministic UniqFM] to learn about nondeterminism.
--- If you use this please provide a justification why it doesn't introduce
--- nondeterminism.
-nonDetFoldUniqSet_Directly:: (Unique -> elt -> a -> a) -> a -> UniqSet elt -> a
-nonDetFoldUniqSet_Directly f n (UniqSet s) = nonDetFoldUFM_Directly f n s
-
 -- See Note [UniqSet invariant]
 mapUniqSet :: Uniquable b => (a -> b) -> UniqSet a -> UniqSet b
 mapUniqSet f = mkUniqSet . map f . nonDetEltsUniqSet


=====================================
compiler/GHC/Types/Var/Set.hs
=====================================
@@ -23,7 +23,7 @@ module GHC.Types.Var.Set (
         sizeVarSet, seqVarSet,
         elemVarSetByKey, partitionVarSet,
         pluralVarSet, pprVarSet,
-        nonDetFoldVarSet, nonDetStrictFoldVarSet,
+        nonDetStrictFoldVarSet,
 
         -- * Deterministic Var set types
         DVarSet, DIdSet, DTyVarSet, DTyCoVarSet,
@@ -37,7 +37,7 @@ module GHC.Types.Var.Set (
         intersectsDVarSet, disjointDVarSet,
         isEmptyDVarSet, delDVarSet, delDVarSetList,
         minusDVarSet,
-        foldDVarSet, nonDetStrictFoldDVarSet,
+        nonDetStrictFoldDVarSet,
         filterDVarSet, mapDVarSet,
         dVarSetMinusVarSet, anyDVarSet, allDVarSet,
         transCloDVarSet,
@@ -154,9 +154,6 @@ allVarSet = uniqSetAll
 mapVarSet :: Uniquable b => (a -> b) -> UniqSet a -> UniqSet b
 mapVarSet = mapUniqSet
 
-nonDetFoldVarSet :: (Var -> a -> a) -> a -> VarSet -> a
-nonDetFoldVarSet = nonDetFoldUniqSet
-
 nonDetStrictFoldVarSet :: (Var -> a -> a) -> a -> VarSet -> a
 nonDetStrictFoldVarSet = nonDetStrictFoldUniqSet
 
@@ -295,9 +292,6 @@ minusDVarSet = minusUniqDSet
 dVarSetMinusVarSet :: DVarSet -> VarSet -> DVarSet
 dVarSetMinusVarSet = uniqDSetMinusUniqSet
 
-foldDVarSet :: (Var -> a -> a) -> a -> DVarSet -> a
-foldDVarSet = foldUniqDSet
-
 nonDetStrictFoldDVarSet :: (Var -> a -> a) -> a -> DVarSet -> a
 nonDetStrictFoldDVarSet = nonDetStrictFoldUniqDSet
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/53a3ff77d6fec5cf71ed0cd6bbeb40646e26234a...ebbd82602573a3313119b079e56ede716d93bab3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/53a3ff77d6fec5cf71ed0cd6bbeb40646e26234a...ebbd82602573a3313119b079e56ede716d93bab3
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/b8e1abdf/attachment-0001.html>


More information about the ghc-commits mailing list