[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: Correct a typo in ghc.mk

Marge Bot gitlab at gitlab.haskell.org
Tue Aug 11 14:27:49 UTC 2020



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


Commits:
8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00
Correct a typo in ghc.mk
- - - - -
1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00
Add a closing parenthesis too

- - - - -
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

- - - - -
4fbe929d by Ben Gamari at 2020-08-11T10:27:44-04:00
typecheck: Drop SPECIALISE pragmas when there is no unfolding

Previously the desugarer would instead fall over when it realized that
there was no unfolding for an imported function with a SPECIALISE
pragma. We now rather drop the SPECIALISE pragma and throw a warning.

Fixes #18118.

- - - - -
d9845759 by Ben Gamari at 2020-08-11T10:27:44-04:00
testsuite: Add test for #18118

- - - - -
83c40ee9 by Sven Tennie at 2020-08-11T10:27:44-04:00
Add hie.yaml to ghc-heap

This enables IDE support by haskell-language-server for ghc-heap.

- - - - -
14575e70 by Ben Gamari at 2020-08-11T10:27:44-04:00
testsuite: Specify metrics collected by T17516

Previously it collected everything, including "max bytes used". This is
problematic since the test makes no attempt to control for deviations in
GC timing, resulting in high variability. Fix this by only collecting
"bytes allocated".

- - - - -


8 changed files:

- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Utils/Misc.hs
- + libraries/ghc-heap/hie.yaml
- testsuite/tests/perf/compiler/all.T
- + testsuite/tests/typecheck/should_compile/T18118.hs
- + testsuite/tests/typecheck/should_compile/T18118A.hs
- testsuite/tests/typecheck/should_compile/all.T
- utils/ghc-pkg/ghc.mk


Changes:

=====================================
compiler/GHC/Tc/Gen/Sig.hs
=====================================
@@ -826,9 +826,13 @@ tcImpPrags prags
 tcImpSpec :: (Name, Sig GhcRn) -> TcM [TcSpecPrag]
 tcImpSpec (name, prag)
  = do { id <- tcLookupId name
-      ; unless (isAnyInlinePragma (idInlinePragma id))
-               (addWarnTc NoReason (impSpecErr name))
-      ; tcSpecPrag id prag }
+      ; if isAnyInlinePragma (idInlinePragma id)
+        then tcSpecPrag id prag
+        else do { addWarnTc NoReason (impSpecErr name)
+                ; return [] } }
+      -- If there is no INLINE/INLINABLE pragma there will be no unfolding. In
+      -- that case, just delete the SPECIALISE pragma altogether, lest the
+      -- desugarer fall over because it can't find the unfolding. See #18118.
 
 impSpecErr :: Name -> SDoc
 impSpecErr name


=====================================
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]


=====================================
libraries/ghc-heap/hie.yaml
=====================================
@@ -0,0 +1,12 @@
+cradle:
+  multi:
+    - path: ./GHC/
+      config:
+        cradle:
+          cabal:
+            component: 'lib:ghc-heap'
+    - path: ./tests
+      config:
+        cradle:
+          direct:
+            arguments: []


=====================================
testsuite/tests/perf/compiler/all.T
=====================================
@@ -370,7 +370,7 @@ test('T16190',
 test('T16473', normal, makefile_test, ['T16473'])
 
 test('T17516',
-      [ collect_compiler_stats(),
+      [ collect_compiler_stats('bytes allocated', 5),
         extra_clean(['T17516A.hi', 'T17516A.o'])
       ],
       multimod_compile,


=====================================
testsuite/tests/typecheck/should_compile/T18118.hs
=====================================
@@ -0,0 +1,5 @@
+module T18118 (myfun) where
+
+import T18118A
+
+{-# SPECIALISE myfun :: Double #-}


=====================================
testsuite/tests/typecheck/should_compile/T18118A.hs
=====================================
@@ -0,0 +1,5 @@
+module T18118A where
+
+myfun :: a
+myfun = undefined
+


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -717,5 +717,6 @@ test('T17775-viewpats-a', normal, compile, [''])
 test('T17775-viewpats-b', normal, compile_fail, [''])
 test('T17775-viewpats-c', normal, compile_fail, [''])
 test('T17775-viewpats-d', normal, compile_fail, [''])
+test('T18118', normal, multimod_compile, ['T18118', '-v0'])
 test('T18412', normal, compile, [''])
 test('T18470', normal, compile, [''])


=====================================
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/01655ec5a1c858c3fa36e295a63e854b8acce184...14575e70224a5a0e6cacb58d0c9a69e17bbc2821

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/01655ec5a1c858c3fa36e295a63e854b8acce184...14575e70224a5a0e6cacb58d0c9a69e17bbc2821
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/20200811/f657da83/attachment-0001.html>


More information about the ghc-commits mailing list