[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: rts: Add stg_copyArray_barrier to RtsSymbols list

Marge Bot gitlab at gitlab.haskell.org
Tue Sep 8 14:32:00 UTC 2020



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


Commits:
3805c844 by Ben Gamari at 2020-09-08T10:31:52-04:00
rts: Add stg_copyArray_barrier to RtsSymbols list

It's incredible that this wasn't noticed until now.

- - - - -
ccc51e27 by Daishi Nakajima at 2020-09-08T10:31:53-04:00
testsuite: Output performance test results in tabular format
this was suggested in #18417.

Change the print format of the values.
* Shorten commit hash
* Reduce precision of the "Value" field
* Shorten metrics name
  * e.g. runtime/bytes allocated -> run/alloc
* Shorten "MetricsChange"
  * e.g. unchanged -> unch, increased -> incr

And, print the baseline environment if there are baselines that were
measured in a different environment than the current environment.

If all "Baseline commit" are the same, print it once.

- - - - -
c74e8a2e by Ryan Scott at 2020-09-08T10:31:54-04:00
Make the forall-or-nothing rule only apply to invisible foralls (#18660)

This fixes #18660 by changing `isLHsForAllTy` to
`isLHsInvisForAllTy`, which is sufficient to make the
`forall`-or-nothing rule only apply to invisible `forall`s. I also
updated some related documentation and Notes while I was in the
neighborhood.

- - - - -
a7430fab by Ben Gamari at 2020-09-08T10:31:54-04:00
gitlab-ci: Handle distributions without locales

Previously we would assume that the `locale` utility exists. However,
this is not so on Alpine as musl's locale support is essentially
non-existent.

(cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e)

- - - - -
dd5196ea by Ben Gamari at 2020-09-08T10:31:54-04:00
gitlab-ci: Accept Centos 7 C.utf8 locale

Centos apparently has C.utf8 rather than C.UTF-8.

(cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464)

- - - - -


10 changed files:

- .gitlab/ci.sh
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Rename/HsType.hs
- docs/users_guide/exts/explicit_forall.rst
- rts/RtsSymbols.c
- testsuite/driver/perf_notes.py
- testsuite/driver/runtests.py
- testsuite/driver/testutil.py
- + testsuite/tests/dependent/should_compile/T18660.hs
- testsuite/tests/dependent/should_compile/all.T


Changes:

=====================================
.gitlab/ci.sh
=====================================
@@ -58,6 +58,12 @@ function run() {
 TOP="$(pwd)"
 
 function setup_locale() {
+  # Musl doesn't provide locale support at all...
+  if ! which locale > /dev/null; then
+    info "No locale executable. Skipping locale setup..."
+    return
+  fi
+
   # BSD grep terminates early with -q, consequently locale -a will get a
   # SIGPIPE and the pipeline will fail with pipefail.
   shopt -o -u pipefail
@@ -70,6 +76,9 @@ function setup_locale() {
   elif locale -a | grep -q en_US.UTF-8; then
     # Centos doesn't have C.UTF-8
     export LANG=en_US.UTF-8
+  elif locale -a | grep -q en_US.utf8; then
+    # Centos doesn't have C.UTF-8
+    export LANG=en_US.utf8
   else
     error "Failed to find usable locale"
     info "Available locales:"


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -61,7 +61,7 @@ module GHC.Hs.Type (
         mkEmptyImplicitBndrs, mkEmptyWildCardBndrs,
         mkHsForAllVisTele, mkHsForAllInvisTele,
         mkHsQTvs, hsQTvExplicit, emptyLHsQTvs,
-        isHsKindedTyVar, hsTvbAllKinded, isLHsForAllTy,
+        isHsKindedTyVar, hsTvbAllKinded, isLHsInvisForAllTy,
         hsScopedTvs, hsWcScopedTvs, dropWildCards,
         hsTyVarName, hsAllLTyVarNames, hsLTyVarLocNames,
         hsLTyVarName, hsLTyVarNames, hsLTyVarLocName, hsExplicitLTyVarNames,
@@ -1278,9 +1278,12 @@ ignoreParens :: LHsType (GhcPass p) -> LHsType (GhcPass p)
 ignoreParens (L _ (HsParTy _ ty)) = ignoreParens ty
 ignoreParens ty                   = ty
 
-isLHsForAllTy :: LHsType (GhcPass p) -> Bool
-isLHsForAllTy (L _ (HsForAllTy {})) = True
-isLHsForAllTy _                     = False
+-- | Is this type headed by an invisible @forall@? This is used to determine
+-- if the type variables in a type should be implicitly quantified.
+-- See @Note [forall-or-nothing rule]@ in "GHC.Rename.HsType".
+isLHsInvisForAllTy :: LHsType (GhcPass p) -> Bool
+isLHsInvisForAllTy (L _ (HsForAllTy{hst_tele = HsForAllInvis{}})) = True
+isLHsInvisForAllTy _                                              = False
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Rename/HsType.hs
=====================================
@@ -168,7 +168,7 @@ rn_hs_sig_wc_type scoping ctxt hs_ty thing_inside
        ; let nwc_rdrs = nubL nwc_rdrs'
        ; implicit_bndrs <- case scoping of
            AlwaysBind       -> pure tv_rdrs
-           BindUnlessForall -> forAllOrNothing (isLHsForAllTy hs_ty) tv_rdrs
+           BindUnlessForall -> forAllOrNothing (isLHsInvisForAllTy hs_ty) tv_rdrs
            NeverBind        -> pure []
        ; rnImplicitBndrs Nothing implicit_bndrs $ \ vars ->
     do { (wcs, hs_ty', fvs1) <- rnWcBody ctxt nwc_rdrs hs_ty
@@ -321,7 +321,7 @@ rnHsSigType :: HsDocContext
 rnHsSigType ctx level (HsIB { hsib_body = hs_ty })
   = do { traceRn "rnHsSigType" (ppr hs_ty)
        ; rdr_env <- getLocalRdrEnv
-       ; vars0 <- forAllOrNothing (isLHsForAllTy hs_ty)
+       ; vars0 <- forAllOrNothing (isLHsInvisForAllTy hs_ty)
            $ filterInScope rdr_env
            $ extractHsTyRdrTyVars hs_ty
        ; rnImplicitBndrs Nothing vars0 $ \ vars ->
@@ -331,17 +331,43 @@ rnHsSigType ctx level (HsIB { hsib_body = hs_ty })
                        , hsib_body = body' }
                 , fvs ) } }
 
--- Note [forall-or-nothing rule]
--- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--- Free variables in signatures are usually bound in an implicit
--- 'forall' at the beginning of user-written signatures. However, if the
--- signature has an explicit forall at the beginning, this is disabled.
---
--- The idea is nested foralls express something which is only
--- expressible explicitly, while a top level forall could (usually) be
--- replaced with an implicit binding. Top-level foralls alone ("forall.") are
--- therefore an indication that the user is trying to be fastidious, so
--- we don't implicitly bind any variables.
+{-
+Note [forall-or-nothing rule]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Free variables in signatures are usually bound in an implicit 'forall' at the
+beginning of user-written signatures. However, if the signature has an
+explicit, invisible forall at the beginning, this is disabled.
+
+The idea is nested foralls express something which is only expressible
+explicitly, while a top level forall could (usually) be replaced with an
+implicit binding. Top-level foralls alone ("forall.") are therefore an
+indication that the user is trying to be fastidious, so we don't implicitly
+bind any variables.
+
+Note that this rule only applies to outermost /in/visible 'forall's, and not
+outermost visible 'forall's. See #18660 for more on this point.
+
+Here are some concrete examples to demonstrate the forall-or-nothing rule in
+action:
+
+  type F1 :: a -> b -> b                    -- Legal; a,b are implicitly quantified.
+                                            -- Equivalently: forall a b. a -> b -> b
+
+  type F2 :: forall a b. a -> b -> b        -- Legal; explicitly quantified
+
+  type F3 :: forall a. a -> b -> b          -- Illegal; the forall-or-nothing rule says that
+                                            -- if you quantify a, you must also quantify b
+
+  type F4 :: forall a -> b -> b             -- Legal; the top quantifier (forall a) is a /visible/
+                                            -- quantifer, so the "nothing" part of the forall-or-nothing
+                                            -- rule applies, and b is therefore implicitly quantified.
+                                            -- Equivalently: forall b. forall a -> b -> b
+
+  type F5 :: forall b. forall a -> b -> c   -- Illegal; the forall-or-nothing rule says that
+                                            -- if you quantify b, you must also quantify c
+
+  type F6 :: forall a -> forall b. b -> c   -- Legal: just like F4.
+-}
 
 -- | See @Note [forall-or-nothing rule]@. This tiny little function is used
 -- (rather than its small body inlined) to indicate that we are implementing


=====================================
docs/users_guide/exts/explicit_forall.rst
=====================================
@@ -56,30 +56,32 @@ The ``forall``-or-nothing rule
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
 In certain forms of types, type variables obey what is known as the
-"``forall``-or-nothing" rule: if a type has an outermost, explicit
-``forall``, then all of the type variables in the type must be explicitly
-quantified. These two examples illustrate how the rule works: ::
+"``forall``-or-nothing" rule: if a type has an outermost, explicit,
+invisible ``forall``, then all of the type variables in the type must be
+explicitly quantified. These two examples illustrate how the rule works: ::
 
   f  :: forall a b. a -> b -> b         -- OK, `a` and `b` are explicitly bound
   g  :: forall a. a -> forall b. b -> b -- OK, `a` and `b` are explicitly bound
   h  :: forall a. a -> b -> b           -- Rejected, `b` is not in scope
 
 The type signatures for ``f``, ``g``, and ``h`` all begin with an outermost
-``forall``, so every type variable in these signatures must be explicitly
-bound by a ``forall``. Both ``f`` and ``g`` obey the ``forall``-or-nothing
-rule, since they explicitly quantify ``a`` and ``b``. On the other hand,
-``h`` does not explicitly quantify ``b``, so GHC will reject its type
-signature for being improperly scoped.
+invisible ``forall``, so every type variable in these signatures must be
+explicitly bound by a ``forall``. Both ``f`` and ``g`` obey the
+``forall``-or-nothing rule, since they explicitly quantify ``a`` and ``b``. On
+the other hand, ``h`` does not explicitly quantify ``b``, so GHC will reject
+its type signature for being improperly scoped.
 
 In places where the ``forall``-or-nothing rule takes effect, if a type does
-*not* have an outermost ``forall``, then any type variables that are not
-explicitly bound by a ``forall`` become implicitly quantified. For example: ::
+*not* have an outermost invisible ``forall``, then any type variables that are
+not explicitly bound by a ``forall`` become implicitly quantified. For example: ::
 
   i :: a -> b -> b             -- `a` and `b` are implicitly quantified
   j :: a -> forall b. b -> b   -- `a` is implicitly quantified
   k :: (forall a. a -> b -> b) -- `b` is implicitly quantified
+  type L :: forall a -> b -> b -- `b` is implicitly quantified
 
-GHC will accept ``i``, ``j``, and ``k``'s type signatures. Note that:
+GHC will accept ``i``, ``j``, and ``k``'s type signatures, as well as ``L``'s
+kind signature. Note that:
 
 - ``j``'s signature is accepted despite its mixture of implicit and explicit
   quantification. As long as a ``forall`` is not an outermost one, it is fine
@@ -88,6 +90,9 @@ GHC will accept ``i``, ``j``, and ``k``'s type signatures. Note that:
   the ``forall`` is not an outermost ``forall``. The ``forall``-or-nothing
   rule is one of the few places in GHC where the presence or absence of
   parentheses can be semantically significant!
+- ``L``'s signature begins with an outermost ``forall``, but it is a *visible*
+  ``forall``, not an invisible ``forall``, and therefore does not trigger the
+  ``forall``-or-nothing rule.
 
 The ``forall``-or-nothing rule takes effect in the following places:
 


=====================================
rts/RtsSymbols.c
=====================================
@@ -710,6 +710,7 @@
       SymI_HasProto(stg_copySmallArrayzh)                               \
       SymI_HasProto(stg_copySmallMutableArrayzh)                        \
       SymI_HasProto(stg_casSmallArrayzh)                                \
+      SymI_HasProto(stg_copyArray_barrier)                              \
       SymI_HasProto(stg_newBCOzh)                                       \
       SymI_HasProto(stg_newByteArrayzh)                                 \
       SymI_HasProto(stg_casIntArrayzh)                                  \


=====================================
testsuite/driver/perf_notes.py
=====================================
@@ -22,7 +22,7 @@ import sys
 from collections import namedtuple
 from math import ceil, trunc
 
-from testutil import passed, failBecause, testing_metrics
+from testutil import passed, failBecause, testing_metrics, print_table
 from term_color import Color, colored
 
 from my_typing import *
@@ -45,6 +45,14 @@ def inside_git_repo() -> bool:
 def is_worktree_dirty() -> bool:
     return subprocess.check_output(['git', 'status', '--porcelain']) != b''
 
+# Get length of abbreviated git commit hash
+def get_abbrev_hash_length() -> int:
+    try:
+        return len(subprocess.check_output(['git', 'rev-parse',
+                                            '--short', 'HEAD']).strip())
+    except subprocess.CalledProcessError:
+        return 10
+
 #
 # Some data access functions. At the moment this uses git notes.
 #
@@ -100,6 +108,15 @@ class MetricChange(Enum):
         }
         return strings[self]
 
+    def short_name(self):
+        strings = {
+            MetricChange.NewMetric: "new",
+            MetricChange.NoChange:  "unch",
+            MetricChange.Increase:  "incr",
+            MetricChange.Decrease:  "decr"
+        }
+        return strings[self]
+
 AllowedPerfChange = NamedTuple('AllowedPerfChange',
                                [('direction', MetricChange),
                                 ('metrics', List[str]),
@@ -758,7 +775,7 @@ def main() -> None:
         exit(0)
 
     #
-    # String utilities for pretty-printing
+    # Print the data in tablular format
     #
 
     #                  T1234                 T1234
@@ -770,11 +787,12 @@ def main() -> None:
     # HEAD~1           10023                 10023
     # HEAD~2           21234                 21234
     # HEAD~3           20000                 20000
-
-    # Data is already in colum major format, so do that, calculate column widths
-    # then transpose and print each row.
     def strMetric(x):
         return '{:.2f}'.format(x.value) if x != None else ""
+    # Data is in colum major format, so transpose and pass to print_table.
+    T = TypeVar('T')
+    def transpose(xss: List[List[T]]) -> List[List[T]]:
+        return list(map(list, zip(*xss)))
 
     headerCols = [ ["","","","Commit"] ] \
                 + [ [name, metric, way, env] for (env, name, metric, way) in testSeries ]
@@ -782,17 +800,7 @@ def main() -> None:
                 + [ [strMetric(get_commit_metric(ref, commit, env, name, metric, way)) \
                         for commit in commits ] \
                         for (env, name, metric, way) in testSeries ]
-    colWidths = [max([2+len(cell) for cell in colH + colD]) for (colH,colD) in zip(headerCols, dataCols)]
-    col_fmts = ['{:>' + str(w) + '}' for w in colWidths]
-
-    def printCols(cols):
-        for row in zip(*cols):
-            # print(list(zip(col_fmts, row)))
-            print(''.join([f.format(cell) for (f,cell) in zip(col_fmts, row)]))
-
-    printCols(headerCols)
-    print('-'*(sum(colWidths)+2))
-    printCols(dataCols)
+    print_table(transpose(headerCols), transpose(dataCols))
 
 if __name__ == '__main__':
     main()


=====================================
testsuite/driver/runtests.py
=====================================
@@ -23,11 +23,11 @@ import traceback
 # So we import it here first, so that the testsuite doesn't appear to fail.
 import subprocess
 
-from testutil import getStdout, Watcher, str_warn, str_info
+from testutil import getStdout, Watcher, str_warn, str_info, print_table, shorten_metric_name
 from testglobals import getConfig, ghc_env, getTestRun, TestConfig, \
                         TestOptions, brokens, PerfMetric
 from my_typing import TestName
-from perf_notes import MetricChange, GitRef, inside_git_repo, is_worktree_dirty, format_perf_stat
+from perf_notes import MetricChange, GitRef, inside_git_repo, is_worktree_dirty, format_perf_stat, get_abbrev_hash_length, is_commit_hash
 from junit import junit
 import term_color
 from term_color import Color, colored
@@ -341,23 +341,52 @@ def cleanup_and_exit(exitcode):
     exit(exitcode)
 
 def tabulate_metrics(metrics: List[PerfMetric]) -> None:
-    for metric in sorted(metrics, key=lambda m: (m.stat.test, m.stat.way, m.stat.metric)):
-        print("{test:24}  {metric:40}  {value:15.3f}".format(
-            test = "{}({})".format(metric.stat.test, metric.stat.way),
-            metric = metric.stat.metric,
-            value = metric.stat.value
-        ))
-        if metric.baseline is not None:
-            val0 = metric.baseline.perfStat.value
-            val1 = metric.stat.value
-            rel = 100 * (val1 - val0) / val0
-            print("{space:24}  {herald:40}  {value:15.3f}  [{direction}, {rel:2.1f}%]".format(
-                space = "",
-                herald = "(baseline @ {commit})".format(
-                    commit = metric.baseline.commit),
-                value = val0,
-                direction = metric.change,
-                rel = rel
+    abbrevLen = get_abbrev_hash_length()
+    hasBaseline = any([x.baseline is not None for x in metrics])
+    baselineCommitSet = set([x.baseline.commit for x in metrics if x.baseline is not None])
+    hideBaselineCommit = not hasBaseline or len(baselineCommitSet) == 1
+    hideBaselineEnv = not hasBaseline or all(
+        [x.stat.test_env == x.baseline.perfStat.test_env
+         for x in metrics if x.baseline is not None])
+    def row(cells: Tuple[str, str, str, str, str, str, str]) -> List[str]:
+        return [x for (idx, x) in enumerate(list(cells)) if
+                (idx != 2 or not hideBaselineCommit) and
+                (idx != 3 or not hideBaselineEnv )]
+
+    headerRows = [
+        row(("", "", "Baseline", "Baseline", "Baseline", "", "")),
+        row(("Test", "Metric", "commit", "environment", "value", "New value", "Change"))
+    ]
+    def strDiff(x: PerfMetric) -> str:
+        if x.baseline is None:
+            return ""
+        val0 = x.baseline.perfStat.value
+        val1 = x.stat.value
+        return "{}({:+2.1f}%)".format(x.change.short_name(), 100 * (val1 - val0) / val0)
+    dataRows = [row((
+        "{}({})".format(x.stat.test, x.stat.way),
+        shorten_metric_name(x.stat.metric),
+          "{}".format(x.baseline.commit[:abbrevLen]
+                      if is_commit_hash(x.baseline.commit) else x.baseline.commit)
+          if x.baseline is not None else "",
+        "{}".format(x.baseline.perfStat.test_env)
+          if x.baseline is not None else "",
+        "{:13.1f}".format(x.baseline.perfStat.value)
+          if x.baseline is not None else "",
+        "{:13.1f}".format(x.stat.value),
+        strDiff(x)
+    )) for x in sorted(metrics, key =
+                      lambda m: (m.stat.test, m.stat.way, m.stat.metric))]
+    print_table(headerRows, dataRows, 1)
+    print("")
+    if hasBaseline:
+        if hideBaselineEnv:
+            print("* All baselines were measured in the same environment as this test run")
+        if hideBaselineCommit:
+            commit = next(iter(baselineCommitSet))
+            print("* All baseline commits are {}".format(
+                commit[:abbrevLen]
+                if is_commit_hash(commit) else commit
             ))
 
 # First collect all the tests to be run


=====================================
testsuite/driver/testutil.py
=====================================
@@ -144,3 +144,29 @@ def memoize(f):
 
     cached._cache = None
     return cached
+
+# Print the matrix data in a tabular format.
+def print_table(header_rows: List[List[str]], data_rows: List[List[str]], padding=2) -> None:
+    # Calculate column widths then print each row.
+    colWidths = [(0 if idx == 0 else padding) + max([len(cell) for cell in col])
+                 for (idx, col) in enumerate(zip(*(header_rows + data_rows)))]
+    col_fmts = ['{:>' + str(w) + '}' for w in colWidths]
+
+    def printCols(cols):
+        for row in cols:
+            print(''.join([f.format(cell) for (f,cell) in zip(col_fmts, row)]))
+
+    printCols(header_rows)
+    print('-' * sum(colWidths))
+    printCols(data_rows)
+
+def shorten_metric_name(name: str) -> str:
+    dic = {
+        "runtime/bytes allocated": "run/alloc",
+        "runtime/peak_megabytes_allocated": "run/peak",
+        "runtime/max_bytes_used": "run/max",
+        "compile_time/bytes allocated": "ghc/alloc",
+        "compile_time/peak_megabytes_allocated": "ghc/peak",
+        "compile_time/max_bytes_used": "ghc/max",
+    }
+    return dic.get(name, name)


=====================================
testsuite/tests/dependent/should_compile/T18660.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
+module T18660 where
+
+type F :: forall a -> b -> b
+type F x y = y


=====================================
testsuite/tests/dependent/should_compile/all.T
=====================================
@@ -66,3 +66,4 @@ test('T16326_Compile2', normal, compile, [''])
 test('T16391a', normal, compile, [''])
 test('T16344b', normal, compile, [''])
 test('T16347', normal, compile, [''])
+test('T18660', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae81705781fe1646f1c1f862b37cf1905397e8b3...dd5196ea57a5cdfa80ff943c298e05002f9ca621

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae81705781fe1646f1c1f862b37cf1905397e8b3...dd5196ea57a5cdfa80ff943c298e05002f9ca621
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/20200908/89a70f48/attachment-0001.html>


More information about the ghc-commits mailing list