summaryrefslogtreecommitdiff
path: root/libraries/base
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base')
-rw-r--r--libraries/base/Control/Monad.hs2
-rw-r--r--libraries/base/Data/OldList.hs28
-rw-r--r--libraries/base/GHC/List.hs4
3 files changed, 34 insertions, 0 deletions
diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 75bc2b2db3..fbdb99e5f4 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -191,6 +191,8 @@ forever a = let a' = a *> a' in a'
-- data structures or a state monad.
mapAndUnzipM :: (Applicative m) => (a -> m (b,c)) -> [a] -> m ([b], [c])
{-# INLINE mapAndUnzipM #-}
+-- Inline so that fusion with 'unzip' and 'traverse' has a chance to fire.
+-- See Note [Inline @unzipN@ functions] in GHC/OldList.hs.
mapAndUnzipM f xs = unzip <$> traverse f xs
-- | The 'zipWithM' function generalizes 'zipWith' to arbitrary applicative functors.
diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs
index 559823c4bd..132ee14673 100644
--- a/libraries/base/Data/OldList.hs
+++ b/libraries/base/Data/OldList.hs
@@ -929,8 +929,27 @@ foldr7_left _ z _ _ _ _ _ _ _ _ = z
#-}
+{-
+
+Note [Inline @unzipN@ functions]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+The inline principle for @unzip{4,5,6,7}@ is the same as 'unzip'/'unzip3' in
+"GHC.List".
+The 'unzip'/'unzip3' functions are inlined so that the `foldr` with which they
+are defined has an opportunity to fuse.
+
+As such, since there are not any differences between 2/3-ary 'unzip' and its
+n-ary counterparts below aside from the number of arguments, the `INLINE`
+pragma should be replicated in the @unzipN@ functions below as well.
+
+-}
+
-- | The 'unzip4' function takes a list of quadruples and returns four
-- lists, analogous to 'unzip'.
+{-# INLINE unzip4 #-}
+-- Inline so that fusion with `foldr` has an opportunity to fire.
+-- See Note [Inline @unzipN@ functions] above.
unzip4 :: [(a,b,c,d)] -> ([a],[b],[c],[d])
unzip4 = foldr (\(a,b,c,d) ~(as,bs,cs,ds) ->
(a:as,b:bs,c:cs,d:ds))
@@ -938,6 +957,9 @@ unzip4 = foldr (\(a,b,c,d) ~(as,bs,cs,ds) ->
-- | The 'unzip5' function takes a list of five-tuples and returns five
-- lists, analogous to 'unzip'.
+{-# INLINE unzip5 #-}
+-- Inline so that fusion with `foldr` has an opportunity to fire.
+-- See Note [Inline @unzipN@ functions] above.
unzip5 :: [(a,b,c,d,e)] -> ([a],[b],[c],[d],[e])
unzip5 = foldr (\(a,b,c,d,e) ~(as,bs,cs,ds,es) ->
(a:as,b:bs,c:cs,d:ds,e:es))
@@ -945,6 +967,9 @@ unzip5 = foldr (\(a,b,c,d,e) ~(as,bs,cs,ds,es) ->
-- | The 'unzip6' function takes a list of six-tuples and returns six
-- lists, analogous to 'unzip'.
+{-# INLINE unzip6 #-}
+-- Inline so that fusion with `foldr` has an opportunity to fire.
+-- See Note [Inline @unzipN@ functions] above.
unzip6 :: [(a,b,c,d,e,f)] -> ([a],[b],[c],[d],[e],[f])
unzip6 = foldr (\(a,b,c,d,e,f) ~(as,bs,cs,ds,es,fs) ->
(a:as,b:bs,c:cs,d:ds,e:es,f:fs))
@@ -952,6 +977,9 @@ unzip6 = foldr (\(a,b,c,d,e,f) ~(as,bs,cs,ds,es,fs) ->
-- | The 'unzip7' function takes a list of seven-tuples and returns
-- seven lists, analogous to 'unzip'.
+{-# INLINE unzip7 #-}
+-- Inline so that fusion with `foldr` has an opportunity to fire.
+-- See Note [Inline @unzipN@ functions] above.
unzip7 :: [(a,b,c,d,e,f,g)] -> ([a],[b],[c],[d],[e],[f],[g])
unzip7 = foldr (\(a,b,c,d,e,f,g) ~(as,bs,cs,ds,es,fs,gs) ->
(a:as,b:bs,c:cs,d:ds,e:es,f:fs,g:gs))
diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs
index 8f03ce3a08..d9b32ea9df 100644
--- a/libraries/base/GHC/List.hs
+++ b/libraries/base/GHC/List.hs
@@ -1128,12 +1128,16 @@ zipWith3FB cons func = \a b c r -> (func a b c) `cons` r
-- and a list of second components.
unzip :: [(a,b)] -> ([a],[b])
{-# INLINE unzip #-}
+-- Inline so that fusion `foldr` has an opportunity to fire.
+-- See Note [Inline @unzipN@ functions] in GHC/OldList.hs.
unzip = foldr (\(a,b) ~(as,bs) -> (a:as,b:bs)) ([],[])
-- | The 'unzip3' function takes a list of triples and returns three
-- lists, analogous to 'unzip'.
unzip3 :: [(a,b,c)] -> ([a],[b],[c])
{-# INLINE unzip3 #-}
+-- Inline so that fusion `foldr` has an opportunity to fire.
+-- See Note [Inline @unzipN@ functions] in GHC/OldList.hs.
unzip3 = foldr (\(a,b,c) ~(as,bs,cs) -> (a:as,b:bs,c:cs))
([],[],[])