Skip to content
Snippets Groups Projects
Commit c016e6f7 authored by David Feuer's avatar David Feuer Committed by Herbert Valerio Riedel
Browse files

base: define `sequence = mapM id`

This avoids duplication in `GHC.Base`; originally, we had

  mapM f = sequence . map f

This led to excessive allocation in `cryptarithm2`. Defining

  sequence = mapM id

does not appear to cause any `nofib` problems.

Reviewed By: hvr

Differential Revision: https://phabricator.haskell.org/D470
parent e73ab541
No related branches found
No related tags found
No related merge requests found
......@@ -518,9 +518,8 @@ when p s = if p then s else pure ()
-- and collect the results.
sequence :: Monad m => [m a] -> m [a]
{-# INLINE sequence #-}
sequence ms = foldr k (return []) ms
where
k m m' = do { x <- m; xs <- m'; return (x:xs) }
sequence = mapM id
-- Note: [sequence and mapM]
-- | @'mapM' f@ is equivalent to @'sequence' . 'map' f@.
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
......@@ -529,6 +528,23 @@ mapM f as = foldr k (return []) as
where
k a r = do { x <- f a; xs <- r; return (x:xs) }
{-
Note: [sequence and mapM]
~~~~~~~~~~~~~~~~~~~~~~~~~
Originally, we defined
mapM f = sequence . map f
This relied on list fusion to produce efficient code for mapM, and led to
excessive allocation in cryptarithm2. Defining
sequence = mapM id
relies only on inlining a tiny function (id) and beta reduction, which tends to
be a more reliable aspect of simplification. Indeed, this does not lead to
similar problems in nofib.
-}
-- | Promote a function to a monad.
liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r
liftM f m1 = do { x1 <- m1; return (f x1) }
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment