[commit: ghc] master: Remove splitEithers, use partitionEithers from base (5c804e5)

git at git.haskell.org git at git.haskell.org
Mon Mar 12 07:56:35 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/5c804e5de11c71e84e81c40a10c11baba04b15e1/ghc

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

commit 5c804e5de11c71e84e81c40a10c11baba04b15e1
Author: Ömer Sinan Ağacan <omeragacan at gmail.com>
Date:   Mon Mar 12 10:54:17 2018 +0300

    Remove splitEithers, use partitionEithers from base


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

5c804e5de11c71e84e81c40a10c11baba04b15e1
 compiler/cmm/Debug.hs           |  5 +++--
 compiler/ghci/ByteCodeGen.hs    |  3 ++-
 compiler/main/DriverPipeline.hs |  5 +++--
 compiler/rename/RnEnv.hs        |  3 ++-
 compiler/utils/Util.hs          | 10 +---------
 5 files changed, 11 insertions(+), 15 deletions(-)

diff --git a/compiler/cmm/Debug.hs b/compiler/cmm/Debug.hs
index c6aae69..044a000 100644
--- a/compiler/cmm/Debug.hs
+++ b/compiler/cmm/Debug.hs
@@ -35,7 +35,7 @@ import Outputable
 import PprCore         ()
 import PprCmmExpr      ( pprExpr )
 import SrcLoc
-import Util
+import Util            ( seqList )
 
 import Hoopl.Block
 import Hoopl.Collections
@@ -46,6 +46,7 @@ import Data.Maybe
 import Data.List     ( minimumBy, nubBy )
 import Data.Ord      ( comparing )
 import qualified Data.Map as Map
+import Data.Either   ( partitionEithers )
 
 -- | Debug information about a block of code. Ticks scope over nested
 -- blocks.
@@ -100,7 +101,7 @@ cmmDebugGen modLoc decls = map (blocksForScope Nothing) topScopes
       -- Analyse tick scope structure: Each one is either a top-level
       -- tick scope, or the child of another.
       (topScopes, childScopes)
-        = splitEithers $ map (\a -> findP a a) $ Map.keys blockCtxs
+        = partitionEithers $ map (\a -> findP a a) $ Map.keys blockCtxs
       findP tsc GlobalScope = Left tsc -- top scope
       findP tsc scp | scp' `Map.member` blockCtxs = Right (scp', tsc)
                     | otherwise                   = findP tsc scp'
diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs
index 90fcb6d..74168ac 100644
--- a/compiler/ghci/ByteCodeGen.hs
+++ b/compiler/ghci/ByteCodeGen.hs
@@ -73,6 +73,7 @@ import qualified Data.IntMap as IntMap
 import qualified FiniteMap as Map
 import Data.Ord
 import GHC.Stack.CCS
+import Data.Either ( partitionEithers )
 
 -- -----------------------------------------------------------------------------
 -- Generating byte code for a complete module
@@ -89,7 +90,7 @@ byteCodeGen hsc_env this_mod binds tycs mb_modBreaks
                 (const ()) $ do
         -- Split top-level binds into strings and others.
         -- See Note [generating code for top-level string literal bindings].
-        let (strings, flatBinds) = splitEithers $ do
+        let (strings, flatBinds) = partitionEithers $ do
                 (bndr, rhs) <- flattenBinds binds
                 return $ case exprIsTickedString_maybe rhs of
                     Just str -> Left (bndr, str)
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index 839f6d0..e631cbb 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -73,6 +73,7 @@ import Control.Monad
 import Data.List        ( isSuffixOf, intercalate )
 import Data.Maybe
 import Data.Version
+import Data.Either      ( partitionEithers )
 
 -- ---------------------------------------------------------------------------
 -- Pre-process
@@ -453,7 +454,7 @@ linkingNeeded dflags staticLink linkables pkg_deps = do
         -- first check object files and extra_ld_inputs
         let extra_ld_inputs = [ f | FileOption _ f <- ldInputs dflags ]
         e_extra_times <- mapM (tryIO . getModificationUTCTime) extra_ld_inputs
-        let (errs,extra_times) = splitEithers e_extra_times
+        let (errs,extra_times) = partitionEithers e_extra_times
         let obj_times =  map linkableTime linkables ++ extra_times
         if not (null errs) || any (t <) obj_times
             then return True
@@ -469,7 +470,7 @@ linkingNeeded dflags staticLink linkables pkg_deps = do
         if any isNothing pkg_libfiles then return True else do
         e_lib_times <- mapM (tryIO . getModificationUTCTime)
                           (catMaybes pkg_libfiles)
-        let (lib_errs,lib_times) = splitEithers e_lib_times
+        let (lib_errs,lib_times) = partitionEithers e_lib_times
         if not (null lib_errs) || any (t <) lib_times
            then return True
            else checkLinkInfo dflags pkg_deps exe_file
diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs
index 1d9dcfa..600b564 100644
--- a/compiler/rename/RnEnv.hs
+++ b/compiler/rename/RnEnv.hs
@@ -79,6 +79,7 @@ import RnUnbound
 import RnUtils
 import Data.Maybe (isJust)
 import qualified Data.Semigroup as Semi
+import Data.Either      ( partitionEithers )
 
 {-
 *********************************************************
@@ -1436,7 +1437,7 @@ lookupLocalTcNames :: HsSigCtxt -> SDoc -> RdrName -> RnM [(RdrName, Name)]
 -- See Note [Fixity signature lookup]
 lookupLocalTcNames ctxt what rdr_name
   = do { mb_gres <- mapM lookup (dataTcOccs rdr_name)
-       ; let (errs, names) = splitEithers mb_gres
+       ; let (errs, names) = partitionEithers mb_gres
        ; when (null names) $ addErr (head errs) -- Bleat about one only
        ; return names }
   where
diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs
index a4520ed..d0a38ec 100644
--- a/compiler/utils/Util.hs
+++ b/compiler/utils/Util.hs
@@ -25,7 +25,7 @@ module Util (
 
         mapFst, mapSnd, chkAppend,
         mapAndUnzip, mapAndUnzip3, mapAccumL2,
-        nOfThem, filterOut, partitionWith, splitEithers,
+        nOfThem, filterOut, partitionWith,
 
         dropWhileEndLE, spanEnd,
 
@@ -296,14 +296,6 @@ partitionWith f (x:xs) = case f x of
                          Right c -> (bs, c:cs)
     where (bs,cs) = partitionWith f xs
 
-splitEithers :: [Either a b] -> ([a], [b])
--- ^ Teases a list of 'Either's apart into two lists
-splitEithers [] = ([],[])
-splitEithers (e : es) = case e of
-                        Left x -> (x:xs, ys)
-                        Right y -> (xs, y:ys)
-    where (xs,ys) = splitEithers es
-
 chkAppend :: [a] -> [a] -> [a]
 -- Checks for the second argument being empty
 -- Used in situations where that situation is common



More information about the ghc-commits mailing list