[commit: ghc] wip/ggreif: Tweaks to brListMapM and brListFoldlM_ (3fca648)

git at git.haskell.org git at git.haskell.org
Mon Aug 3 21:50:03 UTC 2015


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

On branch  : wip/ggreif
Link       : http://ghc.haskell.org/trac/ghc/changeset/3fca648585349e0d42a330090536474475ef0a3f/ghc

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

commit 3fca648585349e0d42a330090536474475ef0a3f
Author: Gabor Greif <ggreif at gmail.com>
Date:   Mon Aug 3 23:50:42 2015 +0200

    Tweaks to brListMapM and brListFoldlM_


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

3fca648585349e0d42a330090536474475ef0a3f
 compiler/types/CoAxiom.hs | 7 +++----
 1 file changed, 3 insertions(+), 4 deletions(-)

diff --git a/compiler/types/CoAxiom.hs b/compiler/types/CoAxiom.hs
index 4380ca8..31f93d8 100644
--- a/compiler/types/CoAxiom.hs
+++ b/compiler/types/CoAxiom.hs
@@ -174,7 +174,7 @@ brListFoldr f x (FirstBranch b) = f b x
 brListFoldr f x (NextBranch h t) = f h (foldr f x t)
 
 brListMapM :: Monad m => (a -> m b) -> BranchList a br -> m [b]
-brListMapM f (FirstBranch b) = f b >>= \fb -> return [fb]
+brListMapM f (FirstBranch b) = f b >>= return . return
 brListMapM f (NextBranch h t) = do { fh <- f h
                                    ; ft <- mapM f t
                                    ; return (fh : ft) }
@@ -183,14 +183,13 @@ brListFoldlM_ :: forall a b m br. Monad m
               => (a -> b -> m a) -> a -> BranchList b br -> m ()
 brListFoldlM_ f z (FirstBranch b) = do { _ <- f z b
                                        ; return () }
-brListFoldlM_ f z (NextBranch h t) = do { z' <- f z h
-                                        ; _ <- go z' t
+brListFoldlM_ f z (NextBranch h t) = do { _ <- go z (h : t)
                                         ; return () }
    where go :: a -> [b] -> m a
          go acc [b]  = f acc b
          go acc (h : t) = do { fh <- f acc h
                              ; go fh t }
-         go _ _ = pprPanic "brListFoldlM_" empty
+         go _ _ = pprPanic "brListFoldlM_" empty -- dead code
 
 -- zipWith
 brListZipWith :: (a -> b -> c) -> BranchList a br1 -> BranchList b br2 -> [c]



More information about the ghc-commits mailing list