[Git][ghc/ghc][master] Make splitAtList strict in its arguments

Marge Bot gitlab at gitlab.haskell.org
Tue Aug 11 00:24:14 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00
Make splitAtList strict in its arguments

Also fix its slightly wrong comment

Metric Decrease:
    T5030
    T12227
    T12545

- - - - -


1 changed file:

- compiler/GHC/Utils/Misc.hs


Changes:

=====================================
compiler/GHC/Utils/Misc.hs
=====================================
@@ -6,6 +6,7 @@
 {-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE TupleSections #-}
 {-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE MagicHash #-}
 
 {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
 
@@ -774,15 +775,18 @@ dropList _  xs@[] = xs
 dropList (_:xs) (_:ys) = dropList xs ys
 
 
--- | Given two lists xs=x0..xn and ys=y0..ym, return `splitAt n ys`.
+-- | Given two lists xs and ys, return `splitAt (length xs) ys`.
 splitAtList :: [b] -> [a] -> ([a], [a])
-splitAtList xs ys = go 0 xs ys
+splitAtList xs ys = go 0# xs ys
    where
       -- we are careful to avoid allocating when there are no leftover
       -- arguments: in this case we can return "ys" directly (cf #18535)
-      go _ _      []     = (ys, [])        -- len(ys) <= len(xs)
-      go n []     bs     = (take n ys, bs) -- = splitAt n ys
-      go n (_:as) (_:bs) = go (n+1) as bs
+      --
+      -- We make `xs` strict because in the general case `ys` isn't `[]` so we
+      -- will have to evaluate `xs` anyway.
+      go _  !_     []     = (ys, [])             -- length ys <= length xs
+      go n  []     bs     = (take (I# n) ys, bs) -- = splitAt n ys
+      go n  (_:as) (_:bs) = go (n +# 1#) as bs
 
 -- drop from the end of a list
 dropTail :: Int -> [a] -> [a]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/acf537f9fefa31883b7cb28ff61b837ab7f8a44a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/acf537f9fefa31883b7cb28ff61b837ab7f8a44a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200810/d7b41fec/attachment-0001.html>


More information about the ghc-commits mailing list