[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Api Annotations : Adjust SrcSpans for prefix bang (!).

Marge Bot gitlab at gitlab.haskell.org
Mon Aug 10 18:23:25 UTC 2020



 Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00
Api Annotations : Adjust SrcSpans for prefix bang (!).

And prefix ~

(cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb)

- - - - -
77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00
Avoid allocations in `splitAtList` (#18535)

As suspected by @simonpj in #18535, avoiding allocations in
`GHC.Utils.Misc.splitAtList` when there are no leftover arguments is
beneficial for performance:

   On CI validate-x86_64-linux-deb9-hadrian:
    T12227 -7%
    T12545 -12.3%
    T5030  -10%
    T9872a -2%
    T9872b -2.1%
    T9872c -2.5%

Metric Decrease:
    T12227
    T12545
    T5030
    T9872a
    T9872b
    T9872c

- - - - -
1f57f526 by Felix Yan at 2020-08-10T14:23:18-04:00
Correct a typo in ghc.mk
- - - - -
1358f83f by Felix Yan at 2020-08-10T14:23:19-04:00
Add a closing parenthesis too

- - - - -
01655ec5 by Sylvain Henry at 2020-08-10T14:23:23-04:00
Make splitAtList strict in its arguments

Also fix its slightly wrong comment

Metric Decrease:
    T5030
    T12227
    T12545

- - - - -


5 changed files:

- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Utils/Misc.hs
- testsuite/tests/ghc-api/annotations/Makefile
- testsuite/tests/ghc-api/annotations/T10358.stdout
- utils/ghc-pkg/ghc.mk


Changes:

=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1201,13 +1201,14 @@ makeFunBind fn ms
 checkPatBind :: LPat GhcPs
              -> Located (a,GRHSs GhcPs (LHsExpr GhcPs))
              -> P ([AddAnn],HsBind GhcPs)
-checkPatBind lhs (L match_span (_,grhss))
+checkPatBind lhs (L rhs_span (_,grhss))
     | BangPat _ p <- unLoc lhs
     , VarPat _ v <- unLoc p
     = return ([], makeFunBind v [L match_span (m v)])
   where
+    match_span = combineSrcSpans (getLoc lhs) rhs_span
     m v = Match { m_ext = noExtField
-                , m_ctxt = FunRhs { mc_fun    = L (getLoc lhs) (unLoc v)
+                , m_ctxt = FunRhs { mc_fun    = v
                                   , mc_fixity = Prefix
                                   , mc_strictness = SrcStrict }
                 , m_pats = []


=====================================
compiler/GHC/Utils/Misc.hs
=====================================
@@ -6,6 +6,7 @@
 {-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE TupleSections #-}
 {-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE MagicHash #-}
 
 {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
 
@@ -774,12 +775,18 @@ dropList _  xs@[] = xs
 dropList (_:xs) (_:ys) = dropList xs ys
 
 
+-- | Given two lists xs and ys, return `splitAt (length xs) ys`.
 splitAtList :: [b] -> [a] -> ([a], [a])
-splitAtList [] xs     = ([], xs)
-splitAtList _ xs@[]   = (xs, xs)
-splitAtList (_:xs) (y:ys) = (y:ys', ys'')
-    where
-      (ys', ys'') = splitAtList 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)
+      --
+      -- 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]


=====================================
testsuite/tests/ghc-api/annotations/Makefile
=====================================
@@ -39,7 +39,8 @@ listcomps:
 
 .PHONY: T10358
 T10358:
-	$(CHECK_API_ANNOTATIONS) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" Test10358.hs
+	# Ignore result code, we have an unattached (superfluous) AnnBang
+	- $(CHECK_API_ANNOTATIONS) "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" Test10358.hs
 
 .PHONY: T10396
 T10396:


=====================================
testsuite/tests/ghc-api/annotations/T10358.stdout
=====================================
@@ -1,5 +1,5 @@
 ---Unattached Annotation Problems (should be empty list)---
-[]
+[(AnnBang, Test10358.hs:5:19)]
 ---Ann before enclosing span problem (should be empty list)---
 [
 


=====================================
utils/ghc-pkg/ghc.mk
=====================================
@@ -61,8 +61,8 @@ endif
 $(eval $(call build-prog,utils/ghc-pkg,dist,0))
 
 # ghc-pkg uses `settings` to figure out the target platform to figure out a
-# subdirectory for the user pkg db. So make sure `settings` exists (alterative
-# is to specify global package db only.
+# subdirectory for the user pkg db. So make sure `settings` exists (alternative
+# is to specify global package db only).
 $(ghc-pkg_INPLACE) : | $(INPLACE_PACKAGE_CONF)/. $(INPLACE_LIB)/settings
 
 # -----------------------------------------------------------------------------



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/090ca60400e8ecdcc4b35b28cf60d662b760a714...01655ec5a1c858c3fa36e295a63e854b8acce184

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/090ca60400e8ecdcc4b35b28cf60d662b760a714...01655ec5a1c858c3fa36e295a63e854b8acce184
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/b6cf46c1/attachment-0001.html>


More information about the ghc-commits mailing list