[commit: ghc] master: Get rid of Traversable UniqFM and Foldable UniqFM (7e28e47)

git at git.haskell.org git at git.haskell.org
Tue May 10 14:14:48 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/7e28e47ca36e849ed104f5a13e0c08253b135fae/ghc

>---------------------------------------------------------------

commit 7e28e47ca36e849ed104f5a13e0c08253b135fae
Author: Bartosz Nitka <niteria at gmail.com>
Date:   Tue May 10 07:17:28 2016 -0700

    Get rid of Traversable UniqFM and Foldable UniqFM
    
    Both Traversable and Foldable can introduce non-determinism
    and because of typeclass overloading it's implicit and not
    obvious at the call site. This removes the instances, so that
    they can't accidentally be used.
    
    Test Plan: ./validate
    
    Reviewers: austin, goldfire, bgamari, simonmar, simonpj
    
    Reviewed By: simonpj
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2190
    
    GHC Trac Issues: #4012


>---------------------------------------------------------------

7e28e47ca36e849ed104f5a13e0c08253b135fae
 compiler/typecheck/TcExpr.hs |  5 ++++-
 compiler/utils/UniqFM.hs     | 23 ++++++++++++-----------
 2 files changed, 16 insertions(+), 12 deletions(-)

diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs
index a4c8d02..834287a 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -69,6 +69,7 @@ import Outputable
 import FastString
 import Control.Monad
 import Class(classTyCon)
+import UniqFM ( nonDetEltsUFM )
 import qualified GHC.LanguageExtensions as LangExt
 
 import Data.Function
@@ -575,7 +576,9 @@ tcExpr (HsStatic fvs expr) res_ty
                        ) $
             tcPolyExprNC expr expr_ty
         -- Check that the free variables of the static form are closed.
-        ; mapM_ checkClosedInStaticForm fvs
+        -- It's OK to use nonDetEltsUFM here as the only side effects of
+        -- checkClosedInStaticForm are error messages.
+        ; mapM_ checkClosedInStaticForm $ nonDetEltsUFM fvs
 
         -- Require the type of the argument to be Typeable.
         -- The evidence is not used, but asking the constraint ensures that
diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs
index ed82fee..590358a 100644
--- a/compiler/utils/UniqFM.hs
+++ b/compiler/utils/UniqFM.hs
@@ -22,10 +22,7 @@ of arguments of combining function.
 
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveTraversable #-}
-{-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
-{-# LANGUAGE StandaloneDeriving #-}
 {-# OPTIONS_GHC -Wall #-}
 
 module UniqFM (
@@ -64,7 +61,7 @@ module UniqFM (
         isNullUFM,
         lookupUFM, lookupUFM_Directly,
         lookupWithDefaultUFM, lookupWithDefaultUFM_Directly,
-        eltsUFM, keysUFM, splitUFM,
+        nonDetEltsUFM, eltsUFM, keysUFM, splitUFM,
         ufmToSet_Directly,
         ufmToList, ufmToIntMap,
         joinUFM, pprUniqFM, pprUFM, pluralUFM
@@ -77,8 +74,6 @@ import Compiler.Hoopl   hiding (Unique)
 
 import qualified Data.IntMap as M
 import qualified Data.IntSet as S
-import qualified Data.Foldable as Foldable
-import qualified Data.Traversable as Traversable
 import Data.Typeable
 import Data.Data
 #if __GLASGOW_HASKELL__ > 710
@@ -221,11 +216,13 @@ instance Monoid (UniqFM a) where
 ************************************************************************
 -}
 
-newtype UniqFM ele = UFM (M.IntMap ele)
-  deriving (Data, Eq, Functor, Traversable.Traversable,
-            Typeable)
 
-deriving instance Foldable.Foldable UniqFM
+newtype UniqFM ele = UFM (M.IntMap ele)
+  deriving (Data, Eq, Functor, Typeable)
+  -- We used to derive Traversable and Foldable, but they were nondeterministic
+  -- and not obvious at the call site. You can use explicit nonDetEltsUFM
+  -- and fold a list if needed.
+  -- See Note [Deterministic UniqFM] in UniqDFM to learn about determinism.
 
 emptyUFM = UFM M.empty
 isNullUFM (UFM m) = M.null m
@@ -306,6 +303,10 @@ anyUFM p (UFM m) = M.fold ((||) . p) False m
 allUFM :: (elt -> Bool) -> UniqFM elt -> Bool
 allUFM p (UFM m) = M.fold ((&&) . p) True m
 
+-- See Note [Deterministic UniqFM] to learn about nondeterminism
+nonDetEltsUFM :: UniqFM elt -> [elt]
+nonDetEltsUFM (UFM m) = M.elems m
+
 ufmToIntMap :: UniqFM elt -> M.IntMap elt
 ufmToIntMap (UFM m) = m
 
@@ -345,7 +346,7 @@ pprUFM :: ([a] -> SDoc) -- ^ The pretty printing function to use on the elements
        -> UniqFM a      -- ^ The things to be pretty printed
        -> SDoc          -- ^ 'SDoc' where the things have been pretty
                         -- printed
-pprUFM pp ufm = pp (eltsUFM ufm)
+pprUFM pp ufm = pp (nonDetEltsUFM ufm)
 
 -- | Determines the pluralisation suffix appropriate for the length of a set
 -- in the same way that plural from Outputable does for lists.



More information about the ghc-commits mailing list